module System.FilePath.Glob.Directory
( GlobOptions(..), globDefault
, globDir, globDirWith, globDir1, glob
, commonDirectory
) where
import Control.Arrow (first, second)
import Control.Monad (forM)
import qualified Data.DList as DL
import Data.DList (DList)
import Data.List ((\\), find)
import System.Directory ( doesDirectoryExist, getDirectoryContents
, getCurrentDirectory
)
import System.FilePath ( (</>), takeDrive, splitDrive
, isExtSeparator
, pathSeparator, isPathSeparator
, takeDirectory
)
import System.FilePath.Glob.Base ( Pattern(..), Token(..)
, MatchOptions, matchDefault
, compile
)
import System.FilePath.Glob.Match (matchWith)
import System.FilePath.Glob.Utils ( getRecursiveContents
, nubOrd
, pathParts
, partitionDL, tailDL
, catchIO
)
data GlobOptions = GlobOptions
{ matchOptions :: MatchOptions
, includeUnmatched :: Bool
}
globDefault :: GlobOptions
globDefault = GlobOptions matchDefault False
data TypedPattern
= Any Pattern
| Dir Int Pattern
| AnyDir Int Pattern
deriving Show
globDir :: [Pattern] -> FilePath -> IO [[FilePath]]
globDir pats dir = fmap fst (globDirWith globDefault pats dir)
globDirWith :: GlobOptions -> [Pattern] -> FilePath
-> IO ([[FilePath]], Maybe [FilePath])
globDirWith opts [pat] dir | not (includeUnmatched opts) =
let (prefix, pat') = commonDirectory pat
in globDirWith' opts [pat'] (dir </> prefix)
globDirWith opts pats dir =
globDirWith' opts pats dir
globDirWith' :: GlobOptions -> [Pattern] -> FilePath
-> IO ([[FilePath]], Maybe [FilePath])
globDirWith' opts [] dir =
if includeUnmatched opts
then do
dir' <- if null dir then getCurrentDirectory else return dir
c <- getRecursiveContents dir'
return ([], Just (DL.toList c))
else
return ([], Nothing)
globDirWith' opts pats@(_:_) dir = do
results <- mapM (\p -> globDir'0 opts p dir) pats
let (matches, others) = unzip results
allMatches = DL.toList . DL.concat $ matches
allOthers = DL.toList . DL.concat $ others
return ( map DL.toList matches
, if includeUnmatched opts
then Just (nubOrd allOthers \\ allMatches)
else Nothing
)
globDir1 :: Pattern -> FilePath -> IO [FilePath]
globDir1 p = fmap head . globDir [p]
glob :: String -> IO [FilePath]
glob = flip globDir1 "" . compile
globDir'0 :: GlobOptions -> Pattern -> FilePath
-> IO (DList FilePath, DList FilePath)
globDir'0 opts pat dir = do
let (pat', drive) = driveSplit pat
dir' <- case drive of
Just "" -> fmap takeDrive getCurrentDirectory
Just d -> return d
Nothing -> if null dir then getCurrentDirectory else return dir
globDir' opts (separate pat') dir'
globDir' :: GlobOptions -> [TypedPattern] -> FilePath
-> IO (DList FilePath, DList FilePath)
globDir' opts pats@(_:_) dir = do
entries <- getDirectoryContents dir `catchIO` const (return [])
results <- forM entries $ \e -> matchTypedAndGo opts pats e (dir </> e)
let (matches, others) = unzip results
return (DL.concat matches, DL.concat others)
globDir' _ [] dir =
return (DL.singleton (dir ++ [pathSeparator]), DL.empty)
matchTypedAndGo :: GlobOptions
-> [TypedPattern]
-> FilePath -> FilePath
-> IO (DList FilePath, DList FilePath)
matchTypedAndGo opts [Any p] path absPath =
if matchWith (matchOptions opts) p path
then return (DL.singleton absPath, DL.empty)
else doesDirectoryExist absPath >>= didNotMatch opts path absPath
matchTypedAndGo opts (Dir n p:ps) path absPath = do
isDir <- doesDirectoryExist absPath
if isDir && matchWith (matchOptions opts) p path
then globDir' opts ps (absPath ++ replicate n pathSeparator)
else didNotMatch opts path absPath isDir
matchTypedAndGo opts (AnyDir n p:ps) path absPath =
if path `elem` [".",".."]
then didNotMatch opts path absPath True
else do
isDir <- doesDirectoryExist absPath
let m = matchWith (matchOptions opts) (unseparate ps)
unconditionalMatch =
null (unPattern p) && not (isExtSeparator $ head path)
p' = Pattern (unPattern p ++ [AnyNonPathSeparator])
case unconditionalMatch || matchWith (matchOptions opts) p' path of
True | isDir -> do
contents <- getRecursiveContents absPath
return $
if null ps
then ( DL.singleton $
DL.head contents
++ replicate n pathSeparator
, tailDL contents
)
else let (matches, nonMatches) =
partitionDL fst
(fmap (recursiveMatch n m) contents)
in (fmap snd matches, fmap snd nonMatches)
True | m path ->
return ( DL.singleton $
takeDirectory absPath
++ replicate n pathSeparator
++ path
, DL.empty
)
_ ->
didNotMatch opts path absPath isDir
matchTypedAndGo _ _ _ _ = error "Glob.matchTypedAndGo :: internal error"
recursiveMatch :: Int -> (FilePath -> Bool) -> FilePath -> (Bool, FilePath)
recursiveMatch n isMatch path =
case find isMatch (pathParts path) of
Just matchedSuffix ->
let dir = take (length path - length matchedSuffix) path
in ( True
, dir
++ replicate (n-1) pathSeparator
++ matchedSuffix
)
Nothing ->
(False, path)
didNotMatch :: GlobOptions -> FilePath -> FilePath -> Bool
-> IO (DList FilePath, DList FilePath)
didNotMatch opts path absPath isDir =
if includeUnmatched opts
then fmap ((,) DL.empty) $
if isDir
then if path `elem` [".",".."]
then return DL.empty
else getRecursiveContents absPath
else return$ DL.singleton absPath
else
return (DL.empty, DL.empty)
separate :: Pattern -> [TypedPattern]
separate = go DL.empty . unPattern
where
go gr [] | null (DL.toList gr) = []
go gr [] = [Any (pat gr)]
go gr (PathSeparator:ps) = slash gr Dir ps
go gr ( AnyDirectory:ps) = slash gr AnyDir ps
go gr ( p:ps) = go (gr `DL.snoc` p) ps
pat = Pattern . DL.toList
slash gr f ps = let (n,ps') = first length . span isSlash $ ps
in f (n+1) (pat gr) : go DL.empty ps'
isSlash PathSeparator = True
isSlash _ = False
unseparate :: [TypedPattern] -> Pattern
unseparate = Pattern . foldr f []
where
f (AnyDir n p) ts = u p ++ AnyDirectory : replicate (n-1) PathSeparator ++ ts
f ( Dir n p) ts = u p ++ replicate n PathSeparator ++ ts
f (Any p) ts = u p ++ ts
u = unPattern
driveSplit :: Pattern -> (Pattern, Maybe FilePath)
driveSplit = check . split . unPattern
where
split (LongLiteral _ l : xs) = first (l++) (split xs)
split ( Literal l : xs) = first (l:) (split xs)
split (PathSeparator : xs) = first (pathSeparator:) (split xs)
split xs = ([],xs)
check (d,ps)
| null d = (Pattern ps, Nothing)
| not (null drive) = (dirify rest ps, Just drive)
| isPathSeparator (head rest) = (Pattern ps, Just "")
| otherwise = (dirify d ps, Nothing)
where
(drive, rest) = splitDrive d
dirify path = Pattern . (comp path++)
comp s = let (p,l) = foldr f ([],[]) s in if null l then p else ll l p
where
f c (p,l) | isExtSeparator c = (Literal '.' : ll l p, [])
| isPathSeparator c = (PathSeparator : ll l p, [])
| otherwise = (p, c:l)
ll l p = if null l then p else LongLiteral (length l) l : p
commonDirectory :: Pattern -> (FilePath, Pattern)
commonDirectory = second unseparate . splitP . separate
where
splitP pt@(Dir n p:ps) =
case fromConst DL.empty (unPattern p) of
Just d -> first ((d ++ replicate n pathSeparator) </>) (splitP ps)
Nothing -> ("", pt)
splitP pt = ("", pt)
fromConst d [] = Just (DL.toList d)
fromConst d (Literal c :xs) = fromConst (d `DL.snoc` c) xs
fromConst d (LongLiteral _ s:xs) = fromConst (d `DL.append`DL.fromList s) xs
fromConst _ _ = Nothing