Rename "append" routines in FileSystem.File to writeAppend

This commit is contained in:
Ranjeet Kumar Ranjan 2023-07-17 15:26:40 +05:30
parent d45b17c3c8
commit 36973708ac

View File

@ -75,11 +75,11 @@ module Streamly.Internal.FileSystem.File
, fromChunks
-- ** Append To File
, append
, appendWith
, writeAppend
, writeAppendWith
-- , appendShared
, appendArray
, appendChunks
, writeAppendArray
, writeAppendChunks
-- * Deprecated
, readWithBufferOf
@ -211,9 +211,9 @@ putChunk file arr = SIO.withFile file WriteMode (`FH.putChunk` arr)
--
-- /Pre-release/
--
{-# INLINABLE appendArray #-}
appendArray :: FilePath -> Array a -> IO ()
appendArray file arr = SIO.withFile file AppendMode (`FH.putChunk` arr)
{-# INLINABLE writeAppendArray #-}
writeAppendArray :: FilePath -> Array a -> IO ()
writeAppendArray file arr = SIO.withFile file AppendMode (`FH.putChunk` arr)
-------------------------------------------------------------------------------
-- Stream of Arrays IO
@ -487,10 +487,10 @@ write = writeWith defaultChunkSize
--
-- /Pre-release/
--
{-# INLINE appendChunks #-}
appendChunks :: (MonadIO m, MonadCatch m)
{-# INLINE writeAppendChunks #-}
writeAppendChunks :: (MonadIO m, MonadCatch m)
=> FilePath -> Stream m (Array a) -> m ()
appendChunks = fromChunksMode AppendMode
writeAppendChunks = fromChunksMode AppendMode
-- | Like 'append' but provides control over the write buffer. Output will
-- be written to the IO device as soon as we collect the specified number of
@ -498,10 +498,10 @@ appendChunks = fromChunksMode AppendMode
--
-- /Pre-release/
--
{-# INLINE appendWith #-}
appendWith :: (MonadIO m, MonadCatch m)
{-# INLINE writeAppendWith #-}
writeAppendWith :: (MonadIO m, MonadCatch m)
=> Int -> FilePath -> Stream m Word8 -> m ()
appendWith n file xs = appendChunks file $ S.chunksOf n xs
writeAppendWith n file xs = writeAppendChunks file $ S.chunksOf n xs
-- | Append a byte stream to a file. Combines the bytes in chunks of size up to
-- 'A.defaultChunkSize' before writing. If the file exists then the new data
@ -510,9 +510,9 @@ appendWith n file xs = appendChunks file $ S.chunksOf n xs
--
-- /Pre-release/
--
{-# INLINE append #-}
append :: (MonadIO m, MonadCatch m) => FilePath -> Stream m Word8 -> m ()
append = appendWith defaultChunkSize
{-# INLINE writeAppend #-}
writeAppend :: (MonadIO m, MonadCatch m) => FilePath -> Stream m Word8 -> m ()
writeAppend = writeAppendWith defaultChunkSize
{-
-- | Like 'append' but the file is not locked for exclusive writes.