renamings to make clean when old-format logs are being used

This commit is contained in:
Joey Hess 2019-02-21 13:43:21 -04:00
parent fd304dce60
commit 9887a378fe
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
17 changed files with 56 additions and 57 deletions

View file

@ -40,15 +40,15 @@ getTransitionCalculator ForgetDeadRemotes = Just dropDead
dropDead :: FilePath -> L.ByteString -> TrustMap -> FileTransition dropDead :: FilePath -> L.ByteString -> TrustMap -> FileTransition
dropDead f content trustmap = case getLogVariety f of dropDead f content trustmap = case getLogVariety f of
Just UUIDBasedLog Just OldUUIDBasedLog
-- Don't remove the dead repo from the trust log, -- Don't remove the dead repo from the trust log,
-- because git remotes may still exist, and they need -- because git remotes may still exist, and they need
-- to still know it's dead. -- to still know it's dead.
| f == trustLog -> PreserveFile | f == trustLog -> PreserveFile
| otherwise -> ChangeFile $ | otherwise -> ChangeFile $
UUIDBased.buildLog byteString $ UUIDBased.buildLogOld byteString $
dropDeadFromMapLog trustmap id $ dropDeadFromMapLog trustmap id $
UUIDBased.parseLog A.takeByteString content UUIDBased.parseLogOld A.takeByteString content
Just NewUUIDBasedLog -> ChangeFile $ Just NewUUIDBasedLog -> ChangeFile $
UUIDBased.buildLogNew byteString $ UUIDBased.buildLogNew byteString $
dropDeadFromMapLog trustmap id $ dropDeadFromMapLog trustmap id $

10
Logs.hs
View file

