Skip to content

Commit

Permalink
Refactor "reader"
Browse files Browse the repository at this point in the history
  • Loading branch information
harendra-kumar committed Jul 14, 2023
1 parent 62d20c0 commit e6640a9
Showing 1 changed file with 42 additions and 40 deletions.
82 changes: 42 additions & 40 deletions core/src/Streamly/Internal/FileSystem/Dir.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,9 +92,11 @@ import Streamly.Internal.Data.Unfold (Step(..))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
import System.FilePath ((</>))
#if (defined linux_HOST_OS) || (defined darwin_HOST_OS)
import System.Posix (openDirStream, readDirStream, closeDirStream)
import System.Posix (DirStream, openDirStream, readDirStream, closeDirStream)
#elif defined(mingw32_HOST_OS)
import qualified System.Win32 as Win32
#else
#error "Unsupported architecture"
#endif
import qualified Streamly.Data.Unfold as UF
import qualified Streamly.Internal.Data.Unfold as UF (mapM2, bracketIO)
Expand Down Expand Up @@ -237,57 +239,57 @@ toStreamWithBufferOf chunkSize h = AS.concat $ toChunksWithBufferOf chunkSize h

-- XXX exception handling

-- | Read a directory emitting a stream with names of the children. Filter out
-- "." and ".." entries.
--
-- /Internal/
--
{-# INLINE reader #-}
reader :: (MonadIO m, MonadCatch m) => Unfold m FilePath FilePath
reader =
#if (defined linux_HOST_OS) || (defined darwin_HOST_OS)
UF.bracketIO openDirStream closeDirStream childOf
& UF.filter (\x -> x /= "." && x /= "..")
{-# INLINE streamReader #-}
streamReader :: MonadIO m => Unfold m DirStream FilePath
streamReader = Unfold step return

where

{-# INLINABLE childOf #-}
childOf = Unfold step inject

where
step strm = do
-- XXX Use readDirStreamMaybe
file <- liftIO $ readDirStream strm
case file of
[] -> return Stop
_ -> return $ Yield file strm

inject = return

step strm = do
file <- liftIO $ readDirStream strm
case file of
[] -> return Stop
_ -> return $ Yield file strm
#elif defined(mingw32_HOST_OS)
UF.bracketIO
Win32.findFirstFile
(\(h, _) -> liftIO $ Win32.findClose h)
childOf
& UF.filter (\x -> x /= "." && x /= "..")
openDirStream :: String -> IO (HANDLE, FindData)
openDirStream = Win32.findFirstFile

where
closeDirStream :: (HANDLE, FindData) -> IO ()
closeDirStream (h, _) = Win32.findClose h

{-# INLINABLE childOf #-}
childOf = Unfold step inject
{-# INLINE streamReader #-}
streamReader :: MonadIO m => Unfold m (Handle, FindData) FilePath
streamReader = Unfold step return

where

inject = return
where

step (h, fdat) = do
more <- liftIO $ Win32.findNextFile h fdat
if more
then do
file <- liftIO $ Win32.getFindDataFileName fdat
return $ Yield file (h, fdat)
else return Stop
step (h, fdat) = do
more <- liftIO $ Win32.findNextFile h fdat
if more
then do
file <- liftIO $ Win32.getFindDataFileName fdat
return $ Yield file (h, fdat)
else return Stop
#endif

-- | Read a directory emitting a stream with names of the children. Filter out
-- "." and ".." entries.
--
-- /Internal/
--
{-# INLINE reader #-}
reader :: (MonadIO m, MonadCatch m) => Unfold m FilePath FilePath
reader =
-- XXX Instead of using bracketIO for each iteration of the loop we should
-- instead yield a buffer of dir entries in each iteration and then use an
-- unfold and concat to flatten those entries. That should improve the
-- performance.
UF.bracketIO openDirStream closeDirStream streamReader
& UF.filter (\x -> x /= "." && x /= "..")

-- XXX We can use a more general mechanism to filter the contents of a
-- directory. We can just stat each child and pass on the stat information. We
-- can then use that info to do a general filtering. "find" like filters can be
Expand Down

0 comments on commit e6640a9

Please sign in to comment.