module Data.Conduit.Filesystem
( sourceDirectory
, sourceDirectoryDeep
) where
import Data.Conduit
import Control.Monad.Trans.Resource (MonadResource)
import Control.Monad.IO.Class (liftIO)
import System.FilePath ((</>))
import qualified Data.Streaming.Filesystem as F
sourceDirectory :: MonadResource m => FilePath -> Producer m FilePath
sourceDirectory dir =
bracketP (F.openDirStream dir) F.closeDirStream go
where
go ds =
loop
where
loop = do
mfp <- liftIO $ F.readDirStream ds
case mfp of
Nothing -> return ()
Just fp -> do
yield $ dir </> fp
loop
sourceDirectoryDeep :: MonadResource m
=> Bool
-> FilePath
-> Producer m FilePath
sourceDirectoryDeep followSymlinks =
start
where
start :: MonadResource m => FilePath -> Producer m FilePath
start dir = sourceDirectory dir =$= awaitForever go
go :: MonadResource m => FilePath -> Producer m FilePath
go fp = do
ft <- liftIO $ F.getFileType fp
case ft of
F.FTFile -> yield fp
F.FTFileSym -> yield fp
F.FTDirectory -> start fp
F.FTDirectorySym
| followSymlinks -> start fp
| otherwise -> return ()
F.FTOther -> return ()