--metadata field=value can now use globs to match, and matches case insensatively, the same as git annex view field=value does.
Also refactored glob code into its own module.
This commit is contained in:
parent
e834227202
commit
24f8136504
5 changed files with 82 additions and 69 deletions
|
@ -5,8 +5,6 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
|
||||||
|
|
||||||
module Annex.View where
|
module Annex.View where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
@ -28,22 +26,15 @@ import Annex.Link
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Logs.MetaData
|
import Logs.MetaData
|
||||||
import Logs.View
|
import Logs.View
|
||||||
|
import Utility.Glob
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
import Types.Command
|
import Types.Command
|
||||||
import Config
|
import Config
|
||||||
import CmdLine.Action
|
import CmdLine.Action
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import System.Path.WildMatch
|
|
||||||
import "mtl" Control.Monad.Writer
|
import "mtl" Control.Monad.Writer
|
||||||
|
|
||||||
#ifdef WITH_TDFA
|
|
||||||
import Text.Regex.TDFA
|
|
||||||
import Text.Regex.TDFA.String
|
|
||||||
#else
|
|
||||||
import Text.Regex
|
|
||||||
#endif
|
|
||||||
|
|
||||||
{- Each visible ViewFilter in a view results in another level of
|
{- Each visible ViewFilter in a view results in another level of
|
||||||
- subdirectory nesting. When a file matches multiple ways, it will appear
|
- subdirectory nesting. When a file matches multiple ways, it will appear
|
||||||
- in multiple subdirectories. This means there is a bit of an exponential
|
- in multiple subdirectories. This means there is a bit of an exponential
|
||||||
|
@ -127,11 +118,11 @@ combineViewFilter old@(FilterValues olds) (FilterValues news)
|
||||||
combineViewFilter (FilterValues _) newglob@(FilterGlob _) =
|
combineViewFilter (FilterValues _) newglob@(FilterGlob _) =
|
||||||
(newglob, Widening)
|
(newglob, Widening)
|
||||||
combineViewFilter (FilterGlob oldglob) new@(FilterValues s)
|
combineViewFilter (FilterGlob oldglob) new@(FilterValues s)
|
||||||
| all (matchGlob (compileGlob oldglob) . fromMetaValue) (S.toList s) = (new, Narrowing)
|
| all (matchGlob (compileGlob oldglob CaseInsensative) . fromMetaValue) (S.toList s) = (new, Narrowing)
|
||||||
| otherwise = (new, Widening)
|
| otherwise = (new, Widening)
|
||||||
combineViewFilter (FilterGlob old) newglob@(FilterGlob new)
|
combineViewFilter (FilterGlob old) newglob@(FilterGlob new)
|
||||||
| old == new = (newglob, Unchanged)
|
| old == new = (newglob, Unchanged)
|
||||||
| matchGlob (compileGlob old) new = (newglob, Narrowing)
|
| matchGlob (compileGlob old CaseInsensative) new = (newglob, Narrowing)
|
||||||
| otherwise = (newglob, Widening)
|
| otherwise = (newglob, Widening)
|
||||||
|
|
||||||
{- Converts a filepath used in a reference branch to the
|
{- Converts a filepath used in a reference branch to the
|
||||||
|
@ -205,31 +196,9 @@ viewComponentMatcher viewcomponent = \metadata ->
|
||||||
matcher = case viewFilter viewcomponent of
|
matcher = case viewFilter viewcomponent of
|
||||||
FilterValues s -> \values -> S.intersection s values
|
FilterValues s -> \values -> S.intersection s values
|
||||||
FilterGlob glob ->
|
FilterGlob glob ->
|
||||||
let regex = compileGlob glob
|
let cglob = compileGlob glob CaseInsensative
|
||||||
in \values ->
|
in \values ->
|
||||||
S.filter (matchGlob regex . fromMetaValue) values
|
S.filter (matchGlob cglob . fromMetaValue) values
|
||||||
|
|
||||||
compileGlob :: String -> Regex
|
|
||||||
compileGlob glob =
|
|
||||||
#ifdef WITH_TDFA
|
|
||||||
case compile (defaultCompOpt {caseSensitive = False}) defaultExecOpt regex of
|
|
||||||
Right r -> r
|
|
||||||
Left _ -> error $ "failed to compile regex: " ++ regex
|
|
||||||
#else
|
|
||||||
mkRegexWithOpts regex False True
|
|
||||||
#endif
|
|
||||||
where
|
|
||||||
regex = '^':wildToRegex glob
|
|
||||||
|
|
||||||
matchGlob :: Regex -> String -> Bool
|
|
||||||
matchGlob regex val =
|
|
||||||
#ifdef WITH_TDFA
|
|
||||||
case execute regex val of
|
|
||||||
Right (Just _) -> True
|
|
||||||
_ -> False
|
|
||||||
#else
|
|
||||||
isJust $ matchRegex regex val
|
|
||||||
#endif
|
|
||||||
|
|
||||||
toViewPath :: MetaValue -> FilePath
|
toViewPath :: MetaValue -> FilePath
|
||||||
toViewPath = concatMap escapeslash . fromMetaValue
|
toViewPath = concatMap escapeslash . fromMetaValue
|
||||||
|
|
43
Limit.hs
43
Limit.hs
|
@ -5,8 +5,6 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
|
||||||
|
|
||||||
module Limit where
|
module Limit where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
@ -29,18 +27,13 @@ import Logs.Group
|
||||||
import Logs.Unused
|
import Logs.Unused
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Git.Types (RefDate(..))
|
import Git.Types (RefDate(..))
|
||||||
|
import Utility.Glob
|
||||||
import Utility.HumanTime
|
import Utility.HumanTime
|
||||||
import Utility.DataUnits
|
import Utility.DataUnits
|
||||||
|
|
||||||
import Data.Time.Clock.POSIX
|
import Data.Time.Clock.POSIX
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import System.Path.WildMatch
|
|
||||||
|
|
||||||
#ifdef WITH_TDFA
|
|
||||||
import Text.Regex.TDFA
|
|
||||||
import Text.Regex.TDFA.String
|
|
||||||
#endif
|
|
||||||
|
|
||||||
{- Checks if there are user-specified limits. -}
|
{- Checks if there are user-specified limits. -}
|
||||||
limited :: Annex Bool
|
limited :: Annex Bool
|
||||||
|
@ -82,33 +75,21 @@ addInclude :: String -> Annex ()
|
||||||
addInclude = addLimit . limitInclude
|
addInclude = addLimit . limitInclude
|
||||||
|
|
||||||
limitInclude :: MkLimit
|
limitInclude :: MkLimit
|
||||||
limitInclude glob = Right $ const $ return . matchglob glob
|
limitInclude glob = Right $ const $ return . matchGlobFile glob
|
||||||
|
|
||||||
{- Add a limit to skip files that match the glob. -}
|
{- Add a limit to skip files that match the glob. -}
|
||||||
addExclude :: String -> Annex ()
|
addExclude :: String -> Annex ()
|
||||||
addExclude = addLimit . limitExclude
|
addExclude = addLimit . limitExclude
|
||||||
|
|
||||||
limitExclude :: MkLimit
|
limitExclude :: MkLimit
|
||||||
limitExclude glob = Right $ const $ return . not . matchglob glob
|
limitExclude glob = Right $ const $ return . not . matchGlobFile glob
|
||||||
|
|
||||||
{- Could just use wildCheckCase, but this way the regex is only compiled
|
matchGlobFile :: String -> (MatchInfo -> Bool)
|
||||||
- once. Also, we use regex-TDFA when available, because it's less buggy
|
matchGlobFile glob = go
|
||||||
- in its support of non-unicode characters. -}
|
|
||||||
matchglob :: String -> MatchInfo -> Bool
|
|
||||||
matchglob glob (MatchingFile fi) =
|
|
||||||
#ifdef WITH_TDFA
|
|
||||||
case cregex of
|
|
||||||
Right r -> case execute r (matchFile fi) of
|
|
||||||
Right (Just _) -> True
|
|
||||||
_ -> False
|
|
||||||
Left _ -> error $ "failed to compile regex: " ++ regex
|
|
||||||
where
|
where
|
||||||
cregex = compile defaultCompOpt defaultExecOpt regex
|
cglob = compileGlob glob CaseSensative -- memoized
|
||||||
regex = '^':wildToRegex glob
|
go (MatchingKey _) = False
|
||||||
#else
|
go (MatchingFile fi) = matchGlob cglob (matchFile fi)
|
||||||
wildCheckCase glob (matchFile fi)
|
|
||||||
#endif
|
|
||||||
matchglob _ (MatchingKey _) = False
|
|
||||||
|
|
||||||
{- Adds a limit to skip files not believed to be present
|
{- Adds a limit to skip files not believed to be present
|
||||||
- in a specfied repository. Optionally on a prior date. -}
|
- in a specfied repository. Optionally on a prior date. -}
|
||||||
|
@ -270,9 +251,13 @@ addMetaData = addLimit . limitMetaData
|
||||||
limitMetaData :: MkLimit
|
limitMetaData :: MkLimit
|
||||||
limitMetaData s = case parseMetaData s of
|
limitMetaData s = case parseMetaData s of
|
||||||
Left e -> Left e
|
Left e -> Left e
|
||||||
Right (f, v) -> Right $ const $ checkKey (check f v)
|
Right (f, v) ->
|
||||||
|
let cglob = compileGlob (fromMetaValue v) CaseInsensative
|
||||||
|
in Right $ const $ checkKey (check f cglob)
|
||||||
where
|
where
|
||||||
check f v k = S.member v . metaDataValues f <$> getCurrentMetaData k
|
check f cglob k = not . S.null
|
||||||
|
. S.filter (matchGlob cglob . fromMetaValue)
|
||||||
|
. metaDataValues f <$> getCurrentMetaData k
|
||||||
|
|
||||||
addTimeLimit :: String -> Annex ()
|
addTimeLimit :: String -> Annex ()
|
||||||
addTimeLimit s = do
|
addTimeLimit s = do
|
||||||
|
|
57
Utility/Glob.hs
Normal file
57
Utility/Glob.hs
Normal file
|
@ -0,0 +1,57 @@
|
||||||
|
{- file globbing
|
||||||
|
-
|
||||||
|
- This uses TDFA when available, with a fallback to regex-compat.
|
||||||
|
- TDFA is less buggy in its support for non-unicode characters.
|
||||||
|
-
|
||||||
|
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
|
module Utility.Glob (
|
||||||
|
Glob,
|
||||||
|
GlobCase(..),
|
||||||
|
compileGlob,
|
||||||
|
matchGlob
|
||||||
|
) where
|
||||||
|
|
||||||
|
import System.Path.WildMatch
|
||||||
|
|
||||||
|
#ifdef WITH_TDFA
|
||||||
|
import Text.Regex.TDFA
|
||||||
|
import Text.Regex.TDFA.String
|
||||||
|
#else
|
||||||
|
import Text.Regex
|
||||||
|
#endif
|
||||||
|
|
||||||
|
newtype Glob = Glob Regex
|
||||||
|
|
||||||
|
data GlobCase = CaseSensative | CaseInsensative
|
||||||
|
|
||||||
|
{- Compiles a glob to a regex, that can be repeatedly used. -}
|
||||||
|
compileGlob :: String -> GlobCase -> Glob
|
||||||
|
compileGlob glob globcase = Glob $
|
||||||
|
#ifdef WITH_TDFA
|
||||||
|
case compile (defaultCompOpt {caseSensitive = casesentitive}) defaultExecOpt regex of
|
||||||
|
Right r -> r
|
||||||
|
Left _ -> error $ "failed to compile regex: " ++ regex
|
||||||
|
#else
|
||||||
|
mkRegexWithOpts regex casesentitive True
|
||||||
|
#endif
|
||||||
|
where
|
||||||
|
regex = '^':wildToRegex glob
|
||||||
|
casesentitive = case globcase of
|
||||||
|
CaseSensative -> True
|
||||||
|
CaseInsensative -> False
|
||||||
|
|
||||||
|
matchGlob :: Glob -> String -> Bool
|
||||||
|
matchGlob (Glob regex) val =
|
||||||
|
#ifdef WITH_TDFA
|
||||||
|
case execute regex val of
|
||||||
|
Right (Just _) -> True
|
||||||
|
_ -> False
|
||||||
|
#else
|
||||||
|
isJust $ matchRegex regex val
|
||||||
|
#endif
|
2
debian/changelog
vendored
2
debian/changelog
vendored
|
@ -2,6 +2,8 @@ git-annex (5.20140222) UNRELEASED; urgency=medium
|
||||||
|
|
||||||
* Fix handling of rsync remote urls containing a username,
|
* Fix handling of rsync remote urls containing a username,
|
||||||
including rsync.net.
|
including rsync.net.
|
||||||
|
* --metadata field=value can now use globs to match, and matches
|
||||||
|
case insensatively, the same as git annex view field=value does.
|
||||||
|
|
||||||
-- Joey Hess <joeyh@debian.org> Fri, 21 Feb 2014 13:03:04 -0400
|
-- Joey Hess <joeyh@debian.org> Fri, 21 Feb 2014 13:03:04 -0400
|
||||||
|
|
||||||
|
|
|
@ -1133,10 +1133,10 @@ file contents are present at either of two repositories.
|
||||||
The size can be specified with any commonly used units, for example,
|
The size can be specified with any commonly used units, for example,
|
||||||
"0.5 gb" or "100 KiloBytes"
|
"0.5 gb" or "100 KiloBytes"
|
||||||
|
|
||||||
* `--metadata field=value`
|
* `--metadata field=glob`
|
||||||
|
|
||||||
Matches only files that have a metadata field attached with the specified
|
Matches only files that have a metadata field attached with a value that
|
||||||
value.
|
matches the glob.
|
||||||
|
|
||||||
* `--want-get`
|
* `--want-get`
|
||||||
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue