{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-- |
-- Module:      System.FilePath.Find
-- Copyright:   Bryan O'Sullivan
-- License:     BSD3
-- Maintainer:  Bryan O'Sullivan <bos@serpentine.com>
-- Stability:   unstable
-- Portability: Unix-like systems (requires newtype deriving)
--
-- This module provides functions for traversing a filesystem
-- hierarchy.  The 'find' function generates a lazy list of matching
-- files, while 'fold' performs a left fold.
--
-- Both 'find' and 'fold' allow fine control over recursion, using the
-- 'FindClause' type.  This type is also used to pre-filter the results
-- returned by 'find'.
--
-- The 'FindClause' type lets you write filtering and recursion
-- control expressions clearly and easily.
--
-- For example, this clause matches C source files.
--
-- @
-- 'extension' '==?' \".c\" '||?' 'extension' '==?' \".h\"
-- @
--
-- Because 'FindClause' is a monad, you can use the usual monad
-- machinery to, for example, lift pure functions into it.
--
-- Here's a clause that will return 'True' for any file whose
-- directory name contains the word @\"temp\"@.
--
-- @
-- (isInfixOf \"temp\") \`liftM\` 'directory'
-- @

module System.FilePath.Find (
      FileInfo(..)
    , FileType(..)
    , FindClause
    , FilterPredicate
    , RecursionPredicate

    -- * Simple entry points
    , find
    , fold

    -- * More expressive entry points
    , findWithHandler
    , foldWithHandler

    -- * Helper functions
    , evalClause
    , statusType
    , liftOp

    -- * Combinators for controlling recursion and filtering behaviour
    , filePath
    , fileStatus
    , depth
    , fileInfo

    , always
    , extension
    , directory
    , fileName

    , fileType

    , contains

    -- ** Combinator versions of 'F.FileStatus' functions from "System.Posix.Files"
    -- $statusFunctions

    , deviceID
    , fileID
    , fileOwner
    , fileGroup
    , fileSize
    , linkCount
    , specialDeviceID
    , fileMode
    , accessTime
    , modificationTime
    , statusChangeTime

    -- *** Convenience combinators for file status
    , filePerms
    , anyPerms

    -- ** Combinators for canonical path and name
    , canonicalPath
    , canonicalName

    -- ** Combinators that operate on symbolic links
    , readLink
    , followStatus

    -- ** Common binary operators, lifted as combinators
    -- $binaryOperators
    , (~~?)
    , (/~?)
    , (==?)
    , (/=?)
    , (>?)
    , (<?)
    , (>=?)
    , (<=?)
    , (.&.?)

    -- ** Combinators for gluing clauses together
    , (&&?)
    , (||?)
    ) 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

-- | Information collected during the traversal of a directory.
data FileInfo = FileInfo
    {
      FileInfo -> FilePath
infoPath :: FilePath -- ^ file path
    , FileInfo -> Int
infoDepth :: Int -- ^ current recursion depth
    , FileInfo -> FileStatus
infoStatus :: F.FileStatus -- ^ status of file
    } deriving (FileInfo -> FileInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileInfo -> FileInfo -> Bool
$c/= :: FileInfo -> FileInfo -> Bool
== :: FileInfo -> FileInfo -> Bool
$c== :: FileInfo -> FileInfo -> Bool
Eq)

instance Eq F.FileStatus where
    FileStatus
a == :: FileStatus -> FileStatus -> Bool
== FileStatus
b = FileStatus -> DeviceID
F.deviceID FileStatus
a forall a. Eq a => a -> a -> Bool
== FileStatus -> DeviceID
F.deviceID FileStatus
b Bool -> Bool -> Bool
&&
             FileStatus -> FileID
F.fileID FileStatus
a forall a. Eq a => a -> a -> Bool
== FileStatus -> FileID
F.fileID FileStatus
b

-- | Construct a 'FileInfo' value.

mkFI :: FilePath -> Int -> F.FileStatus -> FileInfo

mkFI :: FilePath -> Int -> FileStatus -> FileInfo
mkFI = FilePath -> Int -> FileStatus -> FileInfo
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 { forall a. FindClause a -> State FileInfo a
runFC :: State FileInfo a }
    deriving (forall a b. a -> FindClause b -> FindClause a
forall a b. (a -> b) -> FindClause a -> FindClause b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> FindClause b -> FindClause a
$c<$ :: forall a b. a -> FindClause b -> FindClause a
fmap :: forall a b. (a -> b) -> FindClause a -> FindClause b
$cfmap :: forall a b. (a -> b) -> FindClause a -> FindClause b
Functor, Functor FindClause
forall a. a -> FindClause a
forall a b. FindClause a -> FindClause b -> FindClause a
forall a b. FindClause a -> FindClause b -> FindClause b
forall a b. FindClause (a -> b) -> FindClause a -> FindClause b
forall a b c.
(a -> b -> c) -> FindClause a -> FindClause b -> FindClause c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. FindClause a -> FindClause b -> FindClause a
$c<* :: forall a b. FindClause a -> FindClause b -> FindClause a
*> :: forall a b. FindClause a -> FindClause b -> FindClause b
$c*> :: forall a b. FindClause a -> FindClause b -> FindClause b
liftA2 :: forall a b c.
(a -> b -> c) -> FindClause a -> FindClause b -> FindClause c
$cliftA2 :: forall a b c.
(a -> b -> c) -> FindClause a -> FindClause b -> FindClause c
<*> :: forall a b. FindClause (a -> b) -> FindClause a -> FindClause b
$c<*> :: forall a b. FindClause (a -> b) -> FindClause a -> FindClause b
pure :: forall a. a -> FindClause a
$cpure :: forall a. a -> FindClause a
Applicative, Applicative FindClause
forall a. a -> FindClause a
forall a b. FindClause a -> FindClause b -> FindClause b
forall a b. FindClause a -> (a -> FindClause b) -> FindClause b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> FindClause a
$creturn :: forall a. a -> FindClause a
>> :: forall a b. FindClause a -> FindClause b -> FindClause b
$c>> :: forall a b. FindClause a -> FindClause b -> FindClause b
>>= :: forall a b. FindClause a -> (a -> FindClause b) -> FindClause b
$c>>= :: forall a b. FindClause a -> (a -> FindClause b) -> FindClause b
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 :: forall a. FindClause a -> FileInfo -> a
evalClause = forall s a. State s a -> s -> a
evalState forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FindClause a -> State FileInfo a
runFC

evalFI :: FindClause a
       -> FilePath
       -> Int
       -> F.FileStatus
       -> a
evalFI :: forall a. FindClause a -> FilePath -> Int -> FileStatus -> a
evalFI FindClause a
m FilePath
p Int
d FileStatus
s = forall a. FindClause a -> FileInfo -> a
evalClause FindClause a
m (FilePath -> Int -> FileStatus -> FileInfo
mkFI FilePath
p Int
d FileStatus
s)

-- | Return the current 'FileInfo'.
fileInfo :: FindClause FileInfo

fileInfo :: FindClause FileInfo
fileInfo = forall a. State FileInfo a -> FindClause a
FC forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *). MonadState s m => m s
get

-- | Return the name of the file being visited.
filePath :: FindClause FilePath

filePath :: FindClause FilePath
filePath = FileInfo -> FilePath
infoPath forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileInfo
fileInfo

-- | Return the current recursion depth.
depth :: FindClause Int

depth :: FindClause Int
depth = FileInfo -> Int
infoDepth forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileInfo
fileInfo

-- | Return the 'F.FileStatus' for the current file.
fileStatus :: FindClause F.FileStatus

fileStatus :: FindClause FileStatus
fileStatus = FileInfo -> FileStatus
infoStatus forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileInfo
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 :: FilePath -> IO [FilePath]
getDirContents FilePath
dir = (forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
goodName) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FilePath -> IO [FilePath]
getDirectoryContents FilePath
dir
    where goodName :: FilePath -> Bool
goodName FilePath
"." = Bool
False
          goodName FilePath
".." = Bool
False
          goodName FilePath
_ = Bool
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 -> IOException -> 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 :: (FilePath -> IOException -> IO [FilePath])
-> RecursionPredicate
-> RecursionPredicate
-> FilePath
-> IO [FilePath]
findWithHandler FilePath -> IOException -> IO [FilePath]
errHandler RecursionPredicate
recurse RecursionPredicate
filt FilePath
path0 =
    forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (FilePath -> IOException -> IO [FilePath]
errHandler FilePath
path0) forall a b. (a -> b) -> a -> b
$ FilePath -> IO FileStatus
F.getSymbolicLinkStatus FilePath
path0 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> Int -> FileStatus -> IO [FilePath]
visit FilePath
path0 Int
0
  where visit :: FilePath -> Int -> FileStatus -> IO [FilePath]
visit FilePath
path Int
depth FileStatus
st =
            if FileStatus -> Bool
F.isDirectory FileStatus
st Bool -> Bool -> Bool
&& forall a. FindClause a -> FilePath -> Int -> FileStatus -> a
evalFI RecursionPredicate
recurse FilePath
path Int
depth FileStatus
st
              then forall a. IO a -> IO a
unsafeInterleaveIO (FilePath -> Int -> FileStatus -> IO [FilePath]
traverse FilePath
path (forall a. Enum a => a -> a
succ Int
depth) FileStatus
st)
              else forall {m :: * -> *}.
Monad m =>
FilePath -> Int -> FileStatus -> [FilePath] -> m [FilePath]
filterPath FilePath
path Int
depth FileStatus
st []
        traverse :: FilePath -> Int -> FileStatus -> IO [FilePath]
traverse FilePath
dir Int
depth FileStatus
dirSt = do
            [FilePath]
names <- forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch (FilePath -> IO [FilePath]
getDirContents FilePath
dir) (FilePath -> IOException -> IO [FilePath]
errHandler FilePath
dir)
            [[FilePath]]
filteredPaths <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [FilePath]
names forall a b. (a -> b) -> a -> b
$ \FilePath
name -> do
                let path :: FilePath
path = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
name
                forall a. IO a -> IO a
unsafeInterleaveIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (FilePath -> IOException -> IO [FilePath]
errHandler FilePath
path)
                    (FilePath -> IO FileStatus
F.getSymbolicLinkStatus FilePath
path forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> Int -> FileStatus -> IO [FilePath]
visit FilePath
path Int
depth)
            forall {m :: * -> *}.
Monad m =>
FilePath -> Int -> FileStatus -> [FilePath] -> m [FilePath]
filterPath FilePath
dir Int
depth FileStatus
dirSt (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[FilePath]]
filteredPaths)
        filterPath :: FilePath -> Int -> FileStatus -> [FilePath] -> m [FilePath]
filterPath FilePath
path Int
depth FileStatus
st [FilePath]
result =
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if forall a. FindClause a -> FilePath -> Int -> FileStatus -> a
evalFI RecursionPredicate
filt FilePath
path Int
depth FileStatus
st
                then FilePath
pathforall a. a -> [a] -> [a]
:[FilePath]
result
                else [FilePath]
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 :: RecursionPredicate
-> RecursionPredicate -> FilePath -> IO [FilePath]
find = (FilePath -> IOException -> IO [FilePath])
-> RecursionPredicate
-> RecursionPredicate
-> FilePath
-> IO [FilePath]
findWithHandler forall {a} {a}. Show a => FilePath -> a -> IO [a]
warnOnError
    where warnOnError :: FilePath -> a -> IO [a]
warnOnError FilePath
path a
err =
              Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
": " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
err) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return []

