Skip to content

Commit

Permalink
Optimize "." and ".." filtering
Browse files Browse the repository at this point in the history
  • Loading branch information
harendra-kumar committed Dec 20, 2023
1 parent 94762b4 commit 594822d
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 16 deletions.
15 changes: 4 additions & 11 deletions core/src/Streamly/Internal/FileSystem/Dir.hs
Original file line number Diff line number Diff line change
Expand Up @@ -335,22 +335,15 @@ reader =
eitherReader :: (MonadIO m, MonadCatch m) =>
Unfold m OsPath (Either OsPath OsPath)
eitherReader =
-- XXX bracketIO is expensive
-- XXX The measured overhead of bracketIO is not noticeable, if it turns
-- out to be a problems for small filenames we can use getdents64 to use
-- chunked read to avoid the overhead.
UF.bracketIO openDirStream closeDirStream streamEitherReader
& UF.filter f

where

dot = OsPath.unsafeFromChar '.'
f p =
case p of
-- XXX This check could be made more efficient
Left x -> x /= OsPath.pack [dot] && x /= OsPath.pack [dot, dot]
Right _ -> True

{-# INLINE eitherReaderPaths #-}
eitherReaderPaths ::(MonadIO m, MonadCatch m) => Unfold m OsPath (Either OsPath OsPath)
eitherReaderPaths =
-- XXX Do not resolve the children again
UF.mapM2 (\dir -> return . bimap (dir </>) (dir </>)) eitherReader

--
Expand Down
25 changes: 20 additions & 5 deletions core/src/Streamly/Internal/FileSystem/ReadDir.hsc
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ module Streamly.Internal.FileSystem.ReadDir
)
where

import Foreign (Ptr, Word8, nullPtr, peekByteOff)
import Data.Char (ord)
import Foreign (Ptr, Word8, nullPtr, peek, peekByteOff)
import Foreign.C (resetErrno, Errno(..), getErrno, eINTR, throwErrno, CString)
import System.OsPath.Posix (PosixPath)
import System.Posix.Directory.Internals (DirStream(..), CDir, CDirent)
Expand Down Expand Up @@ -40,10 +41,24 @@ readDirStreamEither (DirStream dirp) = loop
dname <- d_name ptr
dtype :: #{type unsigned char} <- #{peek struct dirent, d_type} ptr
name <- peekFilePath dname
return $
if (dtype == #const DT_DIR)
then (Left name)
else (Right name)
if (dtype == #const DT_DIR)
then do
-- XXX Assuming UTF8 encoding
c1 <- peek dname
if (c1 /= fromIntegral (ord '.'))
then return (Left name)
else do
c2 :: Word8 <- peekByteOff dname 1
if (c2 == 0)
then loop
else if (c2 /= fromIntegral (ord '.'))
then return (Left name)
else do
c3 :: Word8 <- peekByteOff dname 2
if (c3 == 0)
then loop
else return (Left name)
else return (Right name)
else do
errno <- getErrno
if (errno == eINTR)
Expand Down

0 comments on commit 594822d

Please sign in to comment.