aboutsummaryrefslogtreecommitdiff
path: root/Command/MetaData.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-02-13 01:49:38 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-02-13 01:49:38 -0400
commit55de2b85f4e646e361d71e58f36d65b617c625e0 (patch)
tree1838bc5713db0951297d4bd76ef2d3fbdeb361a1 /Command/MetaData.hs
parent09edd77928dd55f36292c0e299e6ace70da84578 (diff)
metacata command can now operate on many files at once
Diffstat (limited to 'Command/MetaData.hs')
-rw-r--r--Command/MetaData.hs58
1 files changed, 20 insertions, 38 deletions
diff --git a/Command/MetaData.hs b/Command/MetaData.hs
index d4d3f880c..a645b274a 100644
--- a/Command/MetaData.hs
+++ b/Command/MetaData.hs
@@ -8,6 +8,7 @@
module Command.MetaData where
import Common.Annex
+import qualified Annex
import Command
import Logs.MetaData
import Types.MetaData
@@ -15,27 +16,32 @@ import Types.MetaData
import qualified Data.Set as S
def :: [Command]
-def = [command "metadata" (paramPair paramFile (paramRepeating "FIELD[+-]=VALUE")) seek
+def = [withOptions [setOption] $ command "metadata" paramPaths seek
SectionUtility "sets metadata of a file"]
+setOption :: Option
+setOption = Option ['s'] ["set"] (ReqArg mkmod "field[+-]=value") "set metadata"
+ where
+ mkmod p = case parseModMeta p of
+ Left e -> error e
+ Right modmeta -> Annex.changeState $
+ \s -> s { Annex.modmeta = modmeta:Annex.modmeta s }
+
seek :: CommandSeek
-seek = withWords start
+seek ps = do
+ modmeta <- Annex.getState Annex.modmeta
+ withFilesInGit (whenAnnexed $ start modmeta) ps
-start :: [String] -> CommandStart
-start (file:settings) = ifAnnexed file
- go
- (error $ "not an annexed file, so cannot add metadata: " ++ file)
- where
- go (k, _b) = do
- showStart "metadata" file
- next $ perform k (map parse settings)
-start _ = error "specify a file and the metadata to set"
+start :: [ModMeta] -> FilePath -> (Key, Backend) -> CommandStart
+start ms file (k, _) = do
+ showStart "metadata" file
+ next $ perform k ms
-perform :: Key -> [Action] -> CommandPerform
+perform :: Key -> [ModMeta] -> CommandPerform
perform k [] = next $ cleanup k
-perform k as = do
+perform k ms = do
oldm <- getCurrentMetaData k
- let m = foldr (apply oldm) newMetaData as
+ let m = foldl' unionMetaData newMetaData $ map (modMeta oldm) ms
addMetaData k m
next $ cleanup k
@@ -46,27 +52,3 @@ cleanup k = do
return True
where
showmeta (f, vs) = map (\v -> fromMetaField f ++ "=" ++ fromMetaValue v) $ S.toList vs
-
-data Action
- = AddMeta MetaField MetaValue
- | DelMeta MetaField MetaValue
- | SetMeta MetaField MetaValue
-
-parse :: String -> Action
-parse p = case lastMaybe f of
- Just '+' -> AddMeta (mkf f') v
- Just '-' -> DelMeta (mkf f') v
- _ -> SetMeta (mkf f) v
- where
- (f, sv) = separate (== '=') p
- f' = beginning f
- v = toMetaValue sv
- mkf fld = fromMaybe (badfield fld) (toMetaField fld)
- badfield fld = error $ "Illegal metadata field name, \"" ++ fld ++ "\""
-
-apply :: MetaData -> Action -> MetaData -> MetaData
-apply _ (AddMeta f v) m = updateMetaData f v m
-apply _ (DelMeta f oldv) m = updateMetaData f (unsetMetaValue oldv) m
-apply oldm (SetMeta f v) m = updateMetaData f v $
- foldr (updateMetaData f) m $
- map unsetMetaValue $ S.toList $ currentMetaDataValues f oldm