-- | Search a directory recursively, with recursion controlled by a
-- 'RecursionPredicate'.  Fold over all files found.  Any errors that
-- occur are dealt with by the given handler.  The fold is strict, and
-- run from \"left\" to \"right\", so the folded function should be
-- strict in its left argument to avoid space leaks.  If you need a
-- right-to-left fold, use 'foldr' on the result of 'findWithHandler'
-- instead.
foldWithHandler
    :: (FilePath -> a -> IOException -> IO a) -- ^ error handler
    -> RecursionPredicate -- ^ control recursion into subdirectories
    -> (a -> FileInfo -> a) -- ^ function to fold with
    -> a -- ^ seed value for fold
    -> FilePath -- ^ directory to start searching
    -> IO a -- ^ final value after folding

foldWithHandler :: forall a.
(FilePath -> a -> IOException -> IO a)
-> RecursionPredicate
-> (a -> FileInfo -> a)
-> a
-> FilePath
-> IO a
foldWithHandler FilePath -> a -> IOException -> IO a
errHandler RecursionPredicate
recurse a -> FileInfo -> a
f a
state FilePath
path =
    forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (FilePath -> a -> IOException -> IO a
errHandler FilePath
path a
state) forall a b. (a -> b) -> a -> b
$
        FilePath -> IO FileStatus
