2011-09-18 17:47:49 -04:00
|
|
|
{- user-specified limits on files to act on
|
|
|
|
-
|
2013-04-25 23:44:55 -04:00
|
|
|
- Copyright 2011-2013 Joey Hess <joey@kitenet.net>
|
2011-09-18 17:47:49 -04:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-04-03 03:52:41 -04:00
|
|
|
{-# LANGUAGE CPP #-}
|
2013-02-10 15:48:38 -04:00
|
|
|
|
2011-09-18 17:47:49 -04:00
|
|
|
module Limit where
|
|
|
|
|
2012-09-25 16:48:24 -04:00
|
|
|
import Data.Time.Clock.POSIX
|
2012-10-01 18:25:11 -04:00
|
|
|
import qualified Data.Set as S
|
2012-10-08 15:18:58 -04:00
|
|
|
import qualified Data.Map as M
|
2013-02-10 15:48:38 -04:00
|
|
|
import System.Path.WildMatch
|
2013-05-11 15:03:00 -05:00
|
|
|
import System.PosixCompat.Files
|
2011-09-18 17:47:49 -04:00
|
|
|
|
2011-10-05 16:02:51 -04:00
|
|
|
import Common.Annex
|
2011-10-03 22:24:57 -04:00
|
|
|
import qualified Annex
|
2011-09-18 17:47:49 -04:00
|
|
|
import qualified Utility.Matcher
|
2011-09-18 20:14:18 -04:00
|
|
|
import qualified Remote
|
|
|
|
import qualified Backend
|
2011-10-04 00:40:47 -04:00
|
|
|
import Annex.Content
|
2012-10-05 16:52:44 -04:00
|
|
|
import Annex.UUID
|
2012-09-23 19:50:31 +02:00
|
|
|
import Logs.Trust
|
2012-10-03 17:04:52 -04:00
|
|
|
import Types.TrustLevel
|
2012-10-08 13:39:18 -04:00
|
|
|
import Types.Key
|
2012-10-08 15:18:58 -04:00
|
|
|
import Types.Group
|
2013-05-24 23:07:26 -04:00
|
|
|
import Types.FileMatcher
|
2012-10-01 18:25:11 -04:00
|
|
|
import Logs.Group
|
2012-09-25 16:48:24 -04:00
|
|
|
import Utility.HumanTime
|
2012-10-08 13:39:18 -04:00
|
|
|
import Utility.DataUnits
|
2011-09-18 17:47:49 -04:00
|
|
|
|
2013-05-26 18:14:03 -04:00
|
|
|
#ifdef WITH_TDFA
|
|
|
|
import Text.Regex.TDFA
|
|
|
|
import Text.Regex.TDFA.String
|
|
|
|
#else
|
|
|
|
import System.Path.WildMatch
|
|
|
|
import Types.FileMatcher
|
|
|
|
#endif
|
|
|
|
|
2013-05-24 23:07:26 -04:00
|
|
|
type MatchFiles = AssumeNotPresent -> FileInfo -> Annex Bool
|
2012-10-05 16:52:44 -04:00
|
|
|
type MkLimit = String -> Either String MatchFiles
|
|
|
|
type AssumeNotPresent = S.Set UUID
|
2011-09-18 17:47:49 -04:00
|
|
|
|
2011-09-18 20:41:51 -04:00
|
|
|
{- Checks if there are user-specified limits. -}
|
|
|
|
limited :: Annex Bool
|
2012-12-06 13:22:16 -04:00
|
|
|
limited = (not . Utility.Matcher.isEmpty) <$> getMatcher'
|
2011-09-18 20:41:51 -04:00
|
|
|
|
2011-09-18 17:47:49 -04:00
|
|
|
{- 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. -}
|
2013-05-24 23:07:26 -04:00
|
|
|
getMatcher :: Annex (FileInfo -> Annex Bool)
|
2011-09-19 01:03:16 -04:00
|
|
|
getMatcher = Utility.Matcher.matchM <$> getMatcher'
|
2011-09-18 22:40:31 -04:00
|
|
|
|
2013-05-24 23:07:26 -04:00
|
|
|
getMatcher' :: Annex (Utility.Matcher.Matcher (FileInfo -> Annex Bool))
|
2011-09-18 22:40:31 -04:00
|
|
|
getMatcher' = do
|
2011-09-18 17:47:49 -04:00
|
|
|
m <- Annex.getState Annex.limit
|
|
|
|
case m of
|
|
|
|
Right r -> return r
|
|
|
|
Left l -> do
|
|
|
|
let matcher = Utility.Matcher.generate (reverse l)
|
2013-03-12 05:05:33 -04:00
|
|
|
Annex.changeState $ \s ->
|
|
|
|
s { Annex.limit = Right matcher }
|
2011-09-18 17:47:49 -04:00
|
|
|
return matcher
|
|
|
|
|
2011-09-18 18:21:42 -04:00
|
|
|
{- Adds something to the limit list, which is built up reversed. -}
|
2013-05-24 23:07:26 -04:00
|
|
|
add :: Utility.Matcher.Token (FileInfo -> Annex Bool) -> Annex ()
|
2011-09-19 01:57:12 -04:00
|
|
|
add l = Annex.changeState $ \s -> s { Annex.limit = prepend $ Annex.limit s }
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
|
|
|
prepend (Left ls) = Left $ l:ls
|
|
|
|
prepend _ = error "internal"
|
2011-09-18 17:47:49 -04:00
|
|
|
|
|
|
|
{- Adds a new token. -}
|
2011-09-20 00:49:40 -04:00
|
|
|
addToken :: String -> Annex ()
|
|
|
|
addToken = add . Utility.Matcher.token
|
|
|
|
|
|
|
|
{- Adds a new limit. -}
|
2012-10-05 16:52:44 -04:00
|
|
|
addLimit :: Either String MatchFiles -> Annex ()
|
|
|
|
addLimit = either error (\l -> add $ Utility.Matcher.Operation $ l S.empty)
|
2011-09-18 17:47:49 -04:00
|
|
|
|
|
|
|
{- Add a limit to skip files that do not match the glob. -}
|
2011-12-22 13:53:06 -04:00
|
|
|
addInclude :: String -> Annex ()
|
2012-10-04 15:48:59 -04:00
|
|
|
addInclude = addLimit . limitInclude
|
|
|
|
|
|
|
|
limitInclude :: MkLimit
|
2012-10-05 16:52:44 -04:00
|
|
|
limitInclude glob = Right $ const $ return . matchglob glob
|
2011-12-22 13:53:06 -04:00
|
|
|
|
|
|
|
{- Add a limit to skip files that match the glob. -}
|
2011-09-18 20:14:18 -04:00
|
|
|
addExclude :: String -> Annex ()
|
2012-10-04 15:48:59 -04:00
|
|
|
addExclude = addLimit . limitExclude
|
|
|
|
|
|
|
|
limitExclude :: MkLimit
|
2012-10-05 16:52:44 -04:00
|
|
|
limitExclude glob = Right $ const $ return . not . matchglob glob
|
2011-12-22 13:53:06 -04:00
|
|
|
|
2013-02-26 13:49:22 -04:00
|
|
|
{- Could just use wildCheckCase, but this way the regex is only compiled
|
2013-05-06 09:44:55 -04:00
|
|
|
- once. Also, we use regex-TDFA when available, because it's less buggy
|
|
|
|
- in its support of non-unicode characters. -}
|
2013-05-24 23:07:26 -04:00
|
|
|
matchglob :: String -> FileInfo -> Bool
|
2013-04-25 23:44:55 -04:00
|
|
|
matchglob glob fi =
|
2013-05-06 09:44:55 -04:00
|
|
|
#ifdef WITH_TDFA
|
2013-03-08 15:29:01 -04:00
|
|
|
case cregex of
|
2013-05-24 23:07:26 -04:00
|
|
|
Right r -> case execute r (matchFile fi) of
|
2013-03-08 15:29:01 -04:00
|
|
|
Right (Just _) -> True
|
|
|
|
_ -> False
|
|
|
|
Left _ -> error $ "failed to compile regex: " ++ regex
|
2013-02-11 11:47:53 -04:00
|
|
|
where
|
2013-03-08 15:29:01 -04:00
|
|
|
cregex = compile defaultCompOpt defaultExecOpt regex
|
2012-10-28 22:09:09 -04:00
|
|
|
regex = '^':wildToRegex glob
|
2013-05-06 09:44:55 -04:00
|
|
|
#else
|
2013-05-26 18:14:03 -04:00
|
|
|
wildCheckCase glob (matchFile fi)
|
2013-05-06 09:44:55 -04:00
|
|
|
#endif
|
2011-09-18 20:14:18 -04:00
|
|
|
|
|
|
|
{- Adds a limit to skip files not believed to be present
|
2011-09-19 01:57:12 -04:00
|
|
|
- in a specfied repository. -}
|
2011-09-18 20:14:18 -04:00
|
|
|
addIn :: String -> Annex ()
|
2012-10-04 15:48:59 -04:00
|
|
|
addIn = addLimit . limitIn
|
|
|
|
|
|
|
|
limitIn :: MkLimit
|
2012-10-05 16:52:44 -04:00
|
|
|
limitIn name = Right $ \notpresent -> check $
|
|
|
|
if name == "."
|
|
|
|
then inhere notpresent
|
|
|
|
else inremote notpresent
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
|
|
|
check a = lookupFile >=> handle a
|
|
|
|
handle _ Nothing = return False
|
|
|
|
handle a (Just (key, _)) = a key
|
|
|
|
inremote notpresent key = do
|
|
|
|
u <- Remote.nameToUUID name
|
|
|
|
us <- Remote.keyLocations key
|
|
|
|
return $ u `elem` us && u `S.notMember` notpresent
|
|
|
|
inhere notpresent key
|
|
|
|
| S.null notpresent = inAnnex key
|
|
|
|
| otherwise = do
|
|
|
|
u <- getUUID
|
|
|
|
if u `S.member` notpresent
|
|
|
|
then return False
|
|
|
|
else inAnnex key
|
2011-09-18 20:23:08 -04:00
|
|
|
|
2012-10-19 16:09:21 -04:00
|
|
|
{- Limit to content that is currently present on a uuid. -}
|
|
|
|
limitPresent :: Maybe UUID -> MkLimit
|
2012-10-20 15:30:11 -04:00
|
|
|
limitPresent u _ = Right $ const $ check $ \key -> do
|
2012-10-19 16:09:21 -04:00
|
|
|
hereu <- getUUID
|
2013-04-03 03:52:41 -04:00
|
|
|
if u == Just hereu || isNothing u
|
2012-10-19 16:09:21 -04:00
|
|
|
then inAnnex key
|
|
|
|
else do
|
|
|
|
us <- Remote.keyLocations key
|
|
|
|
return $ maybe False (`elem` us) u
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
|
|
|
check a = lookupFile >=> handle a
|
|
|
|
handle _ Nothing = return False
|
|
|
|
handle a (Just (key, _)) = a key
|
2012-10-19 16:09:21 -04:00
|
|
|
|
2013-04-25 23:44:55 -04:00
|
|
|
{- Limit to content that is in a directory, anywhere in the repository tree -}
|
|
|
|
limitInDir :: FilePath -> MkLimit
|
|
|
|
limitInDir dir = const $ Right $ const $ \fi -> return $
|
2013-05-24 23:07:26 -04:00
|
|
|
any (== dir) $ splitPath $ takeDirectory $ matchFile fi
|
2013-04-25 23:44:55 -04:00
|
|
|
|
2011-09-18 20:23:08 -04:00
|
|
|
{- Adds a limit to skip files not believed to have the specified number
|
|
|
|
- of copies. -}
|
|
|
|
addCopies :: String -> Annex ()
|
2012-10-04 15:48:59 -04:00
|
|
|
addCopies = addLimit . limitCopies
|
|
|
|
|
|
|
|
limitCopies :: MkLimit
|
|
|
|
limitCopies want = case split ":" want of
|
2013-04-02 23:40:13 -04:00
|
|
|
[v, n] -> case parsetrustspec v of
|
2013-04-03 17:44:34 -04:00
|
|
|
Just checker -> go n $ checktrust checker
|
2012-10-04 15:48:59 -04:00
|
|
|
Nothing -> go n $ checkgroup v
|
|
|
|
[n] -> go n $ const $ return True
|
|
|
|
_ -> Left "bad value for copies"
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
|
|
|
go num good = case readish num of
|
|
|
|
Nothing -> Left "bad number for copies"
|
|
|
|
Just n -> Right $ \notpresent f ->
|
|
|
|
lookupFile f >>= handle n good notpresent
|
|
|
|
handle _ _ _ Nothing = return False
|
|
|
|
handle n good notpresent (Just (key, _)) = do
|
|
|
|
us <- filter (`S.notMember` notpresent)
|
|
|
|
<$> (filterM good =<< Remote.keyLocations key)
|
|
|
|
return $ length us >= n
|
2013-04-03 17:44:34 -04:00
|
|
|
checktrust checker u = checker <$> lookupTrust u
|
2012-10-28 22:09:09 -04:00
|
|
|
checkgroup g u = S.member g <$> lookupGroups u
|
2013-04-02 23:40:13 -04:00
|
|
|
parsetrustspec s
|
|
|
|
| "+" `isSuffixOf` s = (>=) <$> readTrustLevel (beginning s)
|
|
|
|
| otherwise = (==) <$> readTrustLevel s
|
2011-11-28 17:37:15 -04:00
|
|
|
|
2012-10-08 15:18:58 -04:00
|
|
|
{- Adds a limit to skip files not believed to be present in all
|
|
|
|
- repositories in the specified group. -}
|
2012-10-10 12:59:45 -04:00
|
|
|
addInAllGroup :: String -> Annex ()
|
|
|
|
addInAllGroup groupname = do
|
2012-10-08 15:18:58 -04:00
|
|
|
m <- groupMap
|
2012-10-10 12:59:45 -04:00
|
|
|
addLimit $ limitInAllGroup m groupname
|
2012-10-08 15:18:58 -04:00
|
|
|
|
2012-10-10 12:59:45 -04:00
|
|
|
limitInAllGroup :: GroupMap -> MkLimit
|
|
|
|
limitInAllGroup m groupname
|
2012-10-08 15:18:58 -04:00
|
|
|
| S.null want = Right $ const $ const $ return True
|
2012-10-17 16:01:09 -04:00
|
|
|
| otherwise = Right $ \notpresent -> lookupFile >=> check notpresent
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
|
|
|
want = fromMaybe S.empty $ M.lookup groupname $ uuidsByGroup m
|
|
|
|
check _ Nothing = return False
|
|
|
|
check notpresent (Just (key, _))
|
|
|
|
-- optimisation: Check if a wanted uuid is notpresent.
|
|
|
|
| not (S.null (S.intersection want notpresent)) = return False
|
|
|
|
| otherwise = do
|
|
|
|
present <- S.fromList <$> Remote.keyLocations key
|
|
|
|
return $ S.null $ want `S.difference` present
|
2012-10-08 15:18:58 -04:00
|
|
|
|
2011-11-28 17:37:15 -04:00
|
|
|
{- Adds a limit to skip files not using a specified key-value backend. -}
|
|
|
|
addInBackend :: String -> Annex ()
|
2012-10-04 15:48:59 -04:00
|
|
|
addInBackend = addLimit . limitInBackend
|
|
|
|
|
|
|
|
limitInBackend :: MkLimit
|
2012-10-17 16:01:09 -04:00
|
|
|
limitInBackend name = Right $ const $ lookupFile >=> check
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
|
|
|
wanted = Backend.lookupBackendName name
|
|
|
|
check = return . maybe False ((==) wanted . snd)
|
2012-09-25 16:48:24 -04:00
|
|
|
|
2012-10-08 13:39:18 -04:00
|
|
|
{- Adds a limit to skip files that are too large or too small -}
|
|
|
|
addLargerThan :: String -> Annex ()
|
|
|
|
addLargerThan = addLimit . limitSize (>)
|
|
|
|
|
|
|
|
addSmallerThan :: String -> Annex ()
|
|
|
|
addSmallerThan = addLimit . limitSize (<)
|
|
|
|
|
|
|
|
limitSize :: (Maybe Integer -> Maybe Integer -> Bool) -> MkLimit
|
|
|
|
limitSize vs s = case readSize dataUnits s of
|
|
|
|
Nothing -> Left "bad size"
|
2013-03-29 16:17:13 -04:00
|
|
|
Just sz -> Right $ go sz
|
2012-10-28 22:09:09 -04:00
|
|
|
where
|
2013-03-29 16:17:13 -04:00
|
|
|
go sz _ fi = lookupFile fi >>= check fi sz
|
|
|
|
check _ sz (Just (key, _)) = return $ keySize key `vs` Just sz
|
|
|
|
check fi sz Nothing = do
|
|
|
|
filesize <- liftIO $ catchMaybeIO $
|
|
|
|
fromIntegral . fileSize
|
2013-05-24 23:07:26 -04:00
|
|
|
<$> getFileStatus (relFile fi)
|
2013-03-29 16:17:13 -04:00
|
|
|
return $ filesize `vs` Just sz
|
2012-10-08 13:39:18 -04:00
|
|
|
|
2012-09-25 16:48:24 -04:00
|
|
|
addTimeLimit :: String -> Annex ()
|
|
|
|
addTimeLimit s = do
|
|
|
|
let seconds = fromMaybe (error "bad time-limit") $ parseDuration s
|
|
|
|
start <- liftIO getPOSIXTime
|
|
|
|
let cutoff = start + seconds
|
2012-10-05 16:52:44 -04:00
|
|
|
addLimit $ Right $ const $ const $ do
|
2012-09-25 16:48:24 -04:00
|
|
|
now <- liftIO getPOSIXTime
|
|
|
|
if now > cutoff
|
|
|
|
then do
|
|
|
|
warning $ "Time limit (" ++ s ++ ") reached!"
|
|
|
|
liftIO $ exitWith $ ExitFailure 101
|
|
|
|
else return True
|
2012-10-17 16:01:09 -04:00
|
|
|
|
2013-05-24 23:07:26 -04:00
|
|
|
lookupFile :: FileInfo -> Annex (Maybe (Key, Backend))
|
|
|
|
lookupFile = Backend.lookupFile . relFile
|