avoid accidental Show of VectorClock

Removed its Show instance.
This commit is contained in:
Joey Hess 2017-08-14 14:43:56 -04:00
parent 2cecc8d2a3
commit 0b307f43e1
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
6 changed files with 29 additions and 27 deletions

View file

@ -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 (== ' ')