avoid accidental Show of VectorClock
Removed its Show instance.
This commit is contained in:
parent
2cecc8d2a3
commit
0b307f43e1
6 changed files with 29 additions and 27 deletions
|
@ -21,7 +21,7 @@ import Utility.QuickCheck
|
|||
-- | Some very old logs did not have any time stamp at all;
|
||||
-- Unknown is used for those.
|
||||
data VectorClock = Unknown | VectorClock POSIXTime
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord)
|
||||
|
||||
-- Unknown is oldest.
|
||||
prop_VectorClock_sane :: Bool
|
||||
|
@ -37,3 +37,10 @@ currentVectorClock = go =<< getEnv "GIT_ANNEX_VECTOR_CLOCK"
|
|||
go (Just s) = case parsePOSIXTime s of
|
||||
Just t -> return (VectorClock t)
|
||||
Nothing -> VectorClock <$> getPOSIXTime
|
||||
|
||||
formatVectorClock :: VectorClock -> String
|
||||
formatVectorClock Unknown = "0"
|
||||
formatVectorClock (VectorClock t) = show t
|
||||
|
||||
parseVectorClock :: String -> Maybe VectorClock
|
||||
parseVectorClock t = VectorClock <$> parsePOSIXTime t
|
||||
|
|
|
@ -19,7 +19,6 @@ module Logs.MapLog (
|
|||
|
||||
import Common
|
||||
import Annex.VectorClock
|
||||
import Logs.TimeStamp
|
||||
import Logs.Line
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
@ -27,7 +26,7 @@ import qualified Data.Map as M
|
|||
data LogEntry v = LogEntry
|
||||
{ changed :: VectorClock
|
||||
, value :: v
|
||||
} deriving (Eq, Show)
|
||||
} deriving (Eq)
|
||||
|
||||
type MapLog f v = M.Map f (LogEntry v)
|
||||
|
||||
|
@ -43,9 +42,9 @@ parseMapLog :: Ord f => (String -> Maybe f) -> (String -> Maybe v) -> String ->
|
|||
parseMapLog fieldparser valueparser = M.fromListWith best . mapMaybe parse . splitLines
|
||||
where
|
||||
parse line = do
|
||||
let (ts, rest) = splitword line
|
||||
let (sc, rest) = splitword line
|
||||
(sf, sv) = splitword rest
|
||||
c <- VectorClock <$> parsePOSIXTime ts
|
||||
c <- parseVectorClock sc
|
||||
f <- fieldparser sf
|
||||
v <- valueparser sv
|
||||
Just (f, LogEntry c v)
|
||||
|
|
|
@ -9,7 +9,6 @@ module Logs.Presence.Pure where
|
|||
|
||||
import Annex.Common
|
||||
import Annex.VectorClock
|
||||
import Logs.TimeStamp
|
||||
import Logs.Line
|
||||
import Utility.QuickCheck
|
||||
|
||||
|
@ -19,7 +18,10 @@ data LogLine = LogLine
|
|||
{ date :: VectorClock
|
||||
, status :: LogStatus
|
||||
, info :: String
|
||||
} deriving (Eq, Show)
|
||||
} deriving (Eq)
|
||||
|
||||
instance Show LogLine where
|
||||
show l = "LogLine " ++ formatVectorClock (date l) ++ show (status l) ++ " " ++ show (info l)
|
||||
|
||||
data LogStatus = InfoPresent | InfoMissing | InfoDead
|
||||
deriving (Eq, Show, Bounded, Enum)
|
||||
|
@ -29,12 +31,12 @@ parseLog :: String -> [LogLine]
|
|||
parseLog = mapMaybe parseline . splitLines
|
||||
where
|
||||
parseline l = LogLine
|
||||
<$> (VectorClock <$> parsePOSIXTime d)
|
||||
<$> parseVectorClock c
|
||||
<*> parseStatus s
|
||||
<*> pure rest
|
||||
where
|
||||
(d, pastd) = separate (== ' ') l
|
||||
(s, rest) = separate (== ' ') pastd
|
||||
(c, pastc) = separate (== ' ') l
|
||||
(s, rest) = separate (== ' ') pastc
|
||||
|
||||
parseStatus :: String -> Maybe LogStatus
|
||||
parseStatus "1" = Just InfoPresent
|
||||
|
@ -46,7 +48,7 @@ parseStatus _ = Nothing
|
|||
showLog :: [LogLine] -> String
|
||||
showLog = unlines . map genline
|
||||
where
|
||||
genline (LogLine d s i) = unwords [show d, genstatus s, i]
|
||||
genline (LogLine c s i) = unwords [formatVectorClock c, genstatus s, i]
|
||||
genstatus InfoPresent = "1"
|
||||
genstatus InfoMissing = "0"
|
||||
genstatus InfoDead = "X"
|
||||
|
|
|
@ -15,7 +15,6 @@ module Logs.SingleValue where
|
|||
|
||||
import Annex.Common
|
||||
import qualified Annex.Branch
|
||||
import Logs.TimeStamp
|
||||
import Logs.Line
|
||||
import Annex.VectorClock
|
||||
|
||||
|
@ -28,21 +27,21 @@ class SingleValueSerializable v where
|
|||
data LogEntry v = LogEntry
|
||||
{ changed :: VectorClock
|
||||
, value :: v
|
||||
} deriving (Eq, Show, Ord)
|
||||
} deriving (Eq, Ord)
|
||||
|
||||
type Log v = S.Set (LogEntry v)
|
||||
|
||||
showLog :: (SingleValueSerializable v) => Log v -> String
|
||||
showLog = unlines . map showline . S.toList
|
||||
where
|
||||
showline (LogEntry t v) = unwords [show t, serialize v]
|
||||
showline (LogEntry c v) = unwords [formatVectorClock c, serialize v]
|
||||
|
||||
parseLog :: (Ord v, SingleValueSerializable v) => String -> Log v
|
||||
parseLog = S.fromList . mapMaybe parse . splitLines
|
||||
where
|
||||
parse line = do
|
||||
let (ts, s) = splitword line
|
||||
c <- VectorClock <$> parsePOSIXTime ts
|
||||
let (sc, s) = splitword line
|
||||
c <- parseVectorClock sc
|
||||
v <- deserialize s
|
||||
Just (LogEntry c v)
|
||||
splitword = separate (== ' ')
|
||||
|
|
|
@ -16,7 +16,6 @@ module Logs.Transitions where
|
|||
|
||||
import Annex.Common
|
||||
import Annex.VectorClock
|
||||
import Logs.TimeStamp
|
||||
import Logs.Line
|
||||
|
||||
import qualified Data.Set as S
|
||||
|
@ -32,7 +31,7 @@ data Transition
|
|||
data TransitionLine = TransitionLine
|
||||
{ transitionStarted :: VectorClock
|
||||
, transition :: Transition
|
||||
} deriving (Show, Ord, Eq)
|
||||
} deriving (Ord, Eq)
|
||||
|
||||
type Transitions = S.Set TransitionLine
|
||||
|
||||
|
@ -63,16 +62,16 @@ parseTransitionsStrictly source = fromMaybe badsource . parseTransitions
|
|||
badsource = giveup $ "unknown transitions listed in " ++ source ++ "; upgrade git-annex!"
|
||||
|
||||
showTransitionLine :: TransitionLine -> String
|
||||
showTransitionLine (TransitionLine ts t) = unwords [show t, show ts]
|
||||
showTransitionLine (TransitionLine c t) = unwords [show t, formatVectorClock c]
|
||||
|
||||
parseTransitionLine :: String -> Maybe TransitionLine
|
||||
parseTransitionLine s = TransitionLine
|
||||
<$> (VectorClock <$> parsePOSIXTime ds)
|
||||
<$> parseVectorClock cs
|
||||
<*> readish ts
|
||||
where
|
||||
ws = words s
|
||||
ts = Prelude.head ws
|
||||
ds = unwords $ Prelude.tail ws
|
||||
cs = unwords $ Prelude.tail ws
|
||||
|
||||
combineTransitions :: [Transitions] -> Transitions
|
||||
combineTransitions = S.unions
|
||||
|
|
|
@ -35,7 +35,6 @@ import Common
|
|||
import Types.UUID
|
||||
import Annex.VectorClock
|
||||
import Logs.MapLog
|
||||
import Logs.TimeStamp
|
||||
import Logs.Line
|
||||
|
||||
type Log v = MapLog UUID v
|
||||
|
@ -68,15 +67,12 @@ parseLogWithUUID parser = M.fromListWith best . mapMaybe parse . splitLines
|
|||
u = toUUID $ Prelude.head ws
|
||||
t = Prelude.last ws
|
||||
ts
|
||||
| tskey `isPrefixOf` t =
|
||||
pdate $ drop 1 $ dropWhile (/= '=') t
|
||||
| tskey `isPrefixOf` t = fromMaybe Unknown $
|
||||
parseVectorClock $ drop 1 $ dropWhile (/= '=') t
|
||||
| otherwise = Unknown
|
||||
info
|
||||
| ts == Unknown = drop 1 ws
|
||||
| otherwise = drop 1 $ beginning ws
|
||||
pdate s = case parsePOSIXTime s of
|
||||
Nothing -> Unknown
|
||||
Just d -> VectorClock d
|
||||
|
||||
showLogNew :: (v -> String) -> Log v -> String
|
||||
showLogNew = showMapLog fromUUID
|
||||
|
|
Loading…
Reference in a new issue