Change the argument order of Unfold.many

This commit is contained in:
Ranjeet Kumar Ranjan 2022-03-14 15:03:32 +05:30 committed by Harendra Kumar
parent 7da8c7933a
commit 3012ae95e5
7 changed files with 11 additions and 11 deletions

View File

@ -135,7 +135,7 @@ _readChunks inh devNull = IUF.fold fld unf inh
where
fld = FH.write devNull
unf = IUF.many FH.readChunks A.read
unf = IUF.many A.read FH.readChunks
-- | Send the chunk content to /dev/null
-- Implicitly benchmarked via 'readWithBufferOfFromBytesNull'
@ -145,7 +145,7 @@ _readChunksWithBufferOf inh devNull = IUF.fold fld unf (defaultChunkSize, inh)
where
fld = FH.write devNull
unf = IUF.many FH.readChunksWithBufferOf A.read
unf = IUF.many A.read FH.readChunksWithBufferOf
o_1_space_copy_fromBytes :: BenchEnv -> [Benchmark]

View File

@ -572,8 +572,8 @@ data ConcatState s1 s2 = ConcatOuter s1 | ConcatInner s1 s2
-- /Since: 0.8.0/
--
{-# INLINE_NORMAL many #-}
many :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c
many (Unfold step1 inject1) (Unfold step2 inject2) = Unfold step inject
many :: Monad m => Unfold m b c -> Unfold m a b -> Unfold m a c
many (Unfold step2 inject2) (Unfold step1 inject1) = Unfold step inject
where

View File

@ -293,7 +293,7 @@ readWithBufferOf = usingFile2 FH.readWithBufferOf
-- @since 0.7.0
{-# INLINE read #-}
read :: (MonadCatch m, MonadAsync m) => Unfold m FilePath Word8
read = UF.many (usingFile FH.readChunks) A.read
read = UF.many A.read (usingFile FH.readChunks)
-- | Generate a stream of bytes from a file specified by path. The stream ends
-- when EOF is encountered. File is locked using multiple reader and single

View File

@ -343,12 +343,12 @@ readChunks = UF.supplyFirst defaultChunkSize readChunksWithBufferOf
-- | Unfolds the tuple @(bufsize, handle)@ into a byte stream, read requests
-- to the IO device are performed using buffers of @bufsize@.
--
-- >>> readWithBufferOf = Unfold.many Handle.readChunksWithBufferOf Array.read
-- >>> readWithBufferOf = Unfold.many Array.read Handle.readChunksWithBufferOf
--
-- @since 0.7.0
{-# INLINE readWithBufferOf #-}
readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8
readWithBufferOf = UF.many readChunksWithBufferOf A.read
readWithBufferOf = UF.many A.read readChunksWithBufferOf
-- | @toBytesWithBufferOf bufsize handle@ reads a byte stream from a file
-- handle, reads are performed in chunks of up to @bufsize@.
@ -373,7 +373,7 @@ toBytesWithBufferOf size h = AS.concat $ toChunksWithBufferOf size h
-- @since 0.7.0
{-# INLINE read #-}
read :: MonadIO m => Unfold m Handle Word8
read = UF.many readChunks A.read
read = UF.many A.read readChunks
-- | Generate a byte stream from a file 'Handle'.
--

View File

@ -314,7 +314,7 @@ withConnection addr port =
{-# INLINE read #-}
read :: (MonadCatch m, MonadAsync m)
=> Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Word8
read = UF.many (usingConnection ISK.readChunks) A.read
read = UF.many A.read (usingConnection ISK.readChunks)
-- | Read a stream from the supplied IPv4 host address and port number.
--

View File

@ -430,7 +430,7 @@ toBytes = AS.concat . toChunks
-- @since 0.7.0
{-# INLINE readWithBufferOf #-}
readWithBufferOf :: MonadIO m => Unfold m (Int, Socket) Word8
readWithBufferOf = UF.many readChunksWithBufferOf A.read
readWithBufferOf = UF.many A.read readChunksWithBufferOf
-- | Unfolds a 'Socket' into a byte stream. IO requests to the socket are
-- performed in sizes of

View File

@ -545,7 +545,7 @@ concat :: Bool
concat =
let unfIn = UF.replicateM 10
unfOut = UF.map return UF.enumerateFromToIntegral
unf = UF.many unfOut unfIn
unf = UF.many unfIn unfOut
lst = Prelude.concat $ Prelude.map (Prelude.replicate 10) [1 .. 10]
in testUnfoldD unf (1, 10) lst