bd5affa362
This deals with the possible security problem that someone could make an unusually low UUID and generate keys that are all constructed to hash to a number that, mod the number of repositories in the group, == 0. So balanced preferred content would always put those keys in the repository with the low UUID as long as the group contains the number of repositories that the attacker anticipated. Presumably the attacker than holds the data for ransom? Dunno. Anyway, the partial solution is to use HMAC (sha256) with all the UUIDs combined together as the "secret", and the key as the "message". Now any change in the set of UUIDs in a group will invalidate the attacker's constructed keys from hashing to anything in particular. Given that there are plenty of other things someone can do if they can write to the repository -- including modifying preferred content so only their repository wants files, and numcopies so other repositories drom them -- this seems like safeguard enough. Note that, in balancedPicker, combineduuids is memoized.
100 lines
3 KiB
Haskell
100 lines
3 KiB
Haskell
{- git-annex group log
|
|
-
|
|
- Copyright 2012-2024 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
-}
|
|
|
|
module Logs.Group (
|
|
groupLog,
|
|
groupChange,
|
|
groupSet,
|
|
lookupGroups,
|
|
groupMap,
|
|
groupMapLoad,
|
|
getStandardGroup,
|
|
inUnwantedGroup
|
|
) where
|
|
|
|
import qualified Data.Map as M
|
|
import qualified Data.Set as S
|
|
import qualified Data.Attoparsec.ByteString as A
|
|
import qualified Data.Attoparsec.ByteString.Char8 as A8
|
|
import Data.ByteString.Builder
|
|
|
|
import Annex.Common
|
|
import Logs
|
|
import qualified Annex.Branch
|
|
import qualified Annex
|
|
import Logs.UUIDBased
|
|
import Types.Group
|
|
import Types.StandardGroups
|
|
import Annex.Balanced
|
|
|
|
{- Returns the groups of a given repo UUID. -}
|
|
lookupGroups :: UUID -> Annex (S.Set Group)
|
|
lookupGroups u = (fromMaybe S.empty . M.lookup u) . groupsByUUID <$> groupMap
|
|
|
|
{- Applies a set modifier to change the groups for a uuid in the groupLog. -}
|
|
groupChange :: UUID -> (S.Set Group -> S.Set Group) -> Annex ()
|
|
groupChange uuid@(UUID _) modifier = do
|
|
curr <- lookupGroups uuid
|
|
c <- currentVectorClock
|
|
Annex.Branch.change (Annex.Branch.RegardingUUID [uuid]) groupLog $
|
|
buildLogOld buildGroup . changeLog c uuid (modifier curr) . parseLogOld parseGroup
|
|
|
|
-- The changed group invalidates the preferred content cache.
|
|
Annex.changeState $ \s -> s
|
|
{ Annex.groupmap = Nothing
|
|
, Annex.preferredcontentmap = Nothing
|
|
}
|
|
groupChange NoUUID _ = error "unknown UUID; cannot modify"
|
|
|
|
buildGroup :: S.Set Group -> Builder
|
|
buildGroup = go . S.toList
|
|
where
|
|
go [] = mempty
|
|
go (g:gs) = bld g <> mconcat [ charUtf8 ' ' <> bld g' | g' <- gs ]
|
|
bld (Group g) = byteString g
|
|
|
|
parseGroup :: A.Parser (S.Set Group)
|
|
parseGroup = S.fromList <$> go []
|
|
where
|
|
go l = (A.endOfInput *> pure l)
|
|
<|> ((getgroup <* A8.char ' ') >>= go . (:l))
|
|
<|> ((:l) <$> getgroup)
|
|
-- allow extra writespace before or after a group name
|
|
<|> (A8.char ' ' >>= const (go l))
|
|
getgroup = Group <$> A8.takeWhile1 (/= ' ')
|
|
|
|
groupSet :: UUID -> S.Set Group -> Annex ()
|
|
groupSet u g = groupChange u (const g)
|
|
|
|
{- The map is cached for speed. -}
|
|
groupMap :: Annex GroupMap
|
|
groupMap = maybe groupMapLoad return =<< Annex.getState Annex.groupmap
|
|
|
|
{- Loads the map, updating the cache. -}
|
|
groupMapLoad :: Annex GroupMap
|
|
groupMapLoad = do
|
|
m <- makeGroupMap . simpleMap . parseLogOld parseGroup
|
|
<$> Annex.Branch.get groupLog
|
|
Annex.changeState $ \s -> s { Annex.groupmap = Just m }
|
|
return m
|
|
|
|
makeGroupMap :: M.Map UUID (S.Set Group) -> GroupMap
|
|
makeGroupMap byuuid = GroupMap byuuid bygroup (M.map balancedPicker bygroup)
|
|
where
|
|
bygroup = M.fromListWith S.union $
|
|
concatMap explode $ M.toList byuuid
|
|
explode (u, s) = map (\g -> (g, S.singleton u)) (S.toList s)
|
|
|
|
{- If a repository is in exactly one standard group, returns it. -}
|
|
getStandardGroup :: S.Set Group -> Maybe StandardGroup
|
|
getStandardGroup s = case mapMaybe toStandardGroup $ S.toList s of
|
|
[g] -> Just g
|
|
_ -> Nothing
|
|
|
|
inUnwantedGroup :: UUID -> Annex Bool
|
|
inUnwantedGroup u = elem UnwantedGroup
|
|
. mapMaybe toStandardGroup . S.toList <$> lookupGroups u
|