{-# LANGUAGE OverloadedStrings #-}
-- | File finding utiliites for Shelly
-- The basic 'find' takes a dir and gives back a list of files.
-- If you don't just want a list, use the folding variants like 'findFold'.
-- If you want to avoid traversing certain directories, use the directory filtering variants like 'findDirFilter'
module Shelly.Find
 (
   find, findWhen, findFold, findDirFilter, findDirFilterWhen, findFoldDirFilter
 ) where

import Prelude hiding (FilePath)
import Shelly.Base
import Control.Monad (foldM)
import Data.Monoid (mappend)
import System.PosixCompat.Files( getSymbolicLinkStatus, isSymbolicLink )
import Filesystem (isDirectory)
import Filesystem.Path.CurrentOS (encodeString)

-- | List directory recursively (like the POSIX utility "find").
-- listing is relative if the path given is relative.
-- If you want to filter out some results or fold over them you can do that with the returned files.
-- A more efficient approach is to use one of the other find functions.
find :: FilePath -> Sh [FilePath]
find :: FilePath -> Sh [FilePath]
find = ([FilePath] -> FilePath -> Sh [FilePath])
-> [FilePath] -> FilePath -> Sh [FilePath]
forall a. (a -> FilePath -> Sh a) -> a -> FilePath -> Sh a
findFold (\[FilePath]
paths FilePath
fp -> [FilePath] -> Sh [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> Sh [FilePath]) -> [FilePath] -> Sh [FilePath]
forall a b. (a -> b) -> a -> b
$ [FilePath]
paths [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
fp]) []

-- | 'find' that filters the found files as it finds.
-- Files must satisfy the given filter to be returned in the result.
findWhen :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findWhen :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findWhen = (FilePath -> Sh Bool)
-> (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findDirFilterWhen (Sh Bool -> FilePath -> Sh Bool
forall a b. a -> b -> a
const (Sh Bool -> FilePath -> Sh Bool) -> Sh Bool -> FilePath -> Sh Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Sh Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True)

-- | Fold an arbitrary folding function over files froma a 'find'.
-- Like 'findWhen' but use a more general fold rather than a filter.
findFold :: (a -> FilePath -> Sh a) -> a -> FilePath -> Sh a
findFold :: forall a. (a -> FilePath -> Sh a) -> a -> FilePath -> Sh a
findFold a -> FilePath -> Sh a
folder a
startValue = (a -> FilePath -> Sh a)
-> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
forall a.
(a -> FilePath -> Sh a)
-> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
findFoldDirFilter a -> FilePath -> Sh a
folder a
startValue (Sh Bool -> FilePath -> Sh Bool
forall a b. a -> b -> a
const (Sh Bool -> FilePath -> Sh Bool) -> Sh Bool -> FilePath -> Sh Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Sh Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True)

-- | 'find' that filters out directories as it finds
-- Filtering out directories can make a find much more efficient by avoiding entire trees of files.
findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findDirFilter FilePath -> Sh Bool
filt = (FilePath -> Sh Bool)
-> (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findDirFilterWhen FilePath -> Sh Bool
filt (Sh Bool -> FilePath -> Sh Bool
forall a b. a -> b -> a
const (Sh Bool -> FilePath -> Sh Bool) -> Sh Bool -> FilePath -> Sh Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Sh Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True)

-- | similar 'findWhen', but also filter out directories
-- Alternatively, similar to 'findDirFilter', but also filter out files
-- Filtering out directories makes the find much more efficient
findDirFilterWhen :: (FilePath -> Sh Bool) -- ^ directory filter
                  -> (FilePath -> Sh Bool) -- ^ file filter
                  -> FilePath -- ^ directory
                  -> Sh [FilePath]
findDirFilterWhen :: (FilePath -> Sh Bool)
-> (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
findDirFilterWhen FilePath -> Sh Bool
dirFilt FilePath -> Sh Bool
fileFilter = ([FilePath] -> FilePath -> Sh [FilePath])
-> [FilePath] -> (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
forall a.
(a -> FilePath -> Sh a)
-> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
findFoldDirFilter [FilePath] -> FilePath -> Sh [FilePath]
filterIt [] FilePath -> Sh Bool
dirFilt
  where
    filterIt :: [FilePath] -> FilePath -> Sh [FilePath]
filterIt [FilePath]
paths FilePath
fp = do
      Bool
yes <- FilePath -> Sh Bool
fileFilter FilePath
fp
      [FilePath] -> Sh [FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath] -> Sh [FilePath]) -> [FilePath] -> Sh [FilePath]
forall a b. (a -> b) -> a -> b
$ if Bool
yes then [FilePath]
paths [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ [FilePath
fp] else [FilePath]
paths

-- | like 'findDirFilterWhen' but use a folding function rather than a filter
-- The most general finder: you likely want a more specific one
findFoldDirFilter :: (a -> FilePath -> Sh a) -> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
findFoldDirFilter :: forall a.
(a -> FilePath -> Sh a)
-> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
findFoldDirFilter a -> FilePath -> Sh a
folder a
startValue FilePath -> Sh Bool
dirFilter FilePath
dir = do
  FilePath
absDir <- FilePath -> Sh FilePath
absPath FilePath
dir
  Text -> Sh ()
trace (Text
"find " Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend` FilePath -> Text
toTextIgnore FilePath
absDir)
  Bool
filt <- FilePath -> Sh Bool
dirFilter FilePath
absDir
  if Bool -> Bool
not Bool
filt then a -> Sh a
forall (m :: * -> *) a. Monad m => a -> m a
return a
startValue
    -- use possible relative path, not absolute so that listing will remain relative
    else do
      ([FilePath]
rPaths, [FilePath]
aPaths) <- FilePath -> Sh ([FilePath], [FilePath])
lsRelAbs FilePath
dir 
      (a -> (FilePath, FilePath) -> Sh a)
-> a -> [(FilePath, FilePath)] -> Sh a
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM a -> (FilePath, FilePath) -> Sh a
traverse a
startValue ([FilePath] -> [FilePath] -> [(FilePath, FilePath)]
forall a b. [a] -> [b] -> [(a, b)]
zip [FilePath]
rPaths [FilePath]
aPaths)
  where
    traverse :: a -> (FilePath, FilePath) -> Sh a
traverse a
acc (FilePath
relativePath, FilePath
absolutePath) = do
      -- optimization: don't use Shelly API since our path is already good
      Bool
isDir <- IO Bool -> Sh Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Sh Bool) -> IO Bool -> Sh Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
isDirectory FilePath
absolutePath
      Bool
sym   <- IO Bool -> Sh Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Sh Bool) -> IO Bool -> Sh Bool
forall a b. (a -> b) -> a -> b
$ (FileStatus -> Bool) -> IO FileStatus -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FileStatus -> Bool
isSymbolicLink (IO FileStatus -> IO Bool) -> IO FileStatus -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FileStatus
getSymbolicLinkStatus (FilePath -> FilePath
encodeString FilePath
absolutePath)
      a
newAcc <- a -> FilePath -> Sh a
folder a
acc FilePath
relativePath
      Bool
follow <- (State -> Bool) -> Sh State -> Sh Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap State -> Bool
sFollowSymlink Sh State
get
      if Bool
isDir Bool -> Bool -> Bool
&& (Bool
follow Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
sym)
        then (a -> FilePath -> Sh a)
-> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
forall a.
(a -> FilePath -> Sh a)
-> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
findFoldDirFilter a -> FilePath -> Sh a
folder a
newAcc 
                FilePath -> Sh Bool
dirFilter FilePath
relativePath
        else a -> Sh a
forall (m :: * -> *) a. Monad m => a -> m a
return a
newAcc