F.getSymbolicLinkStatus FilePath
path forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> FilePath -> Int -> FileStatus -> IO a
visit a
state FilePath
path Int
0
  where visit :: a -> FilePath -> Int -> FileStatus -> IO a
visit a
state FilePath
path Int
depth FileStatus
st =
            if FileStatus -> Bool
F.isDirectory FileStatus
st Bool -> Bool -> Bool
&& forall a. FindClause a -> FilePath -> Int -> FileStatus -> a
evalFI RecursionPredicate
recurse FilePath
path Int
depth FileStatus
st
            then a -> FilePath -> Int -> FileStatus -> IO a
traverse a
state FilePath
path (forall a. Enum a => a -> a
succ Int
depth) FileStatus
st
            else let state' :: a
state' = a -> FileInfo -> a
f a
state (FilePath -> Int -> FileStatus -> FileInfo
mkFI FilePath
path Int
depth FileStatus
st)
                 in a
state' seq :: forall a b. a -> b -> b
`seq` forall (m :: * -> *) a. Monad m => a -> m a
return a
state'
        traverse :: a -> FilePath -> Int -> FileStatus -> IO a
traverse a
state FilePath
dir Int
depth FileStatus
dirSt = forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (FilePath -> a -> IOException -> IO a
errHandler FilePath
dir a
state) forall a b. (a -> b) -> a -> b
$
            FilePath -> IO [FilePath]
