convert all per-uuid log files to use Builder
Mostly didn't push the ByteStrings down very deep, but all of these log files are not written to frequently at all, so slight remaining innefficiency doesn't matter. In Logs.UUID, removed the fixBadUUID code that cleaned up after a bug in git-annex versions 3.20111105-3.20111110. In the unlikely event that a repo was last touched by that ancient git-annex version, the descriptions of remotes would appear missing when used with this version of git-annex. That is such minor breakage, and so unlikely to still be a problem for any repos, that it was not worth forward-porting that code to ByteString.
This commit is contained in:
parent
de4980ef85
commit
2fef43dd71
16 changed files with 70 additions and 54 deletions
|
@ -44,8 +44,9 @@ dropDead f content trustmap = case getLogVariety f of
|
|||
-- because git remotes may still exist, and they need
|
||||
-- to still know it's dead.
|
||||
| f == trustLog -> PreserveFile
|
||||
| otherwise -> ChangeFile $ encodeBL $
|
||||
UUIDBased.showLog id $ dropDeadFromMapLog trustmap id $ UUIDBased.parseLog Just (decodeBL content)
|
||||
| otherwise -> ChangeFile $ toLazyByteString $
|
||||
UUIDBased.buildLog (byteString . encodeBS) $
|
||||
dropDeadFromMapLog trustmap id $ UUIDBased.parseLog Just (decodeBL content)
|
||||
Just NewUUIDBasedLog -> ChangeFile $ toLazyByteString $
|
||||
UUIDBased.buildLogNew (byteString . encodeBS) $
|
||||
dropDeadFromMapLog trustmap id $
|
||||
|
|
|
@ -17,6 +17,11 @@ git-annex (7.20181212) UNRELEASED; urgency=medium
|
|||
* The benchmark command, which only had some old benchmarking of the sqlite
|
||||
databases before, now allows benchmarking any other git-annex commands.
|
||||
* Support being built with ghc 8.6.3 (MonadFail).
|
||||
* Removed old code that cleaned up after a bug in git-annex versions
|
||||
3.20111105-3.20111110. In the unlikely event that a repo was
|
||||
last touched by that ancient git-annex version, the descriptions
|
||||
of remotes would appear missing when used with this version of
|
||||
git-annex.
|
||||
|
||||
-- Joey Hess <id@joeyh.name> Tue, 18 Dec 2018 12:24:52 -0400
|
||||
|
||||
|
|
|
@ -17,6 +17,8 @@ import qualified Annex.Branch
|
|||
import Logs
|
||||
import Logs.UUIDBased
|
||||
|
||||
import Data.ByteString.Builder
|
||||
|
||||
data Activity = Fsck
|
||||
deriving (Eq, Read, Show, Enum, Bounded)
|
||||
|
||||
|
@ -24,7 +26,9 @@ recordActivity :: Activity -> UUID -> Annex ()
|
|||
recordActivity act uuid = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change activityLog $
|
||||
encodeBL . showLog show . changeLog c uuid act . parseLog readish . decodeBL
|
||||
buildLog (byteString . encodeBS . show)
|
||||
. changeLog c uuid act
|
||||
. parseLog readish . decodeBL
|
||||
|
||||
lastActivities :: Maybe Activity -> Annex (Log Activity)
|
||||
lastActivities wantact = parseLog onlywanted . decodeBL <$> Annex.Branch.get activityLog
|
||||
|
|
|
@ -51,6 +51,6 @@ parseLog = parseMapLog fieldparser valueparser
|
|||
buildLog :: ChunkLog -> Builder
|
||||
buildLog = buildMapLog fieldbuilder valuebuilder
|
||||
where
|
||||
fieldbuilder (u, m) = byteString (fromUUID u) <> sep <> buildChunkMethod m
|
||||
fieldbuilder (u, m) = buildUUID u <> sep <> buildChunkMethod m
|
||||
valuebuilder = integerDec
|
||||
sep = charUtf8 ':'
|
||||
|
|
|
@ -13,6 +13,7 @@ module Logs.Difference (
|
|||
) where
|
||||
|
||||
import qualified Data.Map as M
|
||||
import Data.ByteString.Builder
|
||||
|
||||
import Annex.Common
|
||||
import Types.Difference
|
||||
|
@ -25,7 +26,9 @@ recordDifferences :: Differences -> UUID -> Annex ()
|
|||
recordDifferences ds@(Differences {}) uuid = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change differenceLog $
|
||||
encodeBL . showLog id . changeLog c uuid (showDifferences ds) . parseLog Just . decodeBL
|
||||
buildLog (byteString . encodeBS)
|
||||
. changeLog c uuid (showDifferences ds)
|
||||
. parseLog Just . decodeBL
|
||||
recordDifferences UnknownDifferences _ = return ()
|
||||
|
||||
-- Map of UUIDs that have Differences recorded.
|
||||
|
|
|
@ -108,8 +108,8 @@ buildExportLog :: MapLog ExportParticipants Exported -> Builder
|
|||
buildExportLog = buildMapLog buildExportParticipants buildExported
|
||||
|
||||
buildExportParticipants :: ExportParticipants -> Builder
|
||||
buildExportParticipants ep = byteString (fromUUID (exportFrom ep))
|
||||
<> sep <> byteString (fromUUID (exportTo ep))
|
||||
buildExportParticipants ep =
|
||||
buildUUID (exportFrom ep) <> sep <> buildUUID (exportTo ep)
|
||||
where
|
||||
sep = charUtf8 ':'
|
||||
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{- git-annex group log
|
||||
-
|
||||
- Copyright 2012 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2012, 2019 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
@ -18,6 +18,7 @@ module Logs.Group (
|
|||
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
import Data.ByteString.Builder
|
||||
|
||||
import Annex.Common
|
||||
import Logs
|
||||
|
@ -37,7 +38,7 @@ groupChange uuid@(UUID _) modifier = do
|
|||
curr <- lookupGroups uuid
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change groupLog $
|
||||
encodeBL . showLog (unwords . S.toList) .
|
||||
buildLog buildGroup .
|
||||
changeLog c uuid (modifier curr) .
|
||||
parseLog (Just . S.fromList . words) . decodeBL
|
||||
|
||||
|
@ -48,6 +49,13 @@ groupChange uuid@(UUID _) modifier = do
|
|||
}
|
||||
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 = byteString . encodeBS
|
||||
|
||||
groupSet :: UUID -> S.Set Group -> Annex ()
|
||||
groupSet u g = groupChange u (const g)
|
||||
|
||||
|
|
|
@ -39,7 +39,6 @@ buildMapLog fieldbuilder valuebuilder = mconcat . map genline . M.toList
|
|||
sp = charUtf8 ' '
|
||||
nl = charUtf8 '\n'
|
||||
|
||||
|
||||
parseMapLog :: Ord f => (String -> Maybe f) -> (String -> Maybe v) -> String -> MapLog f v
|
||||
parseMapLog fieldparser valueparser = M.fromListWith best . mapMaybe parse . splitLines
|
||||
where
|
||||
|
|
|
@ -17,6 +17,7 @@ import Logs
|
|||
import Logs.UUIDBased
|
||||
|
||||
import qualified Data.Map as M
|
||||
import Data.ByteString.Builder
|
||||
|
||||
newtype Fingerprint = Fingerprint String
|
||||
deriving (Eq, Read, Show)
|
||||
|
@ -25,7 +26,9 @@ recordFingerprint :: Fingerprint -> UUID -> Annex ()
|
|||
recordFingerprint fp uuid = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change multicastLog $
|
||||
encodeBL . showLog show . changeLog c uuid fp . parseLog readish . decodeBL
|
||||
buildLog (byteString . encodeBS . show)
|
||||
. changeLog c uuid fp
|
||||
. parseLog readish . decodeBL
|
||||
|
||||
knownFingerPrints :: Annex (M.Map UUID Fingerprint)
|
||||
knownFingerPrints = simpleMap . parseLog readish . decodeBL <$> Annex.Branch.get activityLog
|
||||
|
|
|
@ -30,7 +30,7 @@ setLog :: FilePath -> UUID -> PreferredContentExpression -> Annex ()
|
|||
setLog logfile uuid@(UUID _) val = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change logfile $
|
||||
encodeBL . showLog id
|
||||
buildLog (byteString . encodeBS)
|
||||
. changeLog c uuid val
|
||||
. parseLog Just . decodeBL
|
||||
Annex.changeState $ \s -> s
|
||||
|
|
|
@ -26,13 +26,16 @@ import Logs.UUIDBased
|
|||
|
||||
import qualified Data.Map as M
|
||||
import Data.Char
|
||||
import Data.ByteString.Builder
|
||||
|
||||
{- Adds or updates a remote's config in the log. -}
|
||||
configSet :: UUID -> RemoteConfig -> Annex ()
|
||||
configSet u cfg = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change remoteLog $
|
||||
encodeBL . showLog showConfig . changeLog c u cfg . parseLog parseConfig . decodeBL
|
||||
buildLog (byteString . encodeBS . showConfig)
|
||||
. changeLog c u cfg
|
||||
. parseLog parseConfig . decodeBL
|
||||
|
||||
{- Map of remotes by uuid containing key/value config maps. -}
|
||||
readRemoteLog :: Annex (M.Map UUID RemoteConfig)
|
||||
|
|
|
@ -20,6 +20,7 @@ module Logs.Schedule (
|
|||
import qualified Data.Map as M
|
||||
import qualified Data.Set as S
|
||||
import Data.Time.LocalTime
|
||||
import Data.ByteString.Builder
|
||||
|
||||
import Annex.Common
|
||||
import Types.ScheduledActivity
|
||||
|
@ -32,7 +33,9 @@ scheduleSet :: UUID -> [ScheduledActivity] -> Annex ()
|
|||
scheduleSet uuid@(UUID _) activities = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change scheduleLog $
|
||||
encodeBL . showLog id . changeLog c uuid val . parseLog Just . decodeBL
|
||||
buildLog (byteString . encodeBS)
|
||||
. changeLog c uuid val
|
||||
. parseLog Just . decodeBL
|
||||
where
|
||||
val = fromScheduledActivities activities
|
||||
scheduleSet NoUUID _ = error "unknown UUID; cannot modify"
|
||||
|
|
|
@ -19,12 +19,14 @@ import Logs
|
|||
import Logs.UUIDBased
|
||||
import Logs.Trust.Pure as X
|
||||
|
||||
import Data.ByteString.Builder
|
||||
|
||||
{- Changes the trust level for a uuid in the trustLog. -}
|
||||
trustSet :: UUID -> TrustLevel -> Annex ()
|
||||
trustSet uuid@(UUID _) level = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change trustLog $
|
||||
encodeBL . showLog showTrustLog .
|
||||
buildLog (byteString . encodeBS . showTrustLog) .
|
||||
changeLog c uuid level .
|
||||
parseLog (Just . parseTrustLog) . decodeBL
|
||||
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
|
||||
|
|
35
Logs/UUID.hs
35
Logs/UUID.hs
|
@ -2,7 +2,7 @@
|
|||
-
|
||||
- uuid.log stores a list of known uuids, and their descriptions.
|
||||
-
|
||||
- Copyright 2010-2012 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2010-2019 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
@ -30,36 +30,9 @@ describeUUID :: UUID -> UUIDDesc -> Annex ()
|
|||
describeUUID uuid desc = do
|
||||
c <- liftIO currentVectorClock
|
||||
Annex.Branch.change uuidLog $
|
||||
encodeBL . showLog id . changeLog c uuid (fromUUIDDesc desc) . fixBadUUID . parseLog Just . decodeBL
|
||||
|
||||
{- Temporarily here to fix badly formatted uuid logs generated by
|
||||
- versions 3.20111105 and 3.20111025.
|
||||
-
|
||||
- Those logs contain entries with the UUID and description flipped.
|
||||
- Due to parsing, if the description is multiword, only the first
|
||||
- will be taken to be the UUID. So, if the UUID of an entry does
|
||||
- not look like a UUID, and the last word of the description does,
|
||||
- flip them back.
|
||||
-}
|
||||
fixBadUUID :: Log String -> Log String
|
||||
fixBadUUID = M.fromList . map fixup . M.toList
|
||||
where
|
||||
fixup (k, v)
|
||||
| isbad = (fixeduuid, LogEntry (newertime v) fixedvalue)
|
||||
| otherwise = (k, v)
|
||||
where
|
||||
kuuid = fromUUID k
|
||||
isbad = not (isuuid kuuid) && not (null ws) && isuuid lastword
|
||||
ws = words $ value v
|
||||
lastword = Prelude.last ws
|
||||
fixeduuid = toUUID lastword
|
||||
fixedvalue = unwords $ kuuid: Prelude.init ws
|
||||
-- For the fixed line to take precidence, it should be
|
||||
-- slightly newer, but only slightly.
|
||||
newertime (LogEntry (VectorClock c) _) = VectorClock (c + minimumPOSIXTimeSlice)
|
||||
newertime (LogEntry Unknown _) = VectorClock minimumPOSIXTimeSlice
|
||||
minimumPOSIXTimeSlice = 0.000001
|
||||
isuuid s = length s == 36 && length (splitc '-' s) == 5
|
||||
buildLog buildUUIDDesc
|
||||
. changeLog c uuid desc
|
||||
. parseLog (Just . UUIDDesc . encodeBS) . decodeBL
|
||||
|
||||
{- The map is cached for speed. -}
|
||||
uuidDescMap :: Annex UUIDDescMap
|
||||
|
|
|
@ -14,6 +14,8 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Logs.UUIDBased (
|
||||
Log,
|
||||
LogEntry(..),
|
||||
|
@ -22,7 +24,7 @@ module Logs.UUIDBased (
|
|||
parseLog,
|
||||
parseLogNew,
|
||||
parseLogWithUUID,
|
||||
showLog,
|
||||
buildLog,
|
||||
buildLogNew,
|
||||
changeLog,
|
||||
addLog,
|
||||
|
@ -41,13 +43,16 @@ import Data.ByteString.Builder
|
|||
|
||||
type Log v = MapLog UUID v
|
||||
|
||||
showLog :: (v -> String) -> Log v -> String
|
||||
showLog shower = unlines . map showpair . M.toList
|
||||
buildLog :: (v -> Builder) -> Log v -> Builder
|
||||
buildLog builder = mconcat . map genline . M.toList
|
||||
where
|
||||
showpair (k, LogEntry (VectorClock c) v) =
|
||||
unwords [fromUUID k, shower v, tskey ++ show c]
|
||||
showpair (k, LogEntry Unknown v) =
|
||||
unwords [fromUUID k, shower v]
|
||||
genline (u, LogEntry c@(VectorClock {}) v) =
|
||||
buildUUID u <> sp <> builder v <> sp <>
|
||||
byteString "timestamp=" <> buildVectorClock c <> nl
|
||||
genline (u, LogEntry Unknown v) =
|
||||
buildUUID u <> sp <> builder v <> nl
|
||||
sp = charUtf8 ' '
|
||||
nl = charUtf8 '\n'
|
||||
|
||||
parseLog :: (String -> Maybe a) -> String -> Log a
|
||||
parseLog = parseLogWithUUID . const
|
||||
|
@ -77,7 +82,7 @@ parseLogWithUUID parser = M.fromListWith best . mapMaybe parse . splitLines
|
|||
| otherwise = drop 1 $ beginning ws
|
||||
|
||||
buildLogNew :: (v -> Builder) -> Log v -> Builder
|
||||
buildLogNew = buildMapLog (byteString . fromUUID)
|
||||
buildLogNew = buildMapLog buildUUID
|
||||
|
||||
parseLogNew :: (String -> Maybe v) -> String -> Log v
|
||||
parseLogNew = parseMapLog (Just . toUUID)
|
||||
|
|
|
@ -14,6 +14,7 @@ import qualified Data.Map as M
|
|||
import qualified Data.UUID as U
|
||||
import Data.Maybe
|
||||
import Data.String
|
||||
import Data.ByteString.Builder
|
||||
|
||||
import Utility.FileSystemEncoding
|
||||
import qualified Utility.SimpleProtocol as Proto
|
||||
|
@ -54,6 +55,9 @@ instance ToUUID String where
|
|||
instance ToUUID U.UUID where
|
||||
toUUID = toUUID . U.toASCIIBytes
|
||||
|
||||
buildUUID :: UUID -> Builder
|
||||
buildUUID (UUID b) = byteString b
|
||||
|
||||
isUUID :: String -> Bool
|
||||
isUUID = isJust . U.fromString
|
||||
|
||||
|
@ -67,6 +71,9 @@ fromUUIDDesc (UUIDDesc d) = decodeBS d
|
|||
toUUIDDesc :: String -> UUIDDesc
|
||||
toUUIDDesc = UUIDDesc . encodeBS
|
||||
|
||||
buildUUIDDesc :: UUIDDesc -> Builder
|
||||
buildUUIDDesc (UUIDDesc b) = byteString b
|
||||
|
||||
type UUIDDescMap = M.Map UUID UUIDDesc
|
||||
|
||||
instance Proto.Serializable UUID where
|
||||
|
|
Loading…
Add table
Reference in a new issue