aboutsummaryrefslogtreecommitdiff
path: root/Limit.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-09-18 17:47:49 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-09-18 17:47:49 -0400
commit8a5a92480b9dcf691af1e8c4849cb71c4158b845 (patch)
tree04a240460520e892532ca8363a71454538e16e6f /Limit.hs
parent38c0f3eaf86b67d584d4ff30ab15ec2c725a7fad (diff)
refactor --exclude to use Utility.Matcher
This should change no behavior, but opens the poissibility to use the matcher for other sorts of limits on which files git-annex processes.
Diffstat (limited to 'Limit.hs')
-rw-r--r--Limit.hs59
1 files changed, 59 insertions, 0 deletions
diff --git a/Limit.hs b/Limit.hs
new file mode 100644
index 000000000..324baee2e
--- /dev/null
+++ b/Limit.hs
@@ -0,0 +1,59 @@
+{- user-specified limits on files to act on
+ -
+ - Copyright 2011 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Limit where
+
+import Text.Regex.PCRE.Light.Char8
+import System.Path.WildMatch
+import Control.Monad (filterM)
+import Data.Maybe
+
+import Annex
+import qualified Utility.Matcher
+
+type Limit = Utility.Matcher.Token (FilePath -> Annex Bool)
+
+{- Filter out files not matching user-specified limits. -}
+filterFiles :: [FilePath] -> Annex [FilePath]
+filterFiles l = do
+ matcher <- getMatcher
+ filterM (Utility.Matcher.matchM matcher) l
+
+{- 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))
+getMatcher = do
+ m <- Annex.getState Annex.limit
+ case m of
+ Right r -> return r
+ Left l -> do
+ let matcher = Utility.Matcher.generate (reverse l)
+ Annex.changeState $ \s -> s { Annex.limit = Right matcher }
+ return matcher
+
+{- Adds something to the limit list. -}
+add :: Limit -> Annex ()
+add l = Annex.changeState $ \s -> s { Annex.limit = append $ Annex.limit s }
+ where
+ append (Left ls) = Left $ l:ls
+ append _ = error "internal"
+
+{- Adds a new limit. -}
+addl :: (FilePath -> Annex Bool) -> Annex ()
+addl = add . Utility.Matcher.Operation
+
+{- Adds a new token. -}
+addt :: String -> Annex ()
+addt = add . Utility.Matcher.Token
+
+{- Add a limit to skip files that do not match the glob. -}
+exclude :: String -> Annex ()
+exclude glob = addl $ return . notExcluded
+ where
+ notExcluded f = isNothing $ match cregex f []
+ cregex = compile regex []
+ regex = '^':wildToRegex glob