getDirContents FilePath
dir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                let state' :: a
state' = a -> FileInfo -> a
f a
state (FilePath -> Int -> FileStatus -> FileInfo
mkFI FilePath
dir Int
depth FileStatus
dirSt)
                in a
state' seq :: forall a b. a -> b -> b
`seq` forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM a
state' (\a
state FilePath
name ->
                    forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (FilePath -> a -> IOException -> IO a
errHandler FilePath
dir a
state) forall a b. (a -> b) -> a -> b
$
                    let path :: FilePath
path = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
name
                    in FilePath -> IO FileStatus
F.getSymbolicLinkStatus FilePath
path forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> FilePath -> Int -> FileStatus -> IO a
visit a
state FilePath
path Int
depth)

-- | Search a directory recursively, with recursion controlled by a
-- 'RecursionPredicate'.  Fold over all files found.  Any errors that
-- occur are ignored, with warnings printed to 'stderr'.  The fold
-- function is run from \"left\" to \"right\", so it should be strict
-- in its left argument to avoid space leaks.  If you need a
-- right-to-left fold, use 'foldr' on the result of 'findWithHandler'
-- instead.
fold :: RecursionPredicate
     -> (a -> FileInfo -> a)
     -> a
     -> FilePath
     -> IO a

fold :: forall a.
RecursionPredicate -> (a -> FileInfo -> a) -> a -> FilePath -> IO a
fold = forall a.
(FilePath -> a -> IOException -> IO a)
-> RecursionPredicate
-> (a -> FileInfo -> a)
-> a
-> FilePath
-> IO a
foldWithHandler forall {a} {b}. Show a => FilePath -> b -> a -> IO b
warnOnError
    where warnOnError :: FilePath -> b -> a -> IO b
warnOnError FilePath
path b
a a
err =
              Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr (FilePath
path forall a. [a] -> [a] -> [a]
++ FilePath
": " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
err) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return b
a

-- | Unconditionally return 'True'.
always :: FindClause Bool
always :: RecursionPredicate
always = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True

-- | Return the file name extension.
--
-- Example:
--
-- @
-- 'extension' \"foo\/bar.txt\" => \".txt\"
-- @
extension :: FindClause FilePath
extension :: FindClause FilePath
extension = FilePath -> FilePath
takeExtension forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FilePath
filePath

