module System.FilePath.Find (
FileInfo(..)
, FileType(..)
, FindClause
, FilterPredicate
, RecursionPredicate
, find
, fold
, findWithHandler
, foldWithHandler
, evalClause
, statusType
, liftOp
, filePath
, fileStatus
, depth
, fileInfo
, always
, extension
, directory
, fileName
, fileType
, contains
, deviceID
, fileID
, fileOwner
, fileGroup
, fileSize
, linkCount
, specialDeviceID
, fileMode
, accessTime
, modificationTime
, statusChangeTime
, filePerms
, anyPerms
, canonicalPath
, canonicalName
, readLink
, followStatus
, (~~?)
, (/~?)
, (==?)
, (/=?)
, (>?)
, (<?)
, (>=?)
, (<=?)
, (.&.?)
, (&&?)
, (||?)
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative (Applicative)
#endif
import qualified Control.Exception as E
import Control.Exception (IOException, handle)
import Control.Monad (foldM, forM, liftM, liftM2)
import Control.Monad.State (State, evalState, get)
import Data.Bits (Bits, (.&.))
import Data.List (sort)
import System.Directory (getDirectoryContents, canonicalizePath)
import System.FilePath ((</>), takeDirectory, takeExtension, takeFileName)
import System.FilePath.GlobPattern (GlobPattern, (~~), (/~))
import System.IO (hPutStrLn, stderr)
import System.IO.Unsafe (unsafeInterleaveIO, unsafePerformIO)
import qualified System.PosixCompat.Files as F
import qualified System.PosixCompat.Types as T
data FileInfo = FileInfo
{
infoPath :: FilePath
, infoDepth :: Int
, infoStatus :: F.FileStatus
} deriving (Eq)
instance Eq F.FileStatus where
a == b = F.deviceID a == F.deviceID b &&
F.fileID a == F.fileID b
mkFI :: FilePath -> Int -> F.FileStatus -> FileInfo
mkFI = FileInfo
newtype FindClause a = FC { runFC :: State FileInfo a }
deriving (Functor, Applicative, Monad)
evalClause :: FindClause a -> FileInfo -> a
evalClause = evalState . runFC
evalFI :: FindClause a
-> FilePath
-> Int
-> F.FileStatus
-> a
evalFI m p d s = evalClause m (mkFI p d s)
fileInfo :: FindClause FileInfo
fileInfo = FC $ get
filePath :: FindClause FilePath
filePath = infoPath `liftM` fileInfo
depth :: FindClause Int
depth = infoDepth `liftM` fileInfo
fileStatus :: FindClause F.FileStatus
fileStatus = infoStatus `liftM` fileInfo
type FilterPredicate = FindClause Bool
type RecursionPredicate = FindClause Bool
getDirContents :: FilePath -> IO [FilePath]
getDirContents dir = (sort . filter goodName) `liftM` getDirectoryContents dir
where goodName "." = False
goodName ".." = False
goodName _ = True
findWithHandler ::
(FilePath -> IOException -> IO [FilePath])
-> RecursionPredicate
-> FilterPredicate
-> FilePath
-> IO [FilePath]
findWithHandler errHandler recurse filt path0 =
handle (errHandler path0) $ F.getSymbolicLinkStatus path0 >>= visit path0 0
where visit path depth st =
if F.isDirectory st && evalFI recurse path depth st
then unsafeInterleaveIO (traverse path (succ depth) st)
else filterPath path depth st []
traverse dir depth dirSt = do
names <- E.catch (getDirContents dir) (errHandler dir)
filteredPaths <- forM names $ \name -> do
let path = dir </> name
unsafeInterleaveIO $ handle (errHandler path)
(F.getSymbolicLinkStatus path >>= visit path depth)
filterPath dir depth dirSt (concat filteredPaths)
filterPath path depth st result =
return $ if evalFI filt path depth st
then path:result
else result
find :: RecursionPredicate
-> FilterPredicate
-> FilePath
-> IO [FilePath]
find = findWithHandler warnOnError
where warnOnError path err =
hPutStrLn stderr (path ++ ": " ++ show err) >> return []
foldWithHandler
:: (FilePath -> a -> IOException -> IO a)
-> RecursionPredicate
-> (a -> FileInfo -> a)
-> a
-> FilePath
-> IO a
foldWithHandler errHandler recurse f state path =
handle (errHandler path state) $
F.getSymbolicLinkStatus path >>= visit state path 0
where visit state path depth st =
if F.isDirectory st && evalFI recurse path depth st
then traverse state path (succ depth) st
else let state' = f state (mkFI path depth st)
in state' `seq` return state'
traverse state dir depth dirSt = handle (errHandler dir state) $
getDirContents dir >>=
let state' = f state (mkFI dir depth dirSt)
in state' `seq` flip foldM state' (\state name ->
handle (errHandler dir state) $
let path = dir </> name
in F.getSymbolicLinkStatus path >>= visit state path depth)
fold :: RecursionPredicate
-> (a -> FileInfo -> a)
-> a
-> FilePath
-> IO a
fold = foldWithHandler warnOnError
where warnOnError path a err =
hPutStrLn stderr (path ++ ": " ++ show err) >> return a
always :: FindClause Bool
always = return True
extension :: FindClause FilePath
extension = takeExtension `liftM` filePath
fileName :: FindClause FilePath
fileName = takeFileName `liftM` filePath
directory :: FindClause FilePath
directory = takeDirectory `liftM` filePath
canonicalPath :: FindClause FilePath
canonicalPath = (unsafePerformIO . canonicalizePath) `liftM` filePath
canonicalName :: FindClause FilePath
canonicalName = takeFileName `liftM` canonicalPath
withLink :: (FilePath -> IO a) -> FindClause (Maybe a)
withLink f = do
path <- filePath
st <- fileStatus
return $ if F.isSymbolicLink st
then unsafePerformIO $ handle (\(_::IOException) -> return Nothing) $
Just `liftM` f path
else Nothing
readLink :: FindClause (Maybe FilePath)
readLink = withLink F.readSymbolicLink
followStatus :: FindClause (Maybe F.FileStatus)
followStatus = withLink F.getFileStatus
data FileType = BlockDevice
| CharacterDevice
| NamedPipe
| RegularFile
| Directory
| SymbolicLink
| Socket
| Unknown
deriving (Eq, Ord, Show)
fileType :: FindClause FileType
fileType = statusType `liftM` fileStatus
statusType :: F.FileStatus -> FileType
statusType st | F.isBlockDevice st = BlockDevice
statusType st | F.isCharacterDevice st = CharacterDevice
statusType st | F.isNamedPipe st = NamedPipe
statusType st | F.isRegularFile st = RegularFile
statusType st | F.isDirectory st = Directory
statusType st | F.isSymbolicLink st = SymbolicLink
statusType st | F.isSocket st = Socket
statusType _ = Unknown
deviceID :: FindClause T.DeviceID
deviceID = F.deviceID `liftM` fileStatus
fileID :: FindClause T.FileID
fileID = F.fileID `liftM` fileStatus
fileOwner :: FindClause T.UserID
fileOwner = F.fileOwner `liftM` fileStatus
fileGroup :: FindClause T.GroupID
fileGroup = F.fileGroup `liftM` fileStatus
fileSize :: FindClause T.FileOffset
fileSize = F.fileSize `liftM` fileStatus
linkCount :: FindClause T.LinkCount
linkCount = F.linkCount `liftM` fileStatus
specialDeviceID :: FindClause T.DeviceID
specialDeviceID = F.specialDeviceID `liftM` fileStatus
fileMode :: FindClause T.FileMode
fileMode = F.fileMode `liftM` fileStatus
filePerms :: FindClause T.FileMode
filePerms = (.&. 0777) `liftM` fileMode
anyPerms :: T.FileMode
-> FindClause Bool
anyPerms m = filePerms >>= \p -> return (p .&. m /= 0)
accessTime :: FindClause T.EpochTime
accessTime = F.accessTime `liftM` fileStatus
modificationTime :: FindClause T.EpochTime
modificationTime = F.modificationTime `liftM` fileStatus
statusChangeTime :: FindClause T.EpochTime
statusChangeTime = F.statusChangeTime `liftM` fileStatus
contains :: FilePath -> FindClause Bool
contains p = do
d <- filePath
return $ unsafePerformIO $
handle (\(_::IOException) -> return False) $
F.getFileStatus (d </> p) >> return True
liftOp :: Monad m => (a -> b -> c) -> m a -> b -> m c
liftOp f a b = a >>= \a' -> return (f a' b)
(~~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
(~~?) = liftOp (~~)
infix 4 ~~?
(/~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
(/~?) = liftOp (/~)
infix 4 /~?
(==?) :: Eq a => FindClause a -> a -> FindClause Bool
(==?) = liftOp (==)
infix 4 ==?
(/=?) :: Eq a => FindClause a -> a -> FindClause Bool
(/=?) = liftOp (/=)
infix 4 /=?
(>?) :: Ord a => FindClause a -> a -> FindClause Bool
(>?) = liftOp (>)
infix 4 >?
(<?) :: Ord a => FindClause a -> a -> FindClause Bool
(<?) = liftOp (<)
infix 4 <?
(>=?) :: Ord a => FindClause a -> a -> FindClause Bool
(>=?) = liftOp (>=)
infix 4 >=?
(<=?) :: Ord a => FindClause a -> a -> FindClause Bool
(<=?) = liftOp (<=)
infix 4 <=?
(.&.?) :: Bits a => FindClause a -> a -> FindClause a
(.&.?) = liftOp (.&.)
infixl 7 .&.?
(&&?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
(&&?) = liftM2 (&&)
infixr 3 &&?
(||?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
(||?) = liftM2 (||)
infixr 2 ||?