@ -12,7 +12,7 @@ import Annex.DirHashes
{- There are several varieties of log file formats. -} {- There are several varieties of log file formats. -}
data LogVariety data LogVariety
= UUIDBasedLog = OldUUIDBasedLog
| NewUUIDBasedLog | NewUUIDBasedLog
| ChunkLog Key | ChunkLog Key
| PresenceLog Key | PresenceLog Key
@ -24,16 +24,16 @@ data LogVariety
- of logs used by git-annex, if it's a known path. -} - of logs used by git-annex, if it's a known path. -}
getLogVariety :: FilePath -> Maybe LogVariety getLogVariety :: FilePath -> Maybe LogVariety
getLogVariety f getLogVariety f
| f `elem` topLevelUUIDBasedLogs = Just UUIDBasedLog | f `elem` topLevelOldUUIDBasedLogs = Just OldUUIDBasedLog
| isRemoteStateLog f || isRemoteContentIdentifierLog f = Just NewUUIDBasedLog | isRemoteStateLog f || isRemoteContentIdentifierLog f = Just NewUUIDBasedLog
| isChunkLog f = ChunkLog <$> chunkLogFileKey f | isChunkLog f = ChunkLog <$> chunkLogFileKey f
| isRemoteMetaDataLog f = Just RemoteMetaDataLog | isRemoteMetaDataLog f = Just RemoteMetaDataLog
| isMetaDataLog f || f `elem` otherLogs = Just OtherLog | isMetaDataLog f || f `elem` otherLogs = Just OtherLog
| otherwise = PresenceLog <$> firstJust (presenceLogs f) | otherwise = PresenceLog <$> firstJust (presenceLogs f)
{- All the uuid-based logs stored in the top of the git-annex branch. -} {- All the (old-format) uuid-based logs stored in the top of the git-annex branch. -}
topLevelUUIDBasedLogs :: [FilePath] topLevelOldUUIDBasedLogs :: [FilePath]
topLevelUUIDBasedLogs = topLevelOldUUIDBasedLogs =
[ uuidLog [ uuidLog
, remoteLog , remoteLog
, trustLog , trustLog

View file

@ -29,12 +29,12 @@ recordActivity :: Activity -> UUID -> Annex ()
recordActivity act uuid = do recordActivity act uuid = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change activityLog $ Annex.Branch.change activityLog $
buildLog buildActivity buildLogOld buildActivity
. changeLog c uuid (Right act) . changeLog c uuid (Right act)
. parseLog parseActivity . parseLogOld parseActivity
lastActivities :: Maybe Activity -> Annex (Log Activity) lastActivities :: Maybe Activity -> Annex (Log Activity)
lastActivities wantact = parseLog (onlywanted =<< parseActivity) lastActivities wantact = parseLogOld (onlywanted =<< parseActivity)
<$> Annex.Branch.get activityLog <$> Annex.Branch.get activityLog
where where
onlywanted (Right a) | wanted a = pure a onlywanted (Right a) | wanted a = pure a

View file

@ -14,7 +14,7 @@ module Logs.ContentIdentifier (
import Annex.Common import Annex.Common
import Logs import Logs
import Logs.MapLog import Logs.MapLog
import Types.Remote (ContentIdentifier) import Types.Import
import qualified Annex.Branch import qualified Annex.Branch
import Logs.ContentIdentifier.Pure as X import Logs.ContentIdentifier.Pure as X
import qualified Annex import qualified Annex

View file

@ -10,8 +10,8 @@
module Logs.ContentIdentifier.Pure where module Logs.ContentIdentifier.Pure where
import Annex.Common import Annex.Common
import Logs.MapLog import Logs.UUIDBased
import Types.Remote (ContentIdentifier(..)) import Types.Import
import Utility.Base64 import Utility.Base64
import qualified Data.ByteString as S import qualified Data.ByteString as S
@ -21,10 +21,10 @@ import qualified Data.Attoparsec.ByteString.Lazy as A
import qualified Data.Attoparsec.ByteString.Char8 as A8 import qualified Data.Attoparsec.ByteString.Char8 as A8
import Data.ByteString.Builder import Data.ByteString.Builder
type ContentIdentifierLog = MapLog UUID [ContentIdentifier] type ContentIdentifierLog = Log [ContentIdentifier]
buildLog :: ContentIdentifierLog -> Builder buildLog :: ContentIdentifierLog -> Builder
buildLog = buildMapLog buildUUID buildContentIdentifierList buildLog = buildLogNew buildContentIdentifierList
buildContentIdentifierList :: [ContentIdentifier] -> Builder buildContentIdentifierList :: [ContentIdentifier] -> Builder
buildContentIdentifierList l = case l of buildContentIdentifierList l = case l of
@ -38,9 +38,7 @@ buildContentIdentifierList l = case l of
| otherwise = byteString c | otherwise = byteString c
parseLog :: L.ByteString -> ContentIdentifierLog parseLog :: L.ByteString -> ContentIdentifierLog
parseLog = parseMapLog parseLog = parseLogNew parseContentIdentifierList
(toUUID <$> A.takeByteString)
parseContentIdentifierList
parseContentIdentifierList :: A.Parser [ContentIdentifier] parseContentIdentifierList :: A.Parser [ContentIdentifier]
parseContentIdentifierList = reverse . catMaybes <$> valueparser [] parseContentIdentifierList = reverse . catMaybes <$> valueparser []

View file

@ -27,9 +27,9 @@ recordDifferences :: Differences -> UUID -> Annex ()
recordDifferences ds@(Differences {}) uuid = do recordDifferences ds@(Differences {}) uuid = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change differenceLog $ Annex.Branch.change differenceLog $
buildLog byteString buildLogOld byteString
. changeLog c uuid (encodeBS $ showDifferences ds) . changeLog c uuid (encodeBS $ showDifferences ds)
. parseLog A.takeByteString . parseLogOld A.takeByteString
recordDifferences UnknownDifferences _ = return () recordDifferences UnknownDifferences _ = return ()
-- Map of UUIDs that have Differences recorded. -- Map of UUIDs that have Differences recorded.

View file

@ -20,7 +20,7 @@ import Logs.UUIDBased
parseDifferencesLog :: L.ByteString -> (M.Map UUID Differences) parseDifferencesLog :: L.ByteString -> (M.Map UUID Differences)
parseDifferencesLog = simpleMap parseDifferencesLog = simpleMap
. parseLog (readDifferences . decodeBS <$> A.takeByteString) . parseLogOld (readDifferences . decodeBS <$> A.takeByteString)
-- The sum of all recorded differences, across all UUIDs. -- The sum of all recorded differences, across all UUIDs.
allDifferences :: M.Map UUID Differences -> Differences allDifferences :: M.Map UUID Differences -> Differences

View file

@ -40,7 +40,7 @@ groupChange uuid@(UUID _) modifier = do
curr <- lookupGroups uuid curr <- lookupGroups uuid
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change groupLog $ Annex.Branch.change groupLog $
buildLog buildGroup . changeLog c uuid (modifier curr) . parseLog parseGroup buildLogOld buildGroup . changeLog c uuid (modifier curr) . parseLogOld parseGroup
-- The changed group invalidates the preferred content cache. -- The changed group invalidates the preferred content cache.
Annex.changeState $ \s -> s Annex.changeState $ \s -> s
@ -76,7 +76,8 @@ groupMap = maybe groupMapLoad return =<< Annex.getState Annex.groupmap
{- Loads the map, updating the cache. -} {- Loads the map, updating the cache. -}
groupMapLoad :: Annex GroupMap groupMapLoad :: Annex GroupMap
groupMapLoad = do groupMapLoad = do
m <- makeGroupMap . simpleMap . parseLog parseGroup <$> Annex.Branch.get groupLog m <- makeGroupMap . simpleMap . parseLogOld parseGroup
<$> Annex.Branch.get groupLog
Annex.changeState $ \s -> s { Annex.groupmap = Just m } Annex.changeState $ \s -> s { Annex.groupmap = Just m }
return m return m

View file

@ -27,12 +27,12 @@ recordFingerprint :: Fingerprint -> UUID -> Annex ()
recordFingerprint fp uuid = do recordFingerprint fp uuid = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change multicastLog $ Annex.Branch.change multicastLog $
buildLog buildFindgerPrint buildLogOld buildFindgerPrint
. changeLog c uuid fp . changeLog c uuid fp
. parseLog fingerprintParser . parseLogOld fingerprintParser
knownFingerPrints :: Annex (M.Map UUID Fingerprint) knownFingerPrints :: Annex (M.Map UUID Fingerprint)
knownFingerPrints = simpleMap . parseLog fingerprintParser knownFingerPrints = simpleMap . parseLogOld fingerprintParser
<$> Annex.Branch.get activityLog <$> Annex.Branch.get activityLog
fingerprintParser :: A.Parser Fingerprint fingerprintParser :: A.Parser Fingerprint

View file

@ -74,7 +74,7 @@ preferredRequiredMapsLoad = do
groupmap <- groupMap groupmap <- groupMap
configmap <- readRemoteLog configmap <- readRemoteLog
let genmap l gm = simpleMap let genmap l gm = simpleMap
. parseLogWithUUID (\u -> makeMatcher groupmap configmap gm u . decodeBS <$> A.takeByteString) . parseLogOldWithUUID (\u -> makeMatcher groupmap configmap gm u . decodeBS <$> A.takeByteString)
<$> Annex.Branch.get l <$> Annex.Branch.get l
pc <- genmap preferredContentLog =<< groupPreferredContentMapRaw pc <- genmap preferredContentLog =<< groupPreferredContentMapRaw
rc <- genmap requiredContentLog M.empty rc <- genmap requiredContentLog M.empty

View file

@ -32,9 +32,9 @@ setLog :: FilePath -> UUID -> PreferredContentExpression -> Annex ()
setLog logfile uuid@(UUID _) val = do setLog logfile uuid@(UUID _) val = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change logfile $ Annex.Branch.change logfile $
buildLog buildPreferredContentExpression buildLogOld buildPreferredContentExpression
. changeLog c uuid val . changeLog c uuid val
. parseLog parsePreferredContentExpression . parseLogOld parsePreferredContentExpression
Annex.changeState $ \s -> s Annex.changeState $ \s -> s
{ Annex.preferredcontentmap = Nothing { Annex.preferredcontentmap = Nothing
, Annex.requiredcontentmap = Nothing , Annex.requiredcontentmap = Nothing
@ -70,11 +70,11 @@ buildPreferredContentExpression :: PreferredContentExpression -> Builder
buildPreferredContentExpression = byteString . encodeBS buildPreferredContentExpression = byteString . encodeBS
preferredContentMapRaw :: Annex (M.Map UUID PreferredContentExpression) preferredContentMapRaw :: Annex (M.Map UUID PreferredContentExpression)
preferredContentMapRaw = simpleMap . parseLog parsePreferredContentExpression preferredContentMapRaw = simpleMap . parseLogOld parsePreferredContentExpression
<$> Annex.Branch.get preferredContentLog <$> Annex.Branch.get preferredContentLog
requiredContentMapRaw :: Annex (M.Map UUID PreferredContentExpression) requiredContentMapRaw :: Annex (M.Map UUID PreferredContentExpression)
requiredContentMapRaw = simpleMap . parseLog parsePreferredContentExpression requiredContentMapRaw = simpleMap . parseLogOld parsePreferredContentExpression
<$> Annex.Branch.get requiredContentLog <$> Annex.Branch.get requiredContentLog
groupPreferredContentMapRaw :: Annex (M.Map Group PreferredContentExpression) groupPreferredContentMapRaw :: Annex (M.Map Group PreferredContentExpression)

View file

@ -33,13 +33,13 @@ configSet :: UUID -> RemoteConfig -> Annex ()
configSet u cfg = do configSet u cfg = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change remoteLog $ Annex.Branch.change remoteLog $
buildLog (byteString . encodeBS . showConfig) buildLogOld (byteString . encodeBS . showConfig)
. changeLog c u cfg . changeLog c u cfg
. parseLog remoteConfigParser . parseLogOld remoteConfigParser
{- Map of remotes by uuid containing key/value config maps. -} {- Map of remotes by uuid containing key/value config maps. -}
readRemoteLog :: Annex (M.Map UUID RemoteConfig) readRemoteLog :: Annex (M.Map UUID RemoteConfig)
readRemoteLog = simpleMap . parseLog remoteConfigParser readRemoteLog = simpleMap . parseLogOld remoteConfigParser
<$> Annex.Branch.get remoteLog <$> Annex.Branch.get remoteLog
remoteConfigParser :: A.Parser RemoteConfig remoteConfigParser :: A.Parser RemoteConfig

View file

@ -34,15 +34,15 @@ scheduleSet :: UUID -> [ScheduledActivity] -> Annex ()
scheduleSet uuid@(UUID _) activities = do scheduleSet uuid@(UUID _) activities = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change scheduleLog $ Annex.Branch.change scheduleLog $
buildLog byteString buildLogOld byteString
. changeLog c uuid (encodeBS val) . changeLog c uuid (encodeBS val)
. parseLog A.takeByteString . parseLogOld A.takeByteString
where where
val = fromScheduledActivities activities val = fromScheduledActivities activities
scheduleSet NoUUID _ = error "unknown UUID; cannot modify" scheduleSet NoUUID _ = error "unknown UUID; cannot modify"
scheduleMap :: Annex (M.Map UUID [ScheduledActivity]) scheduleMap :: Annex (M.Map UUID [ScheduledActivity])
scheduleMap = simpleMap . parseLog parser <$> Annex.Branch.get scheduleLog scheduleMap = simpleMap . parseLogOld parser <$> Annex.Branch.get scheduleLog
where where
parser = either fail pure . parseScheduledActivities . decodeBS parser = either fail pure . parseScheduledActivities . decodeBS
=<< A.takeByteString =<< A.takeByteString

View file

@ -24,9 +24,9 @@ trustSet :: UUID -> TrustLevel -> Annex ()
trustSet uuid@(UUID _) level = do trustSet uuid@(UUID _) level = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change trustLog $ Annex.Branch.change trustLog $
buildLog buildTrustLevel . buildLogOld buildTrustLevel .
changeLog c uuid level . changeLog c uuid level .
parseLog trustLevelParser parseLogOld trustLevelParser
Annex.changeState $ \s -> s { Annex.trustmap = Nothing } Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
trustSet NoUUID _ = error "unknown UUID; cannot modify" trustSet NoUUID _ = error "unknown UUID; cannot modify"

View file

@ -19,7 +19,7 @@ import qualified Data.Attoparsec.ByteString.Char8 as A8
import Data.ByteString.Builder import Data.ByteString.Builder
calcTrustMap :: L.ByteString -> TrustMap calcTrustMap :: L.ByteString -> TrustMap
calcTrustMap = simpleMap . parseLog trustLevelParser calcTrustMap = simpleMap . parseLogOld trustLevelParser
trustLevelParser :: A.Parser TrustLevel trustLevelParser :: A.Parser TrustLevel
trustLevelParser = (totrust <$> A8.anyChar <* A.endOfInput) trustLevelParser = (totrust <$> A8.anyChar <* A.endOfInput)

View file

@ -32,7 +32,7 @@ describeUUID :: UUID -> UUIDDesc -> Annex ()
describeUUID uuid desc = do describeUUID uuid desc = do
c <- liftIO currentVectorClock c <- liftIO currentVectorClock
Annex.Branch.change uuidLog $ Annex.Branch.change uuidLog $
buildLog buildUUIDDesc . changeLog c uuid desc . parseUUIDLog buildLogOld buildUUIDDesc . changeLog c uuid desc . parseUUIDLog
{- The map is cached for speed. -} {- The map is cached for speed. -}
uuidDescMap :: Annex UUIDDescMap uuidDescMap :: Annex UUIDDescMap
@ -53,4 +53,4 @@ uuidDescMapLoad = do
preferold = flip const preferold = flip const
parseUUIDLog :: L.ByteString -> Log UUIDDesc parseUUIDLog :: L.ByteString -> Log UUIDDesc
parseUUIDLog = parseLog (UUIDDesc <$> A.takeByteString) parseUUIDLog = parseLogOld (UUIDDesc <$> A.takeByteString)

View file

@ -3,9 +3,9 @@
- This is used to store information about UUIDs in a way that can - This is used to store information about UUIDs in a way that can
- be union merged. - be union merged.
- -
- A line of the log will look like: "UUID[ INFO[ timestamp=foo]]" - The old format looks like: "UUID[ INFO[ timestamp=foo]]"
- The timestamp is last for backwards compatability reasons, - The timestamp is last for backwards compatability reasons,
- and may not be present on old log lines. - and may not be present on very old log lines.
- -
- New uuid based logs instead use the form: "timestamp UUID INFO" - New uuid based logs instead use the form: "timestamp UUID INFO"
- -
@ -21,10 +21,10 @@ module Logs.UUIDBased (
LogEntry(..), LogEntry(..),
VectorClock, VectorClock,
currentVectorClock, currentVectorClock,
parseLog, parseLogOld,
parseLogNew, parseLogNew,
parseLogWithUUID, parseLogOldWithUUID,
buildLog, buildLogOld,
buildLogNew, buildLogNew,
changeLog, changeLog,
addLog, addLog,
@ -48,8 +48,8 @@ import qualified Data.DList as D
type Log v = MapLog UUID v type Log v = MapLog UUID v
buildLog :: (v -> Builder) -> Log v -> Builder buildLogOld :: (v -> Builder) -> Log v -> Builder
buildLog builder = mconcat . map genline . M.toList buildLogOld builder = mconcat . map genline . M.toList
where where
genline (u, LogEntry c@(VectorClock {}) v) = genline (u, LogEntry c@(VectorClock {}) v) =
buildUUID u <> sp <> builder v <> sp <> buildUUID u <> sp <> builder v <> sp <>
@ -59,15 +59,15 @@ buildLog builder = mconcat . map genline . M.toList
sp = charUtf8 ' ' sp = charUtf8 ' '
nl = charUtf8 '\n' nl = charUtf8 '\n'
parseLog :: A.Parser a -> L.ByteString -> Log a parseLogOld :: A.Parser a -> L.ByteString -> Log a
parseLog = parseLogWithUUID . const parseLogOld = parseLogOldWithUUID . const
parseLogWithUUID :: (UUID -> A.Parser a) -> L.ByteString -> Log a parseLogOldWithUUID :: (UUID -> A.Parser a) -> L.ByteString -> Log a
parseLogWithUUID parser = fromMaybe M.empty . A.maybeResult parseLogOldWithUUID parser = fromMaybe M.empty . A.maybeResult
. A.parse (logParser parser) . A.parse (logParserOld parser)
logParser :: (UUID -> A.Parser a) -> A.Parser (Log a) logParserOld :: (UUID -> A.Parser a) -> A.Parser (Log a)
logParser parser = M.fromListWith best <$> parseLogLines go logParserOld parser = M.fromListWith best <$> parseLogLines go
where where
go = do go = do
u <- toUUID <$> A8.takeWhile1 (/= ' ') u <- toUUID <$> A8.takeWhile1 (/= ' ')