-- | Return the file name, without the directory name.
--
-- What this means in practice:
--
-- @
-- 'fileName' \"foo\/bar.txt\" => \"bar.txt\"
-- @
--
-- Example:
--
-- @
-- 'fileName' '==?' \"init.c\"
-- @
fileName :: FindClause FilePath
fileName :: FindClause FilePath
fileName = FilePath -> FilePath
takeFileName forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FilePath
filePath

-- | Return the directory name, without the file name.
--
-- What this means in practice:
--
-- @
-- 'directory' \"foo\/bar.txt\" => \"foo\"
-- @
--
-- Example in a clause:
--
-- @
-- let hasSuffix = 'liftOp' 'isSuffixOf'
-- in directory \`hasSuffix\` \"tests\"
-- @
directory :: FindClause FilePath
directory :: FindClause FilePath
directory = FilePath -> FilePath
takeDirectory forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FilePath
filePath

-- | Return the canonical path of the file being visited.
--
-- See `canonicalizePath` for details of what canonical path means.
canonicalPath :: FindClause FilePath
canonicalPath :: FindClause FilePath
canonicalPath = (forall a. IO a -> a
unsafePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FilePath
filePath

-- | Return the canonical name of the file (canonical path with the
-- directory part removed).
canonicalName :: FindClause FilePath
canonicalName :: FindClause FilePath
canonicalName = FilePath -> FilePath
takeFileName forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FilePath
canonicalPath

-- | Run the given action in the 'IO' monad (using 'unsafePerformIO')
-- if the current file is a symlink.  Hide errors by wrapping results
-- in the 'Maybe' monad.
withLink :: (FilePath -> IO a) -> FindClause (Maybe a)

withLink :: forall a. (FilePath -> IO a) -> FindClause (Maybe a)
withLink FilePath -> IO a
f = do
    FilePath
path <- FindClause FilePath
filePath
    FileStatus
st <- FindClause FileStatus
fileStatus
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if FileStatus -> Bool
F.isSymbolicLink FileStatus
st
        then forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (\(IOException
_::IOException) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) forall a b. (a -> b) -> a -> b
$
             forall a. a -> Maybe a
Just forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FilePath -> IO a
f FilePath
path
        else forall a. Maybe a
Nothing

-- | If the current file is a symbolic link, return 'Just' the target
-- of the link, otherwise 'Nothing'.
readLink :: FindClause (Maybe FilePath)

readLink :: FindClause (Maybe FilePath)
readLink = forall a. (FilePath -> IO a) -> FindClause (Maybe a)
withLink FilePath -> IO FilePath
F.readSymbolicLink

-- | If the current file is a symbolic link, return 'Just' the status
-- of the ultimate endpoint of the link.  Otherwise (including in the
-- case of an error), return 'Nothing'.
--
-- Example:
--
-- @
-- 'statusType' \`liftM\` 'followStatus' '==?' 'RegularFile'
-- @
followStatus :: FindClause (Maybe F.FileStatus)

followStatus :: FindClause (Maybe FileStatus)
followStatus = forall a. (FilePath -> IO a) -> FindClause (Maybe a)
withLink FilePath -> IO FileStatus
F.getFileStatus

data FileType = BlockDevice
              | CharacterDevice
              | NamedPipe
              | RegularFile
              | Directory
              | SymbolicLink
              | Socket
              | Unknown
                deriving (FileType -> FileType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c== :: FileType -> FileType -> Bool
Eq, Eq FileType
FileType -> FileType -> Bool
FileType -> FileType -> Ordering
FileType -> FileType -> FileType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FileType -> FileType -> FileType
$cmin :: FileType -> FileType -> FileType
max :: FileType -> FileType -> FileType
$cmax :: FileType -> FileType -> FileType
>= :: FileType -> FileType -> Bool
$c>= :: FileType -> FileType -> Bool
> :: FileType -> FileType -> Bool
$c> :: FileType -> FileType -> Bool
<= :: FileType -> FileType -> Bool
$c<= :: FileType -> FileType -> Bool
< :: FileType -> FileType -> Bool
$c< :: FileType -> FileType -> Bool
compare :: FileType -> FileType -> Ordering
$ccompare :: FileType -> FileType -> Ordering
Ord, Int -> FileType -> FilePath -> FilePath
[FileType] -> FilePath -> FilePath
FileType -> FilePath
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [FileType] -> FilePath -> FilePath
$cshowList :: [FileType] -> FilePath -> FilePath
show :: FileType -> FilePath
$cshow :: FileType -> FilePath
showsPrec :: Int -> FileType -> FilePath -> FilePath
$cshowsPrec :: Int -> FileType -> FilePath -> FilePath
Show)

-- | Return the type of file currently being visited.
--
-- Example:
--
-- @
-- 'fileType' '==?' 'RegularFile'
-- @
fileType :: FindClause FileType

fileType :: FindClause FileType
fileType = FileStatus -> FileType
statusType forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
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 :: FileStatus -> FileType
statusType FileStatus
st | FileStatus -> Bool
F.isBlockDevice FileStatus
st = FileType
BlockDevice
statusType FileStatus
st | FileStatus -> Bool
F.isCharacterDevice FileStatus
st = FileType
CharacterDevice
statusType FileStatus
st | FileStatus -> Bool
F.isNamedPipe FileStatus
st = FileType
NamedPipe
statusType FileStatus
st | FileStatus -> Bool
F.isRegularFile FileStatus
st = FileType
RegularFile
statusType FileStatus
st | FileStatus -> Bool
F.isDirectory FileStatus
st = FileType
Directory
statusType FileStatus
st | FileStatus -> Bool
F.isSymbolicLink FileStatus
st = FileType
SymbolicLink
statusType FileStatus
st | FileStatus -> Bool
F.isSocket FileStatus
st = FileType
Socket
statusType FileStatus
_ = FileType
Unknown

-- $statusFunctions
--
-- These are simply lifted versions of the 'F.FileStatus' accessor
-- functions in the "System.Posix.Files" module.  The definitions all
-- have the following form:
--
-- @
-- 'deviceID' :: 'FindClause' "System.Posix.Types".DeviceID
-- 'deviceID' = "System.Posix.Files".deviceID \`liftM\` 'fileStatus'
-- @

deviceID :: FindClause T.DeviceID
deviceID :: FindClause DeviceID
deviceID = FileStatus -> DeviceID
F.deviceID forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

fileID :: FindClause T.FileID
fileID :: FindClause FileID
fileID = FileStatus -> FileID
F.fileID forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

fileOwner :: FindClause T.UserID
fileOwner :: FindClause UserID
fileOwner = FileStatus -> UserID
F.fileOwner forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

fileGroup :: FindClause T.GroupID
fileGroup :: FindClause GroupID
fileGroup = FileStatus -> GroupID
F.fileGroup forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

fileSize :: FindClause T.FileOffset
fileSize :: FindClause FileOffset
fileSize = FileStatus -> FileOffset
F.fileSize forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

linkCount :: FindClause T.LinkCount
linkCount :: FindClause LinkCount
linkCount = FileStatus -> LinkCount
F.linkCount forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

specialDeviceID :: FindClause T.DeviceID
specialDeviceID :: FindClause DeviceID
specialDeviceID = FileStatus -> DeviceID
F.specialDeviceID forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

fileMode :: FindClause T.FileMode
fileMode :: FindClause FileMode
fileMode = FileStatus -> FileMode
F.fileMode forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

-- | Return the permission bits of the 'T.FileMode'.
filePerms :: FindClause T.FileMode
filePerms :: FindClause FileMode
filePerms = (forall a. Bits a => a -> a -> a
.&. FileMode
0777) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileMode
fileMode

-- | Return 'True' if any of the given permission bits is set.
--
-- Example:
--
-- @
-- 'anyPerms' 0444
-- @
anyPerms :: T.FileMode
         -> FindClause Bool
anyPerms :: FileMode -> RecursionPredicate
anyPerms FileMode
m = FindClause FileMode
filePerms forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \FileMode
p -> forall (m :: * -> *) a. Monad m => a -> m a
return (FileMode
p forall a. Bits a => a -> a -> a
.&. FileMode
m forall a. Eq a => a -> a -> Bool
/= FileMode
0)

accessTime :: FindClause T.EpochTime
accessTime :: FindClause EpochTime
accessTime = FileStatus -> EpochTime
F.accessTime forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

modificationTime :: FindClause T.EpochTime
modificationTime :: FindClause EpochTime
modificationTime = FileStatus -> EpochTime
F.modificationTime forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

statusChangeTime :: FindClause T.EpochTime
statusChangeTime :: FindClause EpochTime
statusChangeTime = FileStatus -> EpochTime
F.statusChangeTime forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` FindClause FileStatus
fileStatus

