follow-on changes from MetaData type changes
Including writing and parsing the metadata log files with bytestring-builder and attoparsec.
This commit is contained in:
parent
16c798b5ef
commit
cb375977a6
14 changed files with 102 additions and 81 deletions
|
@ -6,6 +6,7 @@
|
|||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Command.ImportFeed where
|
||||
|
||||
|
@ -124,7 +125,8 @@ getCache opttemplate = ifM (Annex.getState Annex.force)
|
|||
|
||||
knownItems :: (Key, URLString) -> Annex ([ItemId], URLString)
|
||||
knownItems (k, u) = do
|
||||
itemids <- S.toList . S.filter (/= noneValue) . S.map fromMetaValue
|
||||
itemids <- S.toList . S.filter (/= noneValue)
|
||||
. S.map (decodeBS . fromMetaValue)
|
||||
. currentMetaDataValues itemIdField
|
||||
<$> getCurrentMetaData k
|
||||
return (itemids, u)
|
||||
|
@ -322,14 +324,14 @@ extractMetaData i = case getItemPublishDate (item i) :: Maybe (Maybe UTCTime) of
|
|||
Just (Just d) -> unionMetaData meta (dateMetaData d meta)
|
||||
_ -> meta
|
||||
where
|
||||
tometa (k, v) = (mkMetaFieldUnchecked k, S.singleton (toMetaValue v))
|
||||
tometa (k, v) = (mkMetaFieldUnchecked (T.pack k), S.singleton (toMetaValue (encodeBS v)))
|
||||
meta = MetaData $ M.fromList $ map tometa $ extractFields i
|
||||
|
||||
minimalMetaData :: ToDownload -> MetaData
|
||||
minimalMetaData i = case getItemId (item i) of
|
||||
(Nothing) -> emptyMetaData
|
||||
(Just (_, itemid)) -> MetaData $ M.singleton itemIdField
|
||||
(S.singleton $ toMetaValue $ fromFeed itemid)
|
||||
(S.singleton $ toMetaValue $ encodeBS $ fromFeed itemid)
|
||||
|
||||
{- Extract fields from the feed and item, that are both used as metadata,
|
||||
- and to generate the filename. -}
|
||||
|
|
|
@ -20,6 +20,7 @@ import Limit
|
|||
import qualified Data.Set as S
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.ByteString.Char8 as B8
|
||||
import qualified Data.ByteString.Lazy.UTF8 as BU
|
||||
import Control.Concurrent
|
||||
|
||||
|
@ -45,7 +46,7 @@ optParser desc = MetaDataOptions
|
|||
<*> optional parseKeyOptions
|
||||
<*> parseBatchOption
|
||||
where
|
||||
getopt = option (eitherReader mkMetaField)
|
||||
getopt = option (eitherReader (mkMetaField . T.pack))
|
||||
( long "get" <> short 'g' <> metavar paramField
|
||||
<> help "get single metadata field"
|
||||
)
|
||||
|
@ -61,7 +62,7 @@ optParser desc = MetaDataOptions
|
|||
( long "untag" <> short 'u' <> metavar "TAG"
|
||||
<> help "remove a tag"
|
||||
))
|
||||
<|> option (eitherReader (\f -> DelMeta <$> mkMetaField f <*> pure Nothing))
|
||||
<|> option (eitherReader (\f -> DelMeta <$> mkMetaField (T.pack f) <*> pure Nothing))
|
||||
( long "remove" <> short 'r' <> metavar "FIELD"
|
||||
<> help "remove all values of a field"
|
||||
)
|
||||
|
@ -101,7 +102,7 @@ startKeys c o (k, ai) = case getSet o of
|
|||
Get f -> do
|
||||
l <- S.toList . currentMetaDataValues f <$> getCurrentMetaData k
|
||||
liftIO $ forM_ l $
|
||||
putStrLn . fromMetaValue
|
||||
B8.putStrLn . fromMetaValue
|
||||
stop
|
||||
_ -> do
|
||||
showStartKey "metadata" k ai
|
||||
|
@ -126,7 +127,7 @@ cleanup k = do
|
|||
return True
|
||||
where
|
||||
unwrapmeta (f, v) = (fromMetaField f, map fromMetaValue (S.toList v))
|
||||
showmeta (f, vs) = map ((f ++ "=") ++) vs
|
||||
showmeta (f, vs) = map ((T.unpack f ++ "=") ++) (map decodeBS vs)
|
||||
|
||||
-- Metadata serialized to JSON in the field named "fields" of
|
||||
-- a larger object.
|
||||
|
|
|
@ -29,6 +29,7 @@ import qualified Git.Index as Git
|
|||
import qualified Git.LsFiles as Git
|
||||
|
||||
import qualified Data.Set as S
|
||||
import qualified Data.Text as T
|
||||
|
||||
cmd :: Command
|
||||
cmd = command "pre-commit" SectionPlumbing
|
||||
|
@ -111,7 +112,7 @@ showMetaDataChange :: MetaData -> Annex ()
|
|||
showMetaDataChange = showLongNote . unlines . concatMap showmeta . fromMetaData
|
||||
where
|
||||
showmeta (f, vs) = map (showmetavalue f) $ S.toList vs
|
||||
showmetavalue f v = fromMetaField f ++ showset v ++ "=" ++ fromMetaValue v
|
||||
showmetavalue f v = T.unpack (fromMetaField f) <> showset v <> "=" <> decodeBS (fromMetaValue v)
|
||||
showset v
|
||||
| isSet v = "+"
|
||||
| otherwise = "-"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue