{-# LANGUAGE GeneralizedNewtypeDeriving #-} -- from happstack-util/src/Happstack/Util/FileManip.hs, -- which was derived from FileManip package, which only works on unix. -- happstack port works on windows as well. -- repackage here as standalone to remove dependency on happstack, for immediate use with HStringTemplateHelpers. module System.FilePath.FindCompat where import qualified System.PosixCompat.Files as F import Control.Monad.State import qualified Control.Exception.Extensible as E import System.IO import Data.List (sort) import System.Directory (getDirectoryContents) import System.IO.Unsafe (unsafeInterleaveIO) import System.FilePath (()) import Data.Bits (Bits, (.&.)) -- | Information collected during the traversal of a directory. data FileInfo = FileInfo { infoPath :: FilePath -- ^ file path , infoDepth :: Int -- ^ current recursion depth , infoStatus :: F.FileStatus -- ^ status of file } deriving (Eq) instance Eq F.FileStatus where a == b = F.deviceID a == F.deviceID b && F.fileID a == F.fileID b data FileType = BlockDevice | CharacterDevice | NamedPipe | RegularFile | Directory | SymbolicLink | Socket | Unknown deriving (Eq, Ord, Show) -- | Return the type of file currently being visited. -- -- Example: -- -- @ -- 'fileType' '==?' 'RegularFile' -- @ fileType :: FindClause FileType fileType = statusType `liftM` fileStatus -- | Return the type of a file. This is much more useful for case -- analysis than the usual functions on 'F.FileStatus' values. 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 -- | Construct a 'FileInfo' value. mkFI :: FilePath -> Int -> F.FileStatus -> FileInfo mkFI = FileInfo -- | Monadic container for file information, allowing for clean -- construction of combinators. Wraps the 'State' monad, but doesn't -- allow 'get' or 'put'. newtype FindClause a = FC { runFC :: State FileInfo a } deriving (Functor, Monad) -- | Run the given 'FindClause' on the given 'FileInfo' and return its -- result. This can be useful if you are writing a function to pass -- to 'fold'. -- -- Example: -- -- @ -- myFoldFunc :: a -> 'FileInfo' -> a -- myFoldFunc a i = let useThisFile = 'evalClause' ('fileName' '==?' \"foo\") i -- in if useThisFile -- then fiddleWith a -- else a -- @ 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) mkFindClause :: (FileInfo -> (a, FileInfo)) -> FindClause a mkFindClause = FC . State -- | Return the current 'FileInfo'. fileInfo :: FindClause FileInfo fileInfo = mkFindClause $ \st -> (st, st) -- | Return the 'F.FileStatus' for the current file. fileStatus :: FindClause F.FileStatus fileStatus = infoStatus `liftM` fileInfo type FilterPredicate = FindClause Bool type RecursionPredicate = FindClause Bool -- | List the files in the given directory, sorted, and without \".\" -- or \"..\". getDirContents :: FilePath -> IO [FilePath] getDirContents dir = (sort . filter goodName) `liftM` getDirectoryContents dir where goodName "." = False goodName ".." = False goodName _ = True -- | Search a directory recursively, with recursion controlled by a -- 'RecursionPredicate'. Lazily return a sorted list of all files -- matching the given 'FilterPredicate'. Any errors that occur are -- dealt with by the given handler. findWithHandler :: (FilePath -> E.SomeException -> IO [FilePath]) -- ^ error handler -> RecursionPredicate -- ^ control recursion into subdirectories -> FilterPredicate -- ^ decide whether a file appears in the result -> FilePath -- ^ directory to start searching -> IO [FilePath] -- ^ files that matched the 'FilterPredicate' findWithHandler errHandler recurse filt path = E.handle (errHandler path) $ F.getSymbolicLinkStatus path >>= visit path 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 $ E.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 -- | Search a directory recursively, with recursion controlled by a -- 'RecursionPredicate'. Lazily return a sorted list of all files -- matching the given 'FilterPredicate'. Any errors that occur are -- ignored, with warnings printed to 'stderr'. find :: RecursionPredicate -- ^ control recursion into subdirectories -> FilterPredicate -- ^ decide whether a file appears in the result -> FilePath -- ^ directory to start searching -> IO [FilePath] -- ^ files that matched the 'FilterPredicate' find = findWithHandler warnOnError where warnOnError path err = hPutStrLn stderr (path ++ ": " ++ show err) >> return [] -- | Unconditionally return 'True'. always :: FindClause Bool always = return True -- | Return the name of the file being visited. filePath :: FindClause FilePath filePath = infoPath `liftM` fileInfo -- | Lift a binary operator into the 'FindClause' monad, so that it -- becomes a combinator. The left hand side of the combinator should -- be a @'FindClause' a@, while the right remains a normal value of -- type @a@. liftOp :: Monad m => (a -> b -> c) -> m a -> b -> m c liftOp f a b = a >>= \a' -> return (f a' b) -- $binaryOperators -- -- These are lifted versions of the most commonly used binary -- operators. They have the same fixities and associativities as -- their unlifted counterparts. They are lifted using 'liftOp', like -- so: -- -- @('==?') = 'liftOp' (==)@ (==?) :: 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 >? ( FindClause a -> a -> FindClause Bool (=?) :: Ord a => FindClause a -> a -> FindClause Bool (>=?) = liftOp (>=) infix 4 >=? (<=?) :: Ord a => FindClause a -> a -> FindClause Bool (<=?) = liftOp (<=) infix 4 <=? -- | This operator is useful to check if bits are set in a -- 'T.FileMode'. (.&.?) :: 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 ||?