make find show files meeting limits, even when not present
find: Rather than only showing files whose contents are present, when used with --exclude --copies or --in, displays all files that match the specified conditions. Note that this is a behavior change for find --exclude! Old behavior can be gotten with find --in . --exclude=...
This commit is contained in:
parent
9da23dff78
commit
33cd1ffbfe
5 changed files with 29 additions and 5 deletions
|
@ -7,11 +7,12 @@
|
|||
|
||||
module Command.Find where
|
||||
|
||||
import Control.Monad.State (liftIO)
|
||||
import Control.Monad.State
|
||||
|
||||
import Command
|
||||
import Content
|
||||
import Utility.Conditional
|
||||
import Limit
|
||||
|
||||
command :: [Command]
|
||||
command = [repoCommand "find" paramPaths seek "lists available files"]
|
||||
|
@ -19,8 +20,10 @@ command = [repoCommand "find" paramPaths seek "lists available files"]
|
|||
seek :: [CommandSeek]
|
||||
seek = [withFilesInGit start]
|
||||
|
||||
{- Output a list of files. -}
|
||||
start :: FilePath -> CommandStart
|
||||
start file = isAnnexed file $ \(key, _) -> do
|
||||
whenM (inAnnex key) $ liftIO $ putStrLn file
|
||||
-- only files inAnnex are shown, unless the user has requested
|
||||
-- others via a limit
|
||||
whenM (liftM2 (||) (inAnnex key) limited) $
|
||||
liftIO $ putStrLn file
|
||||
stop
|
||||
|
|
5
Limit.hs
5
Limit.hs
|
@ -10,6 +10,7 @@ module Limit where
|
|||
import Text.Regex.PCRE.Light.Char8
|
||||
import System.Path.WildMatch
|
||||
import Control.Monad (filterM)
|
||||
import Control.Applicative
|
||||
import Data.Maybe
|
||||
|
||||
import Annex
|
||||
|
@ -27,6 +28,10 @@ filterFiles l = do
|
|||
matcher <- getMatcher
|
||||
filterM (Utility.Matcher.matchM matcher) l
|
||||
|
||||
{- Checks if there are user-specified limits. -}
|
||||
limited :: Annex Bool
|
||||
limited = (not . Utility.Matcher.matchesAny) <$> getMatcher
|
||||
|
||||
{- Gets a matcher for the user-specified limits. The matcher is cached for
|
||||
- speed; once it's obtained the user-specified limits can't change. -}
|
||||
getMatcher :: Annex (Utility.Matcher.Matcher (FilePath -> Annex Bool))
|
||||
|
|
|
@ -20,7 +20,8 @@ module Utility.Matcher (
|
|||
Matcher,
|
||||
generate,
|
||||
match,
|
||||
matchM
|
||||
matchM,
|
||||
matchesAny
|
||||
) where
|
||||
|
||||
import Control.Monad
|
||||
|
@ -81,3 +82,10 @@ matchM m v = go m
|
|||
go (Or m1 m2) = liftM2 (||) (go m1) (go m2)
|
||||
go (Not m1) = liftM not (go m1)
|
||||
go (Op o) = o v
|
||||
|
||||
{- Checks is a matcher contains no limits, and so (presumably) matches
|
||||
- anything. Note that this only checks the trivial case; it is possible
|
||||
- to construct matchers that match anything but are more complicated. -}
|
||||
matchesAny :: Matcher a -> Bool
|
||||
matchesAny Any = True
|
||||
matchesAny _ = False
|
||||
|
|
5
debian/changelog
vendored
5
debian/changelog
vendored
|
@ -7,6 +7,11 @@ git-annex (3.20110916) UNRELEASED; urgency=low
|
|||
Example: git annex get --exclude '*.mp3' --and --not -( --in usbdrive --or --in archive -)
|
||||
* --copies=N can be used to make git-annex only operate on files with
|
||||
the specified number of copies. (And --not --copies=N for the inverse.)
|
||||
* find: Rather than only showing files whose contents are present,
|
||||
when used with --exclude --copies or --in, displays all files that
|
||||
match the specified conditions.
|
||||
* Note that this is a behavior change for find --exclude! Old behavior
|
||||
can be gotten with: find --in . --exclude=...
|
||||
|
||||
-- Joey Hess <joeyh@debian.org> Sun, 18 Sep 2011 18:25:51 -0400
|
||||
|
||||
|
|
|
@ -222,6 +222,8 @@ subdirectories).
|
|||
* find [path ...]
|
||||
|
||||
Outputs a list of annexed files whose content is currently present.
|
||||
Or, if a file matching option is specified, outputs a list of all
|
||||
matching files, whether or not their content is currently present.
|
||||
|
||||
With no parameters, defaults to finding all files in the current directory
|
||||
and its subdirectories.
|
||||
|
@ -432,7 +434,8 @@ file contents are present at either of two repositories.
|
|||
in a repository.
|
||||
|
||||
The repository should be specified using the name of a configured remote,
|
||||
or the UUID or description of a repository.
|
||||
or the UUID or description of a repository. For the current repository,
|
||||
use "--in=."
|
||||
|
||||
* --copies=number
|
||||
|
||||
|
|
Loading…
Reference in a new issue