-- | Return 'True' if the given path exists, relative to the current
-- file.  For example, if @\"foo\"@ is being visited, and you call
-- contains @\"bar\"@, this combinator will return 'True' if
-- @\"foo\/bar\"@ exists.
contains :: FilePath -> FindClause Bool
contains :: FilePath -> RecursionPredicate
contains FilePath
p = do
    FilePath
d <- FindClause FilePath
filePath
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$
        forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (\(IOException
_::IOException) -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) forall a b. (a -> b) -> a -> b
$
            FilePath -> IO FileStatus
F.getFileStatus (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
p) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True

-- | 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 :: forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp a -> b -> c
f m a
a b
b = m a
a forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a' -> forall (m :: * -> *) a. Monad m => a -> m a
return (a -> b -> c
f a
a' b
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' (==)@

-- | Return 'True' if the current file's name matches the given
-- 'GlobPattern'.
(~~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
~~? :: FindClause FilePath -> FilePath -> RecursionPredicate
(~~?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp FilePath -> FilePath -> Bool
(~~)
infix 4 ~~?

-- | Return 'True' if the current file's name does not match the given
-- 'GlobPattern'.
(/~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
/~? :: FindClause FilePath -> FilePath -> RecursionPredicate
(/~?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp FilePath -> FilePath -> Bool
(/~)
infix 4 /~?

(==?) :: Eq a => FindClause a -> a -> FindClause Bool
==? :: forall a. Eq a => FindClause a -> a -> RecursionPredicate
(==?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Eq a => a -> a -> Bool
(==)
infix 4 ==?

(/=?) :: Eq a => FindClause a -> a -> FindClause Bool
/=? :: forall a. Eq a => FindClause a -> a -> RecursionPredicate
(/=?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Eq a => a -> a -> Bool
(/=)
infix 4 /=?

(>?) :: Ord a => FindClause a -> a -> FindClause Bool
>? :: forall a. Ord a => FindClause a -> a -> RecursionPredicate
(>?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Ord a => a -> a -> Bool
(>)
infix 4 >?

(<?) :: Ord a => FindClause a -> a -> FindClause Bool
<? :: forall a. Ord a => FindClause a -> a -> RecursionPredicate
(<?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Ord a => a -> a -> Bool
(<)
infix 4 <?

(>=?) :: Ord a => FindClause a -> a -> FindClause Bool
>=? :: forall a. Ord a => FindClause a -> a -> RecursionPredicate
(>=?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Ord a => a -> a -> Bool
(>=)
infix 4 >=?

(<=?) :: Ord a => FindClause a -> a -> FindClause Bool
<=? :: forall a. Ord a => FindClause a -> a -> RecursionPredicate
(<=?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Ord a => a -> a -> Bool
(<=)
infix 4 <=?

-- | This operator is useful to check if bits are set in a
-- 'T.FileMode'.
(.&.?) :: Bits a => FindClause a -> a -> FindClause a
.&.? :: forall a. Bits a => FindClause a -> a -> FindClause a
(.&.?) = forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> m a -> b -> m c
liftOp forall a. Bits a => a -> a -> a
(.&.)
infixl 7 .&.?

(&&?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
&&? :: RecursionPredicate -> RecursionPredicate -> RecursionPredicate
(&&?) = forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Bool -> Bool -> Bool
(&&)
infixr 3 &&?

(||?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
||? :: RecursionPredicate -> RecursionPredicate -> RecursionPredicate
(||?) = forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Bool -> Bool -> Bool
(||)
infixr 2 ||?