{-# LANGUAGE CPP #-}
module System.FilePath.Glob.Match (match, matchWith) where
import Control.Exception (assert)
import Data.Char (isDigit, toLower, toUpper)
import Data.List (findIndex)
import Data.Maybe (fromMaybe, isJust)
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (mappend)
#endif
import System.FilePath (isPathSeparator, isExtSeparator)
import System.FilePath.Glob.Base ( Pattern(..), Token(..)
, MatchOptions(..), matchDefault
, isLiteral, tokToLower
)
import System.FilePath.Glob.Utils (dropLeadingZeroes, inRange, pathParts)
match :: Pattern -> FilePath -> Bool
match = matchWith matchDefault
matchWith :: MatchOptions -> Pattern -> FilePath -> Bool
matchWith opts p f = begMatch opts (lcPat $ unPattern p) (lcPath f)
where
lcPath = if ignoreCase opts then map toLower else id
lcPat = if ignoreCase opts then map tokToLower else id
begMatch, match' :: MatchOptions -> [Token] -> FilePath -> Bool
begMatch _ (Literal '.' : AnyDirectory : _) (x:y:_)
| isExtSeparator x && isExtSeparator y = False
begMatch opts (Literal '.' : PathSeparator : pat) s | ignoreDotSlash opts =
begMatch opts (dropWhile isSlash pat) (dropDotSlash s)
where
isSlash PathSeparator = True
isSlash _ = False
dropDotSlash (x:y:ys) | isExtSeparator x && isPathSeparator y =
dropWhile isPathSeparator ys
dropDotSlash xs = xs
begMatch opts pat (x:y:s)
| dotSlash && dotStarSlash = match' opts pat' s
| ignoreDotSlash opts && dotSlash =
begMatch opts pat (dropWhile isPathSeparator s)
where
dotSlash = isExtSeparator x && isPathSeparator y
(dotStarSlash, pat') =
case pat of
Literal '.': AnyNonPathSeparator : PathSeparator : rest -> (True, rest)
_ -> (False, pat)
begMatch opts pat (e:_)
| isExtSeparator e
&& not (matchDotsImplicitly opts)
&& not (isLiteral . Pattern $ take 1 pat) = False
begMatch opts pat s = match' opts pat s
match' _ [] s = null s
match' _ (AnyNonPathSeparator:s) "" = null s
match' _ _ "" = False
match' o (Literal l :xs) (c:cs) = l == c && match' o xs cs
match' o (NonPathSeparator:xs) (c:cs) =
not (isPathSeparator c) && match' o xs cs
match' o (PathSeparator :xs) (c:cs) =
isPathSeparator c && begMatch o (dropWhile (== PathSeparator) xs)
(dropWhile isPathSeparator cs)
match' o (CharRange b rng :xs) (c:cs) =
let rangeMatch r =
either (== c) (`inRange` c) r ||
ignoreCase o && either (== toUpper c) (`inRange` toUpper c) r
in not (isPathSeparator c) &&
any rangeMatch rng == b &&
match' o xs cs
match' o (OpenRange lo hi :xs) path =
let getNumChoices n =
tail . takeWhile (not.null.snd) . map (`splitAt` n) $ [0..]
(lzNum,cs) = span isDigit path
num = dropLeadingZeroes lzNum
numChoices = getNumChoices num
zeroChoices = takeWhile (all (=='0') . fst) (getNumChoices lzNum)
in
not (null lzNum) &&
(any (\(n,rest) -> inOpenRange lo hi n && match' o xs (rest ++ cs))
((num,"") : numChoices)
|| (not (null zeroChoices) && inOpenRange lo hi "0"
&& any (\(_,rest) -> match' o xs (rest ++ cs)) zeroChoices))
match' o again@(AnyNonPathSeparator:xs) path@(c:cs) =
match' o xs path || (not (isPathSeparator c) && match' o again cs)
match' o (AnyDirectory:xs) path =
if matchDotsImplicitly o
then hasMatch
else hasMatch && all (not.isExtSeparator.head) matchedDirs
where parts = pathParts (dropWhile isPathSeparator path)
matchIndex = findIndex (match' o xs) parts
hasMatch = isJust matchIndex
matchedDirs = take (fromMaybe 0 matchIndex) parts
match' o (LongLiteral len s:xs) path =
let (pre,cs) = splitAt len path
in pre == s && match' o xs cs
match' _ (Unmatchable:_) _ = False
match' _ (ExtSeparator:_) _ = error "ExtSeparator survived optimization?"
inOpenRange :: Maybe String -> Maybe String -> String -> Bool
inOpenRange l_ h_ s_ = assert (all isDigit s_) $ go l_ h_ s_ EQ EQ
where
go Nothing Nothing _ _ _ = True
go (Just []) _ [] LT _ = False
go _ (Just []) _ _ GT = False
go _ (Just []) (_:_) _ _ = False
go (Just (_:_)) _ [] _ _ = False
go _ _ [] _ _ = True
go (Just (l:ls)) (Just (h:hs)) (c:cs) ordl ordh =
let ordl' = ordl `mappend` compare c l
ordh' = ordh `mappend` compare c h
in go (Just ls) (Just hs) cs ordl' ordh'
go Nothing (Just (h:hs)) (c:cs) _ ordh =
let ordh' = ordh `mappend` compare c h
in go Nothing (Just hs) cs GT ordh'
go (Just (l:ls)) Nothing (c:cs) ordl _ =
let ordl' = ordl `mappend` compare c l
in go (Just ls) Nothing cs ordl' LT
go (Just []) hi s _ ordh = go Nothing hi s GT ordh