@@ -68,9 +68,9 @@ module Streamly.Internal.FileSystem.FileIO
6868 , writeChunks
6969
7070 -- ** Writing Streams
71- , fromBytes -- putBytes?
72- , fromBytesWith
73- , fromChunks
71+ , fromBytes -- XXX putBytes?
72+ , fromBytesWith -- putBytesWith
73+ , fromChunks -- putChunks?
7474
7575 -- ** Append To File
7676 , writeAppend
8484import Control.Monad.Catch (MonadCatch )
8585import Control.Monad.IO.Class (MonadIO (.. ))
8686import Data.Word (Word8 )
87- import System.IO (Handle , IOMode (.. ), hClose )
87+ import System.IO (Handle , IOMode (.. ), hClose , hSetBuffering , BufferMode ( .. ) )
8888import Prelude hiding (read )
8989
9090import qualified Control.Monad.Catch as MC
@@ -130,32 +130,52 @@ import qualified Streamly.Internal.FileSystem.Windows.File as File
130130-- Safe file reading
131131-------------------------------------------------------------------------------
132132
133- -- | @'withFile' name mode act@ opens a file using 'openFile' and passes
134- -- the resulting handle to the computation @act@. The handle will be
135- -- closed on exit from 'withFile', whether by normal termination or by
136- -- raising an exception. If closing the handle raises an exception, then
137- -- this exception will be raised by 'withFile' rather than any exception
138- -- raised by 'act'.
133+ -- | @'withFile' name mode act@ opens a file with NoBuffering set on the handle
134+ -- and passes the resulting handle to the computation @act@. The handle will be
135+ -- closed on exit from 'withFile', whether by normal termination or by raising
136+ -- an exception. If closing the handle raises an exception, then that
137+ -- exception is raised by 'withFile' rather than any exception raised by 'act'.
138+ --
139+ -- The file is opened without buffering as buffering can be controlled by the
140+ -- streaming APIs.
139141--
140142-- /Pre-release/
141143--
142144{-# INLINE withFile #-}
143145withFile :: (MonadIO m , MonadCatch m )
144146 => Path -> IOMode -> (Handle -> Stream m a ) -> Stream m a
145- withFile file mode = S. bracketIO (File. openFile file mode) hClose
147+ withFile file mode = S. bracketIO open hClose
148+
149+ where
146150
147- -- | Transform an 'Unfold' from a 'Handle' to an unfold from a 'Path'. The
148- -- resulting unfold opens a handle in 'ReadMode', uses it using the supplied
149- -- unfold and then makes sure that the handle is closed on normal termination
150- -- or in case of an exception. If closing the handle raises an exception, then
151- -- this exception will be raised by 'usingFile'.
151+ open = do
152+ h <- File. openFile file mode
153+ hSetBuffering h NoBuffering
154+ return h
155+
156+ -- | Transform an 'Unfold' that takes 'Handle' as input to an unfold that takes
157+ -- a 'Path' as input. The resulting unfold opens the file in 'ReadMode',
158+ -- passes it to the supplied unfold and then makes sure that the handle is
159+ -- closed on normal termination or in case of an exception. If closing the
160+ -- handle raises an exception, then this exception will be raised by
161+ -- 'usingFile'.
162+ --
163+ -- The file is opened without buffering as buffering can be controlled by the
164+ -- streaming APIs.
152165--
153166-- /Pre-release/
154167--
155168{-# INLINE usingFile #-}
156169usingFile :: (MonadIO m , MonadCatch m )
157170 => Unfold m Handle a -> Unfold m Path a
158- usingFile = UF. bracketIO (`File.openFile` ReadMode ) hClose
171+ usingFile = UF. bracketIO open hClose
172+
173+ where
174+
175+ open file = do
176+ h <- File. openFile file ReadMode
177+ hSetBuffering h NoBuffering
178+ return h
159179
160180{-# INLINE usingFile2 #-}
161181usingFile2 :: (MonadIO m , MonadCatch m )
@@ -166,6 +186,7 @@ usingFile2 = UF.bracketIO before after
166186
167187 before (x, file) = do
168188 h <- File. openFile file ReadMode
189+ hSetBuffering h NoBuffering
169190 return (x, h)
170191
171192 after (_, h) = hClose h
@@ -179,6 +200,7 @@ usingFile3 = UF.bracketIO before after
179200
180201 before (x, y, z, file) = do
181202 h <- File. openFile file ReadMode
203+ hSetBuffering h NoBuffering
182204 return (x, y, z, h)
183205
184206 after (_, _, _, h) = hClose h
@@ -201,7 +223,7 @@ usingFile3 = UF.bracketIO before after
201223putChunk :: Path -> Array a -> IO ()
202224putChunk file arr = File. withFile file WriteMode (`FH.putChunk` arr)
203225
204- -- | append an array to a file.
226+ -- | Append an array to a file.
205227--
206228-- /Pre-release/
207229--
@@ -378,17 +400,18 @@ write :: (MonadIO m, Storable a) => Handle -> Stream m a -> m ()
378400write = toHandleWith A.defaultChunkSize
379401-}
380402
381- -- | Write a stream of chunks to a handle. Each chunk in the stream is written
382- -- to the device as a separate IO request.
403+ -- | Write a stream of chunks to a file. Each chunk in the stream is written
404+ -- immediately to the device as a separate IO request, without coalescing or
405+ -- buffering.
383406--
384- -- /Pre-release/
385407{-# INLINE writeChunks #-}
386408writeChunks :: (MonadIO m , MonadCatch m )
387409 => Path -> Fold m (Array a ) ()
388410writeChunks path = Fold step initial extract final
389411 where
390412 initial = do
391413 h <- liftIO (File. openFile path WriteMode )
414+ liftIO $ hSetBuffering h NoBuffering
392415 fld <- FL. reduce (FH. writeChunks h)
393416 `MC.onException` liftIO (hClose h)
394417 return $ FL. Partial (fld, h)
0 commit comments