quickcheck property for parsing of content identifier logs
This commit is contained in:
parent
7c25cc7715
commit
936aee6a60
7 changed files with 40 additions and 16 deletions
|
@ -6,6 +6,7 @@
|
|||
-}
|
||||
|
||||
module Logs.ContentIdentifier (
|
||||
module X,
|
||||
recordContentIdentifier,
|
||||
getContentIdentifiers,
|
||||
) where
|
||||
|
@ -15,7 +16,7 @@ import Logs
|
|||
import Logs.MapLog
|
||||
import Types.Remote (ContentIdentifier)
|
||||
import qualified Annex.Branch
|
||||
import Logs.ContentIdentifier.Pure
|
||||
import Logs.ContentIdentifier.Pure as X
|
||||
import qualified Annex
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -7,11 +7,7 @@
|
|||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Logs.ContentIdentifier.Pure
|
||||
( ContentIdentifierLog
|
||||
, parseLog
|
||||
, buildLog
|
||||
) where
|
||||
module Logs.ContentIdentifier.Pure where
|
||||
|
||||
import Annex.Common
|
||||
import Logs.MapLog
|
||||
|
@ -28,11 +24,14 @@ import Data.ByteString.Builder
|
|||
type ContentIdentifierLog = MapLog UUID [ContentIdentifier]
|
||||
|
||||
buildLog :: ContentIdentifierLog -> Builder
|
||||
buildLog = buildMapLog buildUUID valuebuilder
|
||||
buildLog = buildMapLog buildUUID buildContentIdentifierList
|
||||
|
||||
buildContentIdentifierList :: [ContentIdentifier] -> Builder
|
||||
buildContentIdentifierList l = case l of
|
||||
[] -> mempty
|
||||
[c] -> buildcid c
|
||||
(c:cs) -> buildcid c <> charUtf8 ' ' <> buildContentIdentifierList cs
|
||||
where
|
||||
valuebuilder [] = mempty
|
||||
valuebuilder [c] = buildcid c
|
||||
valuebuilder (c:cs) = buildcid c <> charUtf8 ' ' <> valuebuilder cs
|
||||
buildcid (ContentIdentifier c)
|
||||
| S8.any (`elem` [' ', '\r', '\n']) c || "!" `S8.isPrefixOf` c =
|
||||
charUtf8 '!' <> byteString (toB64' c)
|
||||
|
@ -41,7 +40,10 @@ buildLog = buildMapLog buildUUID valuebuilder
|
|||
parseLog :: L.ByteString -> ContentIdentifierLog
|
||||
parseLog = parseMapLog
|
||||
(toUUID <$> A.takeByteString)
|
||||
(reverse . catMaybes <$> valueparser [])
|
||||
parseContentIdentifierList
|
||||
|
||||
parseContentIdentifierList :: A.Parser [ContentIdentifier]
|
||||
parseContentIdentifierList = reverse . catMaybes <$> valueparser []
|
||||
where
|
||||
valueparser l = do
|
||||
b <- A8.takeWhile1 (/= ' ')
|
||||
|
@ -54,3 +56,7 @@ parseLog = parseMapLog
|
|||
_ <- A8.char ' '
|
||||
valueparser (cid:l)
|
||||
)
|
||||
|
||||
prop_parse_build_contentidentifier_log :: ContentIdentifierLog -> Bool
|
||||
prop_parse_build_contentidentifier_log l =
|
||||
parseLog (toLazyByteString (buildLog l)) == l
|
||||
|
|
|
@ -20,6 +20,7 @@ module Logs.MapLog (
|
|||
import Common
|
||||
import Annex.VectorClock
|
||||
import Logs.Line
|
||||
import Utility.QuickCheck
|
||||
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.Map.Strict as M
|
||||
|
@ -32,6 +33,9 @@ data LogEntry v = LogEntry
|
|||
, value :: v
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance Arbitrary v => Arbitrary (LogEntry v) where
|
||||
arbitrary = LogEntry <$> arbitrary <*> arbitrary
|
||||
|
||||
type MapLog f v = M.Map f (LogEntry v)
|
||||
|
||||
buildMapLog :: (f -> Builder) -> (v -> Builder) -> MapLog f v -> Builder
|
||||
|
|
|
@ -122,6 +122,5 @@ instance Arbitrary LogLine where
|
|||
arbinfo = (encodeBS <$> arbitrary) `suchThat`
|
||||
(\b -> C8.notElem '\n' b && C8.notElem '\r' b)
|
||||
|
||||
prop_parse_build_log :: [LogLine] -> Bool
|
||||
prop_parse_build_log l = parseLog (toLazyByteString (buildLog l)) == l
|
||||
|
||||
prop_parse_build_presence_log :: [LogLine] -> Bool
|
||||
prop_parse_build_presence_log l = parseLog (toLazyByteString (buildLog l)) == l
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue