Format strings can be specified using the new --find option, to control what is output by git annex find.

This commit is contained in:
Joey Hess 2011-12-22 18:31:44 -04:00
parent cf496f09ab
commit 06bafae9e0
7 changed files with 47 additions and 11 deletions

View file

@ -37,6 +37,7 @@ import Types.BranchState
import Types.TrustLevel import Types.TrustLevel
import Types.UUID import Types.UUID
import qualified Utility.Matcher import qualified Utility.Matcher
import qualified Utility.Format
import qualified Data.Map as M import qualified Data.Map as M
-- git-annex's monad -- git-annex's monad
@ -62,7 +63,7 @@ data AnnexState = AnnexState
, force :: Bool , force :: Bool
, fast :: Bool , fast :: Bool
, auto :: Bool , auto :: Bool
, print0 :: Bool , format :: Maybe Utility.Format.Format
, branchstate :: BranchState , branchstate :: BranchState
, catfilehandle :: Maybe CatFileHandle , catfilehandle :: Maybe CatFileHandle
, forcebackend :: Maybe String , forcebackend :: Maybe String
@ -85,7 +86,7 @@ newState gitrepo = AnnexState
, force = False , force = False
, fast = False , fast = False
, auto = False , auto = False
, print0 = False , format = Nothing
, branchstate = startBranchState , branchstate = startBranchState
, catfilehandle = Nothing , catfilehandle = Nothing
, forcebackend = Nothing , forcebackend = Nothing

View file

@ -7,11 +7,16 @@
module Command.Find where module Command.Find where
import qualified Data.Map as M
import Common.Annex import Common.Annex
import Command import Command
import Annex.Content import Annex.Content
import Limit import Limit
import qualified Annex import qualified Annex
import qualified Utility.Format
import Utility.DataUnits
import Types.Key
def :: [Command] def :: [Command]
def = [command "find" paramPaths seek "lists available files"] def = [command "find" paramPaths seek "lists available files"]
@ -24,8 +29,18 @@ start file (key, _) = do
-- only files inAnnex are shown, unless the user has requested -- only files inAnnex are shown, unless the user has requested
-- others via a limit -- others via a limit
whenM (liftM2 (||) (inAnnex key) limited) $ do whenM (liftM2 (||) (inAnnex key) limited) $ do
print0 <- Annex.getState Annex.print0 f <- Annex.getState Annex.format
if print0 case f of
then liftIO $ putStr (file ++ "\0") Nothing -> liftIO $ putStrLn file
else liftIO $ putStrLn file Just formatter -> liftIO $ putStr $
Utility.Format.format formatter vars
stop stop
where
vars = M.fromList
[ ("file", file)
, ("key", show key)
, ("backend", keyBackendName key)
, ("bytesize", size show)
, ("humansize", size $ roughSize storageUnits True)
]
size c = maybe "unknown" c $ keySize key

View file

@ -18,6 +18,7 @@ import Types.TrustLevel
import qualified Annex import qualified Annex
import qualified Remote import qualified Remote
import qualified Limit import qualified Limit
import qualified Utility.Format
import qualified Command.Add import qualified Command.Add
import qualified Command.Unannex import qualified Command.Unannex
@ -108,8 +109,10 @@ options = commonOptions ++
"override trust setting to untrusted" "override trust setting to untrusted"
, Option ['c'] ["config"] (ReqArg setgitconfig "NAME=VALUE") , Option ['c'] ["config"] (ReqArg setgitconfig "NAME=VALUE")
"override git configuration setting" "override git configuration setting"
, Option [] ["print0"] (NoArg (setprint0 True)) , Option [] ["print0"] (NoArg setprint0)
"terminate filename with null" "terminate output with null"
, Option [] ["format"] (ReqArg setformat paramFormat)
"control format of output"
, Option ['x'] ["exclude"] (ReqArg Limit.addExclude paramGlob) , Option ['x'] ["exclude"] (ReqArg Limit.addExclude paramGlob)
"skip files matching the glob pattern" "skip files matching the glob pattern"
, Option ['I'] ["include"] (ReqArg Limit.addInclude paramGlob) , Option ['I'] ["include"] (ReqArg Limit.addInclude paramGlob)
@ -125,7 +128,8 @@ options = commonOptions ++
setto v = Annex.changeState $ \s -> s { Annex.toremote = Just v } setto v = Annex.changeState $ \s -> s { Annex.toremote = Just v }
setfrom v = Annex.changeState $ \s -> s { Annex.fromremote = Just v } setfrom v = Annex.changeState $ \s -> s { Annex.fromremote = Just v }
setnumcopies v = Annex.changeState $ \s -> s {Annex.forcenumcopies = readMaybe v } setnumcopies v = Annex.changeState $ \s -> s {Annex.forcenumcopies = readMaybe v }
setprint0 v = Annex.changeState $ \s -> s { Annex.print0 = v } setformat v = Annex.changeState $ \s -> s { Annex.format = Just $ Utility.Format.gen v }
setprint0 = setformat "${file}\0"
setgitconfig :: String -> Annex () setgitconfig :: String -> Annex ()
setgitconfig v = do setgitconfig v = do
newg <- inRepo $ Git.Config.store v newg <- inRepo $ Git.Config.store v

View file

@ -82,6 +82,8 @@ paramUUID :: String
paramUUID = "UUID" paramUUID = "UUID"
paramType :: String paramType :: String
paramType = "TYPE" paramType = "TYPE"
paramFormat :: String
paramFormat = "FORMAT"
paramKeyValue :: String paramKeyValue :: String
paramKeyValue = "K=V" paramKeyValue = "K=V"
paramNothing :: String paramNothing :: String

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
module Utility.Format (gen, format) where module Utility.Format (Format, gen, format) where
import Text.Printf (printf) import Text.Printf (printf)
import Data.String.Utils (replace) import Data.String.Utils (replace)

2
debian/changelog vendored
View file

@ -10,6 +10,8 @@ git-annex (3.20111212) UNRELEASED; urgency=low
* Add --include, which is the same as --not --exclude. * Add --include, which is the same as --not --exclude.
* Can now be built with older git versions (before 1.7.7); the resulting * Can now be built with older git versions (before 1.7.7); the resulting
binary should only be used with old git. binary should only be used with old git.
* Format strings can be specified using the new --find option, to control
what is output by git annex find.
-- Joey Hess <joeyh@debian.org> Mon, 12 Dec 2011 01:57:49 -0400 -- Joey Hess <joeyh@debian.org> Mon, 12 Dec 2011 01:57:49 -0400

View file

@ -250,7 +250,11 @@ subdirectories).
annexed files whose content is not present, specify --not --in "." annexed files whose content is not present, specify --not --in "."
To output filenames terminated with nulls, for use with xargs -0, To output filenames terminated with nulls, for use with xargs -0,
specify --print0. specify --print0. Or, a custom output formatting can be specified using
--format. The default output format is the same as --format='${file}\n'
These variables are available for use in formats: file, key, backend,
bytesize, humansize
* whereis [path ...] * whereis [path ...]
@ -428,6 +432,14 @@ subdirectories).
are in the annex, their backend is known and this option is not are in the annex, their backend is known and this option is not
necessary. necessary.
* --format=value
Specifies a custom output format. The value is a format string,
in which '${var}' is expanded to the value of a variable. To right-align
a variable with whitespace, use '${var;width}' ; to left-align
a variable, use '${var;-width}'. Also, '\n' is a newline, '\0' is a NULL,
etc.
* -c name=value * -c name=value
Used to override git configuration settings. May be specified multiple times. Used to override git configuration settings. May be specified multiple times.