Added metadata --batch option, which allows getting, setting, deleting, and modifying metadata for multiple files/keys.
This commit is contained in:
parent
e5225f08fc
commit
bf3327ff25
8 changed files with 126 additions and 38 deletions
|
@ -63,7 +63,7 @@ parseModMeta p = case lastMaybe f of
|
|||
Just '+' -> AddMeta <$> mkMetaField f' <*> v
|
||||
Just '-' -> DelMeta <$> mkMetaField f' <*> (Just <$> v)
|
||||
Just '?' -> MaybeSetMeta <$> mkMetaField f' <*> v
|
||||
_ -> SetMeta <$> mkMetaField f <*> v
|
||||
_ -> SetMeta <$> mkMetaField f <*> (S.singleton <$> v)
|
||||
where
|
||||
(f, sv) = separate (== '=') p
|
||||
f' = beginning f
|
||||
|
|
|
@ -5,6 +5,8 @@ git-annex (6.20160726) UNRELEASED; urgency=medium
|
|||
This should be easier to parse than the old format, which mixed up
|
||||
metadata fields with other keys in the json object.
|
||||
Any consumers of the old format will need to be updated.
|
||||
* Added metadata --batch option, which allows getting, setting, deleting,
|
||||
and modifying metadata for multiple files/keys.
|
||||
* Added --branch option to copy, drop, fsck, get, metadata, mirror, move,
|
||||
and whereis commands. This option makes git-annex operate on files that
|
||||
are included in a specified branch (or other treeish).
|
||||
|
|
|
@ -10,9 +10,12 @@ module Command.MetaData where
|
|||
import Command
|
||||
import Annex.MetaData
|
||||
import Logs.MetaData
|
||||
import Annex.WorkTree
|
||||
import Messages.JSON (JSONActionItem(..))
|
||||
import Types.Messages
|
||||
|
||||
import qualified Data.Set as S
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.ByteString.Lazy.UTF8 as BU
|
||||
import Data.Time.Clock.POSIX
|
||||
|
@ -28,6 +31,7 @@ data MetaDataOptions = MetaDataOptions
|
|||
{ forFiles :: CmdParams
|
||||
, getSet :: GetSet
|
||||
, keyOptions :: Maybe KeyOptions
|
||||
, batchOption :: BatchMode
|
||||
}
|
||||
|
||||
data GetSet = Get MetaField | GetAll | Set [ModMeta]
|
||||
|
@ -37,6 +41,7 @@ optParser desc = MetaDataOptions
|
|||
<$> cmdParams desc
|
||||
<*> ((Get <$> getopt) <|> (Set <$> some modopts) <|> pure GetAll)
|
||||
<*> optional (parseKeyOptions False)
|
||||
<*> parseBatchOption
|
||||
where
|
||||
getopt = option (eitherReader mkMetaField)
|
||||
( long "get" <> short 'g' <> metavar paramField
|
||||
|
@ -62,15 +67,21 @@ optParser desc = MetaDataOptions
|
|||
seek :: MetaDataOptions -> CommandSeek
|
||||
seek o = do
|
||||
now <- liftIO getPOSIXTime
|
||||
let seeker = case getSet o of
|
||||
Get _ -> withFilesInGit
|
||||
GetAll -> withFilesInGit
|
||||
Set _ -> withFilesInGitNonRecursive
|
||||
"Not recursively setting metadata. Use --force to do that."
|
||||
withKeyOptions (keyOptions o) False
|
||||
(startKeys now o)
|
||||
(seeker $ whenAnnexed $ start now o)
|
||||
(forFiles o)
|
||||
case batchOption o of
|
||||
NoBatch -> do
|
||||
let seeker = case getSet o of
|
||||
Get _ -> withFilesInGit
|
||||
GetAll -> withFilesInGit
|
||||
Set _ -> withFilesInGitNonRecursive
|
||||
"Not recursively setting metadata. Use --force to do that."
|
||||
withKeyOptions (keyOptions o) False
|
||||
(startKeys now o)
|
||||
(seeker $ whenAnnexed $ start now o)
|
||||
(forFiles o)
|
||||
Batch -> withOutputType $ \ot -> case ot of
|
||||
JSONOutput -> batchInput parseJSONInput $
|
||||
commandAction . startBatch now
|
||||
_ -> error "--batch is currently only supported in --json mode"
|
||||
|
||||
start :: POSIXTime -> MetaDataOptions -> FilePath -> Key -> CommandStart
|
||||
start now o file k = startKeys now o k (mkActionItem afile)
|
||||
|
@ -128,14 +139,37 @@ instance FromJSON MetaDataFields where
|
|||
fieldsField :: T.Text
|
||||
fieldsField = T.pack "fields"
|
||||
|
||||
parseJSONInput :: String -> Maybe (Either FilePath Key, MetaData)
|
||||
parseJSONInput :: String -> Either String (Either FilePath Key, MetaData)
|
||||
parseJSONInput i = do
|
||||
v <- decode (BU.fromString i)
|
||||
v <- eitherDecode (BU.fromString i)
|
||||
let m = case itemAdded v of
|
||||
Nothing -> emptyMetaData
|
||||
Just (MetaDataFields m') -> m'
|
||||
let keyfile = case (itemKey v, itemFile v) of
|
||||
(Just k, _) -> Right k
|
||||
(Nothing, Just f) -> Left f
|
||||
(Nothing, Nothing) -> error "JSON input is missing either file or key"
|
||||
return (keyfile, m)
|
||||
case (itemKey v, itemFile v) of
|
||||
(Just k, _) -> Right (Right k, m)
|
||||
(Nothing, Just f) -> Right (Left f, m)
|
||||
(Nothing, Nothing) -> Left "JSON input is missing either file or key"
|
||||
|
||||
startBatch :: POSIXTime -> (Either FilePath Key, MetaData) -> CommandStart
|
||||
startBatch now (i, (MetaData m)) = case i of
|
||||
Left f -> do
|
||||
mk <- lookupFile f
|
||||
case mk of
|
||||
Just k -> go k (mkActionItem (Just f))
|
||||
Nothing -> error $ "not an annexed file: " ++ f
|
||||
Right k -> go k (mkActionItem k)
|
||||
where
|
||||
go k ai = do
|
||||
showStart' "metadata" k ai
|
||||
let o = MetaDataOptions
|
||||
{ forFiles = []
|
||||
, getSet = if MetaData m == emptyMetaData
|
||||
then GetAll
|
||||
else Set $ map mkModMeta (M.toList m)
|
||||
, keyOptions = Nothing
|
||||
, batchOption = NoBatch
|
||||
}
|
||||
next $ perform now o k
|
||||
mkModMeta (f, s)
|
||||
| S.null s = DelMeta f Nothing
|
||||
| otherwise = SetMeta f s
|
||||
|
|
|
@ -42,6 +42,7 @@ module Messages (
|
|||
commandProgressDisabled,
|
||||
outputMessage,
|
||||
implicitMessage,
|
||||
withOutputType,
|
||||
) where
|
||||
|
||||
import System.Log.Logger
|
||||
|
|
|
@ -204,8 +204,11 @@ emptyMetaData = MetaData M.empty
|
|||
{- Can be used to set a value, or to unset it, depending on whether
|
||||
- the MetaValue has CurrentlySet or not. -}
|
||||
updateMetaData :: MetaField -> MetaValue -> MetaData -> MetaData
|
||||
updateMetaData f v (MetaData m) = MetaData $
|
||||
M.insertWith' S.union f (S.singleton v) m
|
||||
updateMetaData f v = updateMetaData' f (S.singleton v)
|
||||
|
||||
updateMetaData' :: MetaField -> S.Set MetaValue -> MetaData -> MetaData
|
||||
updateMetaData' f s (MetaData m) = MetaData $
|
||||
M.insertWith' S.union f s m
|
||||
|
||||
{- New metadata overrides old._-}
|
||||
unionMetaData :: MetaData -> MetaData -> MetaData
|
||||
|
@ -247,7 +250,7 @@ data ModMeta
|
|||
| DelMeta MetaField (Maybe MetaValue)
|
||||
-- ^ delete value of a field. With Just, only that specific value
|
||||
-- is deleted; with Nothing, all current values are deleted.
|
||||
| SetMeta MetaField MetaValue
|
||||
| SetMeta MetaField (S.Set MetaValue)
|
||||
-- ^ removes any existing values
|
||||
| MaybeSetMeta MetaField MetaValue
|
||||
-- ^ set when field has no existing value
|
||||
|
@ -262,7 +265,7 @@ modMeta _ (DelMeta f (Just oldv)) =
|
|||
updateMetaData f (unsetMetaValue oldv) emptyMetaData
|
||||
modMeta m (DelMeta f Nothing) = MetaData $ M.singleton f $
|
||||
S.fromList $ map unsetMetaValue $ S.toList $ currentMetaDataValues f m
|
||||
modMeta m (SetMeta f v) = updateMetaData f v $
|
||||
modMeta m (SetMeta f s) = updateMetaData' f s $
|
||||
foldr (updateMetaData f) emptyMetaData $
|
||||
map unsetMetaValue $ S.toList $ currentMetaDataValues f m
|
||||
modMeta m (MaybeSetMeta f v)
|
||||
|
|
|
@ -17,6 +17,11 @@ metadata.
|
|||
|
||||
When run without any -s or -t parameters, displays the current metadata.
|
||||
|
||||
Each metadata field has its own "field-lastchanged" metadata, which
|
||||
contains the date the field was last changed. Unlike other metadata,
|
||||
this cannot be directly modified by this command. It is updated
|
||||
automatically.
|
||||
|
||||
# OPTIONS
|
||||
|
||||
* `-g field` / `--get field`
|
||||
|
@ -66,21 +71,6 @@ When run without any -s or -t parameters, displays the current metadata.
|
|||
The [[git-annex-matching-options]](1)
|
||||
can be used to specify files to act on.
|
||||
|
||||
* `--json`
|
||||
|
||||
Enable JSON output. This is intended to be parsed by programs that use
|
||||
git-annex. Each line of output is a JSON object.
|
||||
|
||||
The format of the JSON objects changed in git-annex version 6.20160726.
|
||||
|
||||
Example of the new format:
|
||||
|
||||
{"command":"metadata","file":"foo","key":"...","fields":{"author":["bar"],...},"note":"...","success":true}
|
||||
|
||||
Example of the old format, which lacks the inner fields object:
|
||||
|
||||
{"command":"metadata","file":"foo","key":"...","author":["bar"],...,"note":"...","success":true}
|
||||
|
||||
* `--all`
|
||||
|
||||
Specify instead of a file to get/set metadata on all known keys.
|
||||
|
@ -99,6 +89,55 @@ When run without any -s or -t parameters, displays the current metadata.
|
|||
|
||||
Specify instead of a file to get/set metadata of the specified key.
|
||||
|
||||
* `--json`
|
||||
|
||||
Enable JSON output (and input). Each line is a JSON object.
|
||||
|
||||
The format of the JSON objects changed in git-annex version 6.20160726.
|
||||
|
||||
Example of the new format:
|
||||
|
||||
{"command":"metadata","file":"foo","key":"...","fields":{"author":["bar"],...},"note":"...","success":true}
|
||||
|
||||
Example of the old format, which lacks the inner fields object:
|
||||
|
||||
{"command":"metadata","file":"foo","key":"...","author":["bar"],...,"note":"...","success":true}
|
||||
|
||||
* `--batch`
|
||||
|
||||
Enables batch mode, which can be used to both get, store, and unset
|
||||
metadata for multiple files or keys.
|
||||
|
||||
Batch currently only supports JSON input. So, you must
|
||||
enable `--json` along with `--batch`.
|
||||
|
||||
In batch mode, git-annex reads lines from stdin, which contain
|
||||
JSON objects. It replies to each input with an output JSON object.
|
||||
|
||||
The format of the JSON sent to git-annex can be the same as the JSON that
|
||||
it outputs. Or, a simplified version. Only the "file" (or "key") field
|
||||
is actually necessary.
|
||||
|
||||
For example, to get the current metadata of file foo:
|
||||
|
||||
{"file":"foo"}
|
||||
|
||||
To get the current metadata of the key k:
|
||||
|
||||
{"key":"k"}
|
||||
|
||||
Any metadata fields included in the JSON object will be stored,
|
||||
replacing whatever values the fields had before.
|
||||
To unset a field, include it with an empty list of values.
|
||||
|
||||
To change the author of file foo to bar:
|
||||
|
||||
{"file":"foo","fields":{"author":["bar"]}}
|
||||
|
||||
To remove the author of file foo:
|
||||
|
||||
{"file":"foo","fields":{"author":[]}}
|
||||
|
||||
# EXAMPLES
|
||||
|
||||
To set some tags on a file and also its author:
|
||||
|
|
|
@ -1,6 +1,13 @@
|
|||
I can export metadata to JSON format, which is nice as this can now be read into any other tool and manipulated. But I cannot find a way to set the metadata from JSON and so I am left to figure out what changes need to be made via the g-a interface to get to the desired state, and that is hard to get right.
|
||||
I can export metadata to JSON format, which is nice as this can now be read
|
||||
into any other tool and manipulated. But I cannot find a way to set the
|
||||
metadata from JSON and so I am left to figure out what changes need to be
|
||||
made via the g-a interface to get to the desired state, and that is hard to
|
||||
get right.
|
||||
|
||||
Maybe g-a metadata could grow an import-json function which would set (overwrite) the metadata for the given file(s) from JSON input.
|
||||
Maybe g-a metadata could grow an import-json function which would set
|
||||
(overwrite) the metadata for the given file(s) from JSON input.
|
||||
|
||||
Thanks,
|
||||
-m
|
||||
|
||||
> [[done]] via `git annex metadata --batch --json` --[[Joey]]
|
||||
|
|
|
@ -1 +1,3 @@
|
|||
[[!meta author=yoh]]
|
||||
|
||||
> [[done]] (using json input) --[[Joey]]
|
||||
|
|
Loading…
Reference in a new issue