git-annex/Limit.hs

91 lines
2.6 KiB
Haskell
Raw Normal View History

{- 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
2011-10-05 20:02:51 +00:00
import Common.Annex
import qualified Annex
import qualified Utility.Matcher
2011-09-19 00:14:18 +00:00
import qualified Remote
import qualified Backend
2011-10-15 20:21:08 +00:00
import Logs.Location
2011-10-04 04:40:47 +00:00
import Annex.Content
type Limit = Utility.Matcher.Token (FilePath -> Annex Bool)
{- 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 (FilePath -> Annex Bool)
2011-09-19 05:03:16 +00:00
getMatcher = Utility.Matcher.matchM <$> getMatcher'
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, which is built up reversed. -}
add :: Limit -> Annex ()
2011-09-19 05:57:12 +00:00
add l = Annex.changeState $ \s -> s { Annex.limit = prepend $ Annex.limit s }
where
2011-09-19 05:57:12 +00:00
prepend (Left ls) = Left $ l:ls
prepend _ = error "internal"
{- Adds a new token. -}
addToken :: String -> Annex ()
addToken = add . Utility.Matcher.token
{- Adds a new limit. -}
addLimit :: (FilePath -> Annex Bool) -> Annex ()
addLimit = add . Utility.Matcher.Operation
{- Add a limit to skip files that do not match the glob. -}
2011-09-19 00:14:18 +00:00
addExclude :: String -> Annex ()
addExclude glob = addLimit $ return . notExcluded
where
notExcluded f = isNothing $ match cregex f []
cregex = compile regex []
regex = '^':wildToRegex glob
2011-09-19 00:14:18 +00:00
{- Adds a limit to skip files not believed to be present
2011-09-19 05:57:12 +00:00
- in a specfied repository. -}
2011-09-19 00:14:18 +00:00
addIn :: String -> Annex ()
2011-10-11 18:43:45 +00:00
addIn name = addLimit $ check $ if name == "." then inAnnex else inremote
2011-09-19 00:14:18 +00:00
where
check a = Backend.lookupFile >=> handle a
2011-09-19 00:14:18 +00:00
handle _ Nothing = return False
handle a (Just (key, _)) = a key
2011-10-11 18:43:45 +00:00
inremote key = do
u <- Remote.nameToUUID name
2011-09-19 00:14:18 +00:00
us <- keyLocations key
return $ u `elem` us
{- Adds a limit to skip files not believed to have the specified number
- of copies. -}
addCopies :: String -> Annex ()
2011-09-21 03:24:48 +00:00
addCopies num =
case readMaybe num :: Maybe Int of
Nothing -> error "bad number for --copies"
Just n -> addLimit $ check n
where
check n = Backend.lookupFile >=> handle n
handle _ Nothing = return False
handle n (Just (key, _)) = do
us <- keyLocations key
return $ length us >= n