summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Annex.hs5
-rw-r--r--Command/Find.hs23
-rw-r--r--GitAnnex.hs10
-rw-r--r--Options.hs2
-rw-r--r--Utility/Format.hs2
-rw-r--r--debian/changelog2
-rw-r--r--doc/git-annex.mdwn14
7 files changed, 47 insertions, 11 deletions
diff --git a/Annex.hs b/Annex.hs
index e5792fbcb..e82ffc5d1 100644
--- a/Annex.hs
+++ b/Annex.hs
@@ -37,6 +37,7 @@ import Types.BranchState
import Types.TrustLevel
import Types.UUID
import qualified Utility.Matcher
+import qualified Utility.Format
import qualified Data.Map as M
-- git-annex's monad
@@ -62,7 +63,7 @@ data AnnexState = AnnexState
, force :: Bool
, fast :: Bool
, auto :: Bool
- , print0 :: Bool
+ , format :: Maybe Utility.Format.Format
, branchstate :: BranchState
, catfilehandle :: Maybe CatFileHandle
, forcebackend :: Maybe String
@@ -85,7 +86,7 @@ newState gitrepo = AnnexState
, force = False
, fast = False
, auto = False
- , print0 = False
+ , format = Nothing
, branchstate = startBranchState
, catfilehandle = Nothing
, forcebackend = Nothing
diff --git a/Command/Find.hs b/Command/Find.hs
index 47058fa25..6050ff7bb 100644
--- a/Command/Find.hs
+++ b/Command/Find.hs
@@ -7,11 +7,16 @@
module Command.Find where
+import qualified Data.Map as M
+
import Common.Annex
import Command
import Annex.Content
import Limit
import qualified Annex
+import qualified Utility.Format
+import Utility.DataUnits
+import Types.Key
def :: [Command]
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
-- others via a limit
whenM (liftM2 (||) (inAnnex key) limited) $ do
- print0 <- Annex.getState Annex.print0
- if print0
- then liftIO $ putStr (file ++ "\0")
- else liftIO $ putStrLn file
+ f <- Annex.getState Annex.format
+ case f of
+ Nothing -> liftIO $ putStrLn file
+ Just formatter -> liftIO $ putStr $
+ Utility.Format.format formatter vars
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
diff --git a/GitAnnex.hs b/GitAnnex.hs
index 40ebed0d6..7243d69cb 100644
--- a/GitAnnex.hs
+++ b/GitAnnex.hs
@@ -18,6 +18,7 @@ import Types.TrustLevel
import qualified Annex
import qualified Remote
import qualified Limit
+import qualified Utility.Format
import qualified Command.Add
import qualified Command.Unannex
@@ -108,8 +109,10 @@ options = commonOptions ++
"override trust setting to untrusted"
, Option ['c'] ["config"] (ReqArg setgitconfig "NAME=VALUE")
"override git configuration setting"
- , Option [] ["print0"] (NoArg (setprint0 True))
- "terminate filename with null"
+ , Option [] ["print0"] (NoArg setprint0)
+ "terminate output with null"
+ , Option [] ["format"] (ReqArg setformat paramFormat)
+ "control format of output"
, Option ['x'] ["exclude"] (ReqArg Limit.addExclude paramGlob)
"skip files matching the glob pattern"
, Option ['I'] ["include"] (ReqArg Limit.addInclude paramGlob)
@@ -125,7 +128,8 @@ options = commonOptions ++
setto v = Annex.changeState $ \s -> s { Annex.toremote = Just v }
setfrom v = Annex.changeState $ \s -> s { Annex.fromremote = Just 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 v = do
newg <- inRepo $ Git.Config.store v
diff --git a/Options.hs b/Options.hs
index a8c165a81..cce750316 100644
--- a/Options.hs
+++ b/Options.hs
@@ -82,6 +82,8 @@ paramUUID :: String
paramUUID = "UUID"
paramType :: String
paramType = "TYPE"
+paramFormat :: String
+paramFormat = "FORMAT"
paramKeyValue :: String
paramKeyValue = "K=V"
paramNothing :: String
diff --git a/Utility/Format.hs b/Utility/Format.hs
index a49d95ff8..cde63f57c 100644
--- a/Utility/Format.hs
+++ b/Utility/Format.hs
@@ -5,7 +5,7 @@
- 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 Data.String.Utils (replace)
diff --git a/debian/changelog b/debian/changelog
index 6c5b6effb..a27611f55 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -10,6 +10,8 @@ git-annex (3.20111212) UNRELEASED; urgency=low
* Add --include, which is the same as --not --exclude.
* Can now be built with older git versions (before 1.7.7); the resulting
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
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index f4eef5c4c..70e54a91f 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -250,7 +250,11 @@ subdirectories).
annexed files whose content is not present, specify --not --in "."
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 ...]
@@ -428,6 +432,14 @@ subdirectories).
are in the annex, their backend is known and this option is not
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
Used to override git configuration settings. May be specified multiple times.