2019-02-20 19:36:09 +00:00
|
|
|
{- Remote content identifier logs, pure operations.
|
|
|
|
-
|
|
|
|
- Copyright 2019 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2019-02-21 16:22:50 +00:00
|
|
|
module Logs.ContentIdentifier.Pure where
|
2019-02-20 19:36:09 +00:00
|
|
|
|
|
|
|
import Annex.Common
|
|
|
|
import Logs.MapLog
|
|
|
|
import Types.Remote (ContentIdentifier(..))
|
|
|
|
import Utility.Base64
|
|
|
|
|
|
|
|
import qualified Data.ByteString as S
|
|
|
|
import qualified Data.ByteString.Char8 as S8
|
|
|
|
import qualified Data.ByteString.Lazy as L
|
|
|
|
import qualified Data.Attoparsec.ByteString.Lazy as A
|
|
|
|
import qualified Data.Attoparsec.ByteString.Char8 as A8
|
|
|
|
import Data.ByteString.Builder
|
|
|
|
|
|
|
|
type ContentIdentifierLog = MapLog UUID [ContentIdentifier]
|
|
|
|
|
|
|
|
buildLog :: ContentIdentifierLog -> Builder
|
2019-02-21 16:22:50 +00:00
|
|
|
buildLog = buildMapLog buildUUID buildContentIdentifierList
|
|
|
|
|
|
|
|
buildContentIdentifierList :: [ContentIdentifier] -> Builder
|
|
|
|
buildContentIdentifierList l = case l of
|
|
|
|
[] -> mempty
|
|
|
|
[c] -> buildcid c
|
|
|
|
(c:cs) -> buildcid c <> charUtf8 ' ' <> buildContentIdentifierList cs
|
2019-02-20 19:36:09 +00:00
|
|
|
where
|
|
|
|
buildcid (ContentIdentifier c)
|
|
|
|
| S8.any (`elem` [' ', '\r', '\n']) c || "!" `S8.isPrefixOf` c =
|
|
|
|
charUtf8 '!' <> byteString (toB64' c)
|
|
|
|
| otherwise = byteString c
|
|
|
|
|
|
|
|
parseLog :: L.ByteString -> ContentIdentifierLog
|
|
|
|
parseLog = parseMapLog
|
|
|
|
(toUUID <$> A.takeByteString)
|
2019-02-21 16:22:50 +00:00
|
|
|
parseContentIdentifierList
|
|
|
|
|
|
|
|
parseContentIdentifierList :: A.Parser [ContentIdentifier]
|
|
|
|
parseContentIdentifierList = reverse . catMaybes <$> valueparser []
|
2019-02-20 19:36:09 +00:00
|
|
|
where
|
|
|
|
valueparser l = do
|
|
|
|
b <- A8.takeWhile1 (/= ' ')
|
|
|
|
let cid = if "!" `S8.isPrefixOf` b
|
|
|
|
then ContentIdentifier <$> fromB64Maybe' (S.drop 1 b)
|
|
|
|
else Just $ ContentIdentifier b
|
|
|
|
ifM A8.atEnd
|
|
|
|
( return (cid:l)
|
|
|
|
, do
|
|
|
|
_ <- A8.char ' '
|
|
|
|
valueparser (cid:l)
|
|
|
|
)
|
2019-02-21 16:22:50 +00:00
|
|
|
|
|
|
|
prop_parse_build_contentidentifier_log :: ContentIdentifierLog -> Bool
|
|
|
|
prop_parse_build_contentidentifier_log l =
|
|
|
|
parseLog (toLazyByteString (buildLog l)) == l
|