Skip to content

Commit

Permalink
fix review comments
Browse files Browse the repository at this point in the history
  • Loading branch information
rnjtranjan committed May 24, 2023
1 parent dea3d5f commit f990b47
Show file tree
Hide file tree
Showing 4 changed files with 18 additions and 38 deletions.
1 change: 0 additions & 1 deletion core/src/Streamly/Data/MutArray/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,6 @@ module Streamly.Data.MutArray.Generic

-- * Streams
, read
, readRev

-- * Random reads
, getIndex
Expand Down
10 changes: 3 additions & 7 deletions core/src/Streamly/Internal/Data/Array/Generic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -209,15 +209,11 @@ getIndexUnsafe :: Int -> Array a -> a
getIndexUnsafe i arr =
unsafePerformIO $ MArray.getIndexUnsafe i (unsafeThaw arr)

invalidIndex :: String -> Int -> a
invalidIndex label i =
error $ label ++ ": invalid array index " ++ show i

getIndex :: Int -> Array a -> a
getIndex :: Int -> Array a -> Maybe a
getIndex i arr@Array {..} =
if i >= 0 && i < arrLen
then getIndexUnsafe i arr
else invalidIndex "getIndex" i
then Just $ getIndexUnsafe i arr
else Nothing

{-# INLINE writeLastN #-}
writeLastN :: MonadIO m => Int -> Fold m a (Array a)
Expand Down
17 changes: 1 addition & 16 deletions core/src/Streamly/Internal/Data/Array/Generic/Mut/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,10 +28,6 @@ module Streamly.Internal.Data.Array.Generic.Mut.Type
, writeWith
, write
, fromStreamN
, fromStream

, fromListN
, fromList

-- , writeRevN
-- , writeRev
Expand Down Expand Up @@ -97,7 +93,6 @@ module Streamly.Internal.Data.Array.Generic.Mut.Type

-- ** To containers
, read
, readRev
, toStreamK
-- , toStreamKRev
, toList
Expand Down Expand Up @@ -533,11 +528,8 @@ getSlice index len arr@MutArray{..} =
toList :: MonadIO m => MutArray a -> m [a]
toList arr@MutArray{..} = mapM (`getIndexUnsafe` arr) [0 .. (arrLen - 1)]

-- | Use the 'read' unfold instead.
--
-- @read = D.unfold read@
--
-- We can try this if the unfold has any performance issues.
-- /Pre-release/
{-# INLINE_NORMAL read #-}
read :: MonadIO m => MutArray a -> D.Stream m a
read arr@MutArray{..} =
Expand All @@ -556,13 +548,6 @@ toStreamK arr@MutArray{..} = K.unfoldrM step 0
x <- getIndexUnsafe i arr
return $ Just (x, i + 1)

{-# INLINE_NORMAL readRev #-}
readRev :: MonadIO m => MutArray a -> D.Stream m a
readRev arr@MutArray{..} =
D.mapM (`getIndexUnsafe` arr)
$ D.enumerateFromThenToIntegral (arrLen - 1) (arrLen - 2) 0


-------------------------------------------------------------------------------
-- Folds
-------------------------------------------------------------------------------
Expand Down
28 changes: 14 additions & 14 deletions core/src/Streamly/Internal/FileSystem/File.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,9 +71,9 @@ module Streamly.Internal.FileSystem.File
, writeChunks

-- ** Writing Streams
, putBytes
, putBytesWith
, putChunks
, fromBytes -- putBytes?
, fromBytesWith
, fromChunks

-- ** Append To File
, append
Expand Down Expand Up @@ -383,10 +383,10 @@ fromChunksMode mode file xs = S.fold drain $
--
-- /Pre-release/
--
{-# INLINE putChunks #-}
putChunks :: (MonadIO m, MonadCatch m)
{-# INLINE fromChunks #-}
fromChunks :: (MonadIO m, MonadCatch m)
=> FilePath -> Stream m (Array a) -> m ()
putChunks = fromChunksMode WriteMode
fromChunks = fromChunksMode WriteMode

-- GHC buffer size dEFAULT_FD_BUFFER_SIZE=8192 bytes.
--
Expand All @@ -402,16 +402,16 @@ putChunks = fromChunksMode WriteMode
--
-- /Pre-release/
--
{-# INLINE putBytesWith #-}
putBytesWith :: (MonadIO m, MonadCatch m)
{-# INLINE fromBytesWith #-}
fromBytesWith :: (MonadIO m, MonadCatch m)
=> Int -> FilePath -> Stream m Word8 -> m ()
putBytesWith n file xs = putChunks file $ S.chunksOf n xs
fromBytesWith n file xs = fromChunks file $ S.chunksOf n xs

{-# DEPRECATED fromBytesWithBufferOf "Please use 'putBytesWith' instead" #-}
{-# DEPRECATED fromBytesWithBufferOf "Please use 'fromBytesWith' instead" #-}
{-# INLINE fromBytesWithBufferOf #-}
fromBytesWithBufferOf :: (MonadIO m, MonadCatch m)
=> Int -> FilePath -> Stream m Word8 -> m ()
fromBytesWithBufferOf = putBytesWith
fromBytesWithBufferOf = fromBytesWith

-- > write = 'writeWith' defaultChunkSize
--
Expand All @@ -421,9 +421,9 @@ fromBytesWithBufferOf = putBytesWith
-- created. File is locked using single writer locking mode.
--
-- /Pre-release/
{-# INLINE putBytes #-}
putBytes :: (MonadIO m, MonadCatch m) => FilePath -> Stream m Word8 -> m ()
putBytes = putBytesWith defaultChunkSize
{-# INLINE fromBytes #-}
fromBytes :: (MonadIO m, MonadCatch m) => FilePath -> Stream m Word8 -> m ()
fromBytes = fromBytesWith defaultChunkSize

{-
{-# INLINE write #-}
Expand Down

0 comments on commit f990b47

Please sign in to comment.