module System.Path.Glob (glob, vGlob)
where
import Data.List.Utils (hasAny)
import System.IO.HVFS
import System.FilePath (splitFileName, (</>), pathSeparator, isPathSeparator)
import Control.Exception (tryJust)
import System.Path.WildMatch (wildCheckCase)
import Data.List (isSuffixOf)
hasWild :: String -> Bool
hasWild = hasAny "*?["
glob :: FilePath -> IO [FilePath]
glob = vGlob SystemFS
vGlob :: HVFS a => a -> FilePath -> IO [FilePath]
vGlob fs fn =
if not (hasWild fn)
then do de <- vDoesExist fs fn
if de
then return [fn]
else return []
else expandGlob fs fn
expandGlob :: HVFS a => a -> FilePath -> IO [FilePath]
expandGlob fs fn
| dirnameslash == '.':pathSeparator:[] = runGlob fs "." basename
| dirnameslash == [pathSeparator] = do
rgs <- runGlob fs [pathSeparator] basename
return $ map (pathSeparator :) rgs
| otherwise = do dirlist <- if hasWild dirname
then expandGlob fs dirname
else return [dirname]
if hasWild basename
then concat `fmap` mapM expandWildBase dirlist
else concat `fmap` mapM expandNormalBase dirlist
where (dirnameslash, basename) = splitFileName fn
dirname = if dirnameslash == [pathSeparator]
then [pathSeparator]
else if isSuffixOf [pathSeparator] dirnameslash
then init dirnameslash
else dirnameslash
expandWildBase :: FilePath -> IO [FilePath]
expandWildBase dname =
do dirglobs <- runGlob fs dname basename
return $ map withD dirglobs
where withD = case dname of
"" -> id
_ -> \globfn -> dname ++ [pathSeparator] ++ globfn
expandNormalBase :: FilePath -> IO [FilePath]
expandNormalBase dname =
do isdir <- vDoesDirectoryExist fs dname
let newname = dname </> basename
isexists <- vDoesExist fs newname
if isexists && ((basename /= "." && basename /= "") || isdir)
then return [dname </> basename]
else return []
runGlob :: HVFS a => a -> FilePath -> FilePath -> IO [FilePath]
runGlob fs "" patt = runGlob fs "." patt
runGlob fs dirname patt =
do r <- tryJust ioErrors (vGetDirectoryContents fs dirname)
case r of
Left _ -> return []
Right names -> let matches = filter (wildCheckCase patt) $ names
in if head patt == '.'
then return matches
else return $ filter (\x -> head x /= '.') matches
where ioErrors :: IOError -> Maybe IOError
ioErrors e = Just e