Skip to content

Commit 3aedcd0

Browse files
committed
Use ReadOptions and options config in all the Posix APIs
1 parent 61ed777 commit 3aedcd0

File tree

4 files changed

+106
-57
lines changed

4 files changed

+106
-57
lines changed

core/src/Streamly/Internal/FileSystem/Dir.hs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -123,14 +123,20 @@ pMapUnfoldE = fmap ePathMap . Unfold.lmapM Path.fromString
123123
-- Functions
124124
--------------------------------------------------------------------------------
125125

126+
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
127+
#define CONF_AP(x) x
128+
#else
129+
#define CONF_AP(x) (x (DirIO.followSymlinks True))
130+
#endif
131+
126132
-- | Read a directory emitting a stream with names of the children. Filter out
127133
-- "." and ".." entries.
128134
--
129135
-- /Internal/
130136
--
131137
{-# INLINE reader #-}
132138
reader :: (MonadIO m, MonadCatch m) => Unfold m FilePath FilePath
133-
reader = fmap Path.toString $ Unfold.lmapM Path.fromString DirIO.reader
139+
reader = fmap Path.toString $ Unfold.lmapM Path.fromString CONF_AP(DirIO.reader)
134140

135141
-- | Read directories as Left and files as Right. Filter out "." and ".."
136142
-- entries.
@@ -139,12 +145,12 @@ reader = fmap Path.toString $ Unfold.lmapM Path.fromString DirIO.reader
139145
--
140146
{-# INLINE eitherReader #-}
141147
eitherReader :: (MonadIO m, MonadCatch m) => Unfold m FilePath (Either FilePath FilePath)
142-
eitherReader = pMapUnfoldE DirIO.eitherReader
148+
eitherReader = pMapUnfoldE CONF_AP(DirIO.eitherReader)
143149

144150

145151
{-# INLINE eitherReaderPaths #-}
146152
eitherReaderPaths ::(MonadIO m, MonadCatch m) => Unfold m FilePath (Either FilePath FilePath)
147-
eitherReaderPaths = pMapUnfoldE DirIO.eitherReaderPaths
153+
eitherReaderPaths = pMapUnfoldE CONF_AP(DirIO.eitherReaderPaths)
148154

149155
--
150156
-- | Read files only.
@@ -153,15 +159,15 @@ eitherReaderPaths = pMapUnfoldE DirIO.eitherReaderPaths
153159
--
154160
{-# INLINE fileReader #-}
155161
fileReader :: (MonadIO m, MonadCatch m) => Unfold m FilePath FilePath
156-
fileReader = pMapUnfold DirIO.fileReader
162+
fileReader = pMapUnfold CONF_AP(DirIO.fileReader)
157163

158164
-- | Read directories only. Filter out "." and ".." entries.
159165
--
160166
-- /Internal/
161167
--
162168
{-# INLINE dirReader #-}
163169
dirReader :: (MonadIO m, MonadCatch m) => Unfold m FilePath FilePath
164-
dirReader = pMapUnfold DirIO.dirReader
170+
dirReader = pMapUnfold CONF_AP(DirIO.dirReader)
165171

166172
-- | Raw read of a directory.
167173
--

core/src/Streamly/Internal/FileSystem/DirIO.hs

Lines changed: 51 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -80,8 +80,14 @@ module Streamly.Internal.FileSystem.DirIO
8080
-- * Metadata
8181
-- getMetadata GetMetadata (followSymlinks, noAutoMount - see fstatat)
8282

83+
-- * Configuration
84+
ReadOptions
85+
, followSymlinks
86+
, ignoreNonExisting
87+
, defaultReadOptions
88+
8389
-- * Streams
84-
read
90+
, read
8591

8692
-- Is there a benefit in providing a low level recursive read or
8793
-- concatIterate is good enough? Could be more efficient for non-concurrent
@@ -149,7 +155,9 @@ import qualified Streamly.Internal.Data.Fold as Fold
149155
import Streamly.Internal.FileSystem.Windows.ReadDir (eitherReader, reader)
150156
#else
151157
import Streamly.Internal.FileSystem.Posix.ReadDir
152-
(readEitherChunks, eitherReader, reader)
158+
( readEitherChunks, eitherReader, reader, ReadOptions, defaultReadOptions
159+
, ignoreNonExisting, followSymlinks
160+
)
153161
#endif
154162
import qualified Streamly.Internal.Data.Stream as S
155163
import qualified Streamly.Data.Unfold as UF
@@ -252,6 +260,20 @@ toChunks = toChunksWithBufferOf defaultChunkSize
252260
readChunks :: MonadIO m => Unfold m Handle (Array Word8)
253261
readChunks = UF.first readChunksWithBufferOf defaultChunkSize
254262
263+
-------------------------------------------------------------------------------
264+
-- Macros for Windows and Posix
265+
-------------------------------------------------------------------------------
266+
267+
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
268+
#define CONF_TYP
269+
#define CONF_ARG
270+
#define CONF_AP(x) x
271+
#else
272+
#define CONF_TYP (ReadOptions -> ReadOptions) ->
273+
#define CONF_ARG confMod
274+
#define CONF_AP(x) (x CONF_ARG)
275+
#endif
276+
255277
-------------------------------------------------------------------------------
256278
-- Read a Directory to Stream
257279
-------------------------------------------------------------------------------
@@ -298,52 +320,56 @@ toStreamWithBufferOf chunkSize h = AS.concat $ toChunksWithBufferOf chunkSize h
298320
-- created.
299321

300322
{-# INLINE eitherReaderPaths #-}
301-
eitherReaderPaths ::(MonadIO m, MonadCatch m) =>
323+
eitherReaderPaths ::(MonadIO m, MonadCatch m) => CONF_TYP
302324
Unfold m Path (Either Path Path)
303-
eitherReaderPaths =
325+
eitherReaderPaths CONF_ARG =
304326
let (</>) = Path.append
305-
in UF.mapM2 (\dir -> return . bimap (dir </>) (dir </>)) eitherReader
327+
in UF.mapM2 (\dir -> return . bimap (dir </>) (dir </>)) CONF_AP(eitherReader)
306328

307329
--
308330
-- | Read files only.
309331
--
310332
-- /Internal/
311333
--
312334
{-# INLINE fileReader #-}
313-
fileReader :: (MonadIO m, MonadCatch m) => Unfold m Path Path
314-
fileReader = fmap (fromRight undefined) $ UF.filter isRight eitherReader
335+
fileReader :: (MonadIO m, MonadCatch m) => CONF_TYP
336+
Unfold m Path Path
337+
fileReader CONF_ARG = fmap (fromRight undefined) $ UF.filter isRight CONF_AP(eitherReader)
315338

316339
-- | Read directories only. Filter out "." and ".." entries.
317340
--
318341
-- /Internal/
319342
--
320343
{-# INLINE dirReader #-}
321-
dirReader :: (MonadIO m, MonadCatch m) => Unfold m Path Path
322-
dirReader = fmap (fromLeft undefined) $ UF.filter isLeft eitherReader
344+
dirReader :: (MonadIO m, MonadCatch m) => CONF_TYP
345+
Unfold m Path Path
346+
dirReader CONF_ARG = fmap (fromLeft undefined) $ UF.filter isLeft CONF_AP(eitherReader)
323347

324348
-- | Raw read of a directory.
325349
--
326350
-- /Pre-release/
327351
{-# INLINE read #-}
328-
read :: (MonadIO m, MonadCatch m) => Path -> Stream m Path
329-
read = S.unfold reader
352+
read :: (MonadIO m, MonadCatch m) => CONF_TYP
353+
Path -> Stream m Path
354+
read CONF_ARG = S.unfold CONF_AP(reader)
330355

331356
-- | Read directories as Left and files as Right. Filter out "." and ".."
332357
-- entries. The output contains the names of the directories and files.
333358
--
334359
-- /Pre-release/
335360
{-# INLINE readEither #-}
336-
readEither :: (MonadIO m, MonadCatch m) => Path -> Stream m (Either Path Path)
337-
readEither = S.unfold eitherReader
361+
readEither :: (MonadIO m, MonadCatch m) => CONF_TYP
362+
Path -> Stream m (Either Path Path)
363+
readEither CONF_ARG = S.unfold CONF_AP(eitherReader)
338364

339365
-- | Like 'readEither' but prefix the names of the files and directories with
340366
-- the supplied directory path.
341367
{-# INLINE readEitherPaths #-}
342-
readEitherPaths :: (MonadIO m, MonadCatch m) =>
368+
readEitherPaths :: (MonadIO m, MonadCatch m) => CONF_TYP
343369
Path -> Stream m (Either Path Path)
344-
readEitherPaths dir =
370+
readEitherPaths f dir =
345371
let (</>) = Path.append
346-
in fmap (bimap (dir </>) (dir </>)) $ readEither dir
372+
in fmap (bimap (dir </>) (dir </>)) $ readEither f dir
347373

348374
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
349375
-- XXX Implement a custom version of readEitherChunks (like for Posix) for
@@ -356,13 +382,13 @@ readEitherPaths dir =
356382
-- This is a generic (but slower?) version of readEitherChunks using
357383
-- eitherReaderPaths.
358384
{-# INLINE readEitherChunks #-}
359-
readEitherChunks :: (MonadIO m, MonadCatch m) =>
385+
readEitherChunks :: (MonadIO m, MonadCatch m) => CONF_TYP
360386
[Path] -> Stream m (Either [Path] [Path])
361-
readEitherChunks dirs =
387+
readEitherChunks f dirs =
362388
-- XXX Need to use a take to limit the group size. There will be separate
363389
-- limits for dir and files groups.
364390
S.groupsWhile grouper collector
365-
$ S.unfoldEach eitherReaderPaths
391+
$ S.unfoldEach (eitherReaderPaths f)
366392
$ S.fromList dirs
367393

368394
where
@@ -390,16 +416,18 @@ readEitherChunks dirs =
390416
-- /Internal/
391417
--
392418
{-# INLINE readFiles #-}
393-
readFiles :: (MonadIO m, MonadCatch m) => Path -> Stream m Path
394-
readFiles = S.unfold fileReader
419+
readFiles :: (MonadIO m, MonadCatch m) => CONF_TYP
420+
Path -> Stream m Path
421+
readFiles CONF_ARG = S.unfold CONF_AP(fileReader)
395422

396423
-- | Read directories only.
397424
--
398425
-- /Internal/
399426
--
400427
{-# INLINE readDirs #-}
401-
readDirs :: (MonadIO m, MonadCatch m) => Path -> Stream m Path
402-
readDirs = S.unfold dirReader
428+
readDirs :: (MonadIO m, MonadCatch m) => CONF_TYP
429+
Path -> Stream m Path
430+
readDirs CONF_ARG = S.unfold CONF_AP(dirReader)
403431

404432
{-
405433
-------------------------------------------------------------------------------

0 commit comments

Comments
 (0)