refactoring
filterBranch should be reusable for copy-branch command. Changed LogVariety to differentiate between LocationLog and UrlLog; only location logs contain uuids and need to be filtered by uuid, while url logs do not. This does not change current behavior, but it will let filterBranch be reused without filtering url logs incorrectly.
This commit is contained in:
parent
13a8706cda
commit
4ff8a1ae2b
3 changed files with 55 additions and 64 deletions
|
@ -678,7 +678,7 @@ performTransitionsLocked jl ts neednewlocalbranch transitionedrefs = do
|
||||||
trustmap <- calcTrustMap <$> getStaged trustLog
|
trustmap <- calcTrustMap <$> getStaged trustLog
|
||||||
remoteconfigmap <- calcRemoteConfigMap <$> getStaged remoteLog
|
remoteconfigmap <- calcRemoteConfigMap <$> getStaged remoteLog
|
||||||
-- partially apply, improves performance
|
-- partially apply, improves performance
|
||||||
let changers' = map (\c -> c config trustmap remoteconfigmap) changers
|
let changers' = map (\c -> c trustmap remoteconfigmap config) changers
|
||||||
(fs, cleanup) <- branchFiles
|
(fs, cleanup) <- branchFiles
|
||||||
forM_ fs $ \f -> do
|
forM_ fs $ \f -> do
|
||||||
content <- getStaged f
|
content <- getStaged f
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex branch transitions
|
{- git-annex branch transitions
|
||||||
-
|
-
|
||||||
- Copyright 2013-2019 Joey Hess <id@joeyh.name>
|
- Copyright 2013-2021 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -36,9 +36,9 @@ data FileTransition
|
||||||
= ChangeFile Builder
|
= ChangeFile Builder
|
||||||
| PreserveFile
|
| PreserveFile
|
||||||
|
|
||||||
type TransitionCalculator = GitConfig -> TrustMap -> M.Map UUID RemoteConfig -> RawFilePath -> L.ByteString -> FileTransition
|
type TransitionCalculator = GitConfig -> RawFilePath -> L.ByteString -> FileTransition
|
||||||
|
|
||||||
getTransitionCalculator :: Transition -> Maybe TransitionCalculator
|
getTransitionCalculator :: Transition -> Maybe (TrustMap -> M.Map UUID RemoteConfig -> TransitionCalculator)
|
||||||
getTransitionCalculator ForgetGitHistory = Nothing
|
getTransitionCalculator ForgetGitHistory = Nothing
|
||||||
getTransitionCalculator ForgetDeadRemotes = Just dropDead
|
getTransitionCalculator ForgetDeadRemotes = Just dropDead
|
||||||
|
|
||||||
|
@ -54,36 +54,17 @@ getTransitionCalculator ForgetDeadRemotes = Just dropDead
|
||||||
-- the latter uuid, that also needs to be removed. The sameas-uuid
|
-- the latter uuid, that also needs to be removed. The sameas-uuid
|
||||||
-- is not removed from the remote log, for the same reason the trust log
|
-- is not removed from the remote log, for the same reason the trust log
|
||||||
-- is not changed.
|
-- is not changed.
|
||||||
dropDead :: TransitionCalculator
|
dropDead :: TrustMap -> M.Map UUID RemoteConfig -> TransitionCalculator
|
||||||
dropDead gc trustmap remoteconfigmap f content = case getLogVariety gc f of
|
dropDead trustmap remoteconfigmap gc f content
|
||||||
Just OldUUIDBasedLog
|
| f == trustLog = PreserveFile
|
||||||
| f == trustLog -> PreserveFile
|
| f == remoteLog = ChangeFile $
|
||||||
| f == remoteLog -> ChangeFile $
|
Remote.buildRemoteConfigLog $
|
||||||
Remote.buildRemoteConfigLog $
|
M.mapWithKey minimizesameasdead $
|
||||||
M.mapWithKey minimizesameasdead $
|
filterMapLog (notdead trustmap) id $
|
||||||
dropDeadFromMapLog trustmap id $
|
Remote.parseRemoteConfigLog content
|
||||||
Remote.parseRemoteConfigLog content
|
| otherwise = filterBranch (notdead trustmap') gc f content
|
||||||
| otherwise -> ChangeFile $
|
|
||||||
UUIDBased.buildLogOld byteString $
|
|
||||||
dropDeadFromMapLog trustmap' id $
|
|
||||||
UUIDBased.parseLogOld A.takeByteString content
|
|
||||||
Just NewUUIDBasedLog -> ChangeFile $
|
|
||||||
UUIDBased.buildLogNew byteString $
|
|
||||||
dropDeadFromMapLog trustmap' id $
|
|
||||||
UUIDBased.parseLogNew A.takeByteString content
|
|
||||||
Just (ChunkLog _) -> ChangeFile $
|
|
||||||
Chunk.buildLog $ dropDeadFromMapLog trustmap' fst $
|
|
||||||
Chunk.parseLog content
|
|
||||||
Just (PresenceLog _) -> ChangeFile $ Presence.buildLog $
|
|
||||||
Presence.compactLog $
|
|
||||||
dropDeadFromPresenceLog trustmap' $
|
|
||||||
Presence.parseLog content
|
|
||||||
Just RemoteMetaDataLog -> ChangeFile $ MetaData.buildLog $
|
|
||||||
dropDeadFromRemoteMetaDataLog trustmap' $
|
|
||||||
MetaData.simplifyLog $ MetaData.parseLog content
|
|
||||||
Just OtherLog -> PreserveFile
|
|
||||||
Nothing -> PreserveFile
|
|
||||||
where
|
where
|
||||||
|
notdead m u = M.findWithDefault def u m /= DeadTrusted
|
||||||
trustmap' = trustmap `M.union`
|
trustmap' = trustmap `M.union`
|
||||||
M.map (const DeadTrusted) (M.filter sameasdead remoteconfigmap)
|
M.map (const DeadTrusted) (M.filter sameasdead remoteconfigmap)
|
||||||
sameasdead cm =
|
sameasdead cm =
|
||||||
|
@ -96,19 +77,37 @@ dropDead gc trustmap remoteconfigmap f content = case getLogVariety gc f of
|
||||||
| otherwise = l
|
| otherwise = l
|
||||||
minimizesameasdead' c = M.restrictKeys c (S.singleton sameasUUIDField)
|
minimizesameasdead' c = M.restrictKeys c (S.singleton sameasUUIDField)
|
||||||
|
|
||||||
dropDeadFromMapLog :: TrustMap -> (k -> UUID) -> M.Map k v -> M.Map k v
|
filterBranch :: (UUID -> Bool) -> TransitionCalculator
|
||||||
dropDeadFromMapLog trustmap getuuid =
|
filterBranch wantuuid gc f content = case getLogVariety gc f of
|
||||||
M.filterWithKey $ \k _v -> notDead trustmap getuuid k
|
Just OldUUIDBasedLog -> ChangeFile $
|
||||||
|
UUIDBased.buildLogOld byteString $
|
||||||
|
filterMapLog wantuuid id $
|
||||||
|
UUIDBased.parseLogOld A.takeByteString content
|
||||||
|
Just NewUUIDBasedLog -> ChangeFile $
|
||||||
|
UUIDBased.buildLogNew byteString $
|
||||||
|
filterMapLog wantuuid id $
|
||||||
|
UUIDBased.parseLogNew A.takeByteString content
|
||||||
|
Just (ChunkLog _) -> ChangeFile $
|
||||||
|
Chunk.buildLog $ filterMapLog wantuuid fst $
|
||||||
|
Chunk.parseLog content
|
||||||
|
Just (LocationLog _) -> ChangeFile $ Presence.buildLog $
|
||||||
|
Presence.compactLog $
|
||||||
|
filterLocationLog wantuuid $
|
||||||
|
Presence.parseLog content
|
||||||
|
Just (UrlLog _) -> PreserveFile
|
||||||
|
Just RemoteMetaDataLog -> ChangeFile $ MetaData.buildLog $
|
||||||
|
filterRemoteMetaDataLog wantuuid $
|
||||||
|
MetaData.simplifyLog $ MetaData.parseLog content
|
||||||
|
Just OtherLog -> PreserveFile
|
||||||
|
Nothing -> PreserveFile
|
||||||
|
|
||||||
{- Presence logs can contain UUIDs or other values. Any line that matches
|
filterMapLog :: (UUID -> Bool) -> (k -> UUID) -> M.Map k v -> M.Map k v
|
||||||
- a dead uuid is dropped; any other values are passed through. -}
|
filterMapLog wantuuid getuuid = M.filterWithKey $ \k _v -> wantuuid (getuuid k)
|
||||||
dropDeadFromPresenceLog :: TrustMap -> [Presence.LogLine] -> [Presence.LogLine]
|
|
||||||
dropDeadFromPresenceLog trustmap =
|
|
||||||
filter $ notDead trustmap (toUUID . Presence.fromLogInfo . Presence.info)
|
|
||||||
|
|
||||||
dropDeadFromRemoteMetaDataLog :: TrustMap -> MetaData.Log MetaData -> MetaData.Log MetaData
|
filterLocationLog :: (UUID -> Bool) -> [Presence.LogLine] -> [Presence.LogLine]
|
||||||
dropDeadFromRemoteMetaDataLog trustmap =
|
filterLocationLog wantuuid = filter $
|
||||||
MetaData.filterOutEmpty . MetaData.filterRemoteMetaData (notDead trustmap id)
|
wantuuid . toUUID . Presence.fromLogInfo . Presence.info
|
||||||
|
|
||||||
notDead :: TrustMap -> (v -> UUID) -> v -> Bool
|
filterRemoteMetaDataLog :: (UUID -> Bool) -> MetaData.Log MetaData -> MetaData.Log MetaData
|
||||||
notDead trustmap a v = M.findWithDefault def (a v) trustmap /= DeadTrusted
|
filterRemoteMetaDataLog wantuuid =
|
||||||
|
MetaData.filterOutEmpty . MetaData.filterRemoteMetaData wantuuid
|
||||||
|
|
28
Logs.hs
28
Logs.hs
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex log file names
|
{- git-annex log file names
|
||||||
-
|
-
|
||||||
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
|
- Copyright 2013-2021 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -20,7 +20,8 @@ data LogVariety
|
||||||
= OldUUIDBasedLog
|
= OldUUIDBasedLog
|
||||||
| NewUUIDBasedLog
|
| NewUUIDBasedLog
|
||||||
| ChunkLog Key
|
| ChunkLog Key
|
||||||
| PresenceLog Key
|
| LocationLog Key
|
||||||
|
| UrlLog Key
|
||||||
| RemoteMetaDataLog
|
| RemoteMetaDataLog
|
||||||
| OtherLog
|
| OtherLog
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
@ -33,10 +34,11 @@ getLogVariety config f
|
||||||
| f `elem` topLevelNewUUIDBasedLogs = Just NewUUIDBasedLog
|
| f `elem` topLevelNewUUIDBasedLogs = Just NewUUIDBasedLog
|
||||||
| isRemoteStateLog f = Just NewUUIDBasedLog
|
| isRemoteStateLog f = Just NewUUIDBasedLog
|
||||||
| isRemoteContentIdentifierLog f = Just NewUUIDBasedLog
|
| isRemoteContentIdentifierLog f = Just NewUUIDBasedLog
|
||||||
| isChunkLog f = ChunkLog <$> extLogFileKey chunkLogExt f
|
|
||||||
| isRemoteMetaDataLog f = Just RemoteMetaDataLog
|
| isRemoteMetaDataLog f = Just RemoteMetaDataLog
|
||||||
| isMetaDataLog f || f `elem` otherLogs = Just OtherLog
|
| isMetaDataLog f || f `elem` otherTopLevelLogs = Just OtherLog
|
||||||
| otherwise = PresenceLog <$> firstJust (presenceLogs config f)
|
| otherwise = (LocationLog <$> locationLogFileKey config f)
|
||||||
|
<|> (ChunkLog <$> extLogFileKey chunkLogExt f)
|
||||||
|
<|> (UrlLog <$> urlLogFileKey f)
|
||||||
|
|
||||||
{- Typical number of log files that may be read while processing a single
|
{- Typical number of log files that may be read while processing a single
|
||||||
- key. This is used to size a cache.
|
- key. This is used to size a cache.
|
||||||
|
@ -79,16 +81,9 @@ topLevelNewUUIDBasedLogs =
|
||||||
[ exportLog
|
[ exportLog
|
||||||
]
|
]
|
||||||
|
|
||||||
{- All the ways to get a key from a presence log file -}
|
{- Other top-level logs. -}
|
||||||
presenceLogs :: GitConfig -> RawFilePath -> [Maybe Key]
|
otherTopLevelLogs :: [RawFilePath]
|
||||||
presenceLogs config f =
|
otherTopLevelLogs =
|
||||||
[ urlLogFileKey f
|
|
||||||
, locationLogFileKey config f
|
|
||||||
]
|
|
||||||
|
|
||||||
{- Top-level logs that are neither UUID based nor presence logs. -}
|
|
||||||
otherLogs :: [RawFilePath]
|
|
||||||
otherLogs =
|
|
||||||
[ numcopiesLog
|
[ numcopiesLog
|
||||||
, mincopiesLog
|
, mincopiesLog
|
||||||
, configLog
|
, configLog
|
||||||
|
@ -192,9 +187,6 @@ chunkLogFile config key =
|
||||||
chunkLogExt :: S.ByteString
|
chunkLogExt :: S.ByteString
|
||||||
chunkLogExt = ".log.cnk"
|
chunkLogExt = ".log.cnk"
|
||||||
|
|
||||||
isChunkLog :: RawFilePath -> Bool
|
|
||||||
isChunkLog path = chunkLogExt `S.isSuffixOf` path
|
|
||||||
|
|
||||||
{- The filename of the metadata log for a given key. -}
|
{- The filename of the metadata log for a given key. -}
|
||||||
metaDataLogFile :: GitConfig -> Key -> RawFilePath
|
metaDataLogFile :: GitConfig -> Key -> RawFilePath
|
||||||
metaDataLogFile config key =
|
metaDataLogFile config key =
|
||||||
|
|
Loading…
Reference in a new issue