annex.largefiles: Add support for mimetype=text/* etc, when git-annex is linked with libmagic.
This commit is contained in:
parent
86444fe507
commit
5127cb59cc
8 changed files with 78 additions and 11 deletions
30
Limit.hs
30
Limit.hs
|
@ -1,10 +1,12 @@
|
|||
{- user-specified limits on files to act on
|
||||
-
|
||||
- Copyright 2011-2014 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2011-2016 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Limit where
|
||||
|
||||
import Annex.Common
|
||||
|
@ -30,6 +32,10 @@ import Utility.Glob
|
|||
import Utility.HumanTime
|
||||
import Utility.DataUnits
|
||||
|
||||
#ifdef WITH_MAGICMIME
|
||||
import Magic
|
||||
#endif
|
||||
|
||||
import Data.Time.Clock.POSIX
|
||||
import qualified Data.Set as S
|
||||
import qualified Data.Map as M
|
||||
|
@ -84,11 +90,23 @@ limitExclude glob = Right $ const $ not <$$> matchGlobFile glob
|
|||
|
||||
matchGlobFile :: String -> MatchInfo -> Annex Bool
|
||||
matchGlobFile glob = go
|
||||
where
|
||||
cglob = compileGlob glob CaseSensative -- memoized
|
||||
go (MatchingKey _) = pure False
|
||||
go (MatchingFile fi) = pure $ matchGlob cglob (matchFile fi)
|
||||
go (MatchingInfo af _ _) = matchGlob cglob <$> getInfo af
|
||||
where
|
||||
cglob = compileGlob glob CaseSensative -- memoized
|
||||
go (MatchingKey _) = pure False
|
||||
go (MatchingFile fi) = pure $ matchGlob cglob (matchFile fi)
|
||||
go (MatchingInfo af _ _) = matchGlob cglob <$> getInfo af
|
||||
|
||||
#ifdef WITH_MAGICMIME
|
||||
matchMagic :: Magic -> MkLimit Annex
|
||||
matchMagic magic glob = Right $ const go
|
||||
where
|
||||
cglob = compileGlob glob CaseSensative -- memoized
|
||||
go (MatchingKey _) = pure False
|
||||
go (MatchingFile fi) = check (matchFile fi)
|
||||
go (MatchingInfo af _ _) = check =<< getInfo af
|
||||
check f = liftIO $ catchBoolIO $
|
||||
matchGlob cglob <$> magicFile magic f
|
||||
#endif
|
||||
|
||||
{- Adds a limit to skip files not believed to be present
|
||||
- in a specfied repository. Optionally on a prior date. -}
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue