Rename write* to create* in Array module

Export create/createOf from Array module
Rearrange exports in Array module
This commit is contained in:
Harendra Kumar 2024-01-06 15:38:55 +05:30
parent b7d8b96728
commit 8e8159f156
9 changed files with 128 additions and 75 deletions

View File

@ -8,7 +8,7 @@
For APIs that have not been released yet.
>>> import qualified Streamly.Internal.Data.Array as Array (writeNUnsafe)
>>> import qualified Streamly.Internal.Data.Array as Array (unsafeCreateOf)
>>> import qualified Streamly.Internal.Data.Unfold as Unfold (first)
>>> import qualified Streamly.Internal.FileSystem.Handle as Handle
>>> import qualified Streamly.Internal.System.IO as IO (defaultChunkSize)

View File

@ -31,28 +31,6 @@ module Streamly.Data.Array
-- * The Array Type
Array
-- * Construction
-- | When performance matters, the fastest way to generate an array is
-- 'writeN'. 'IsList' and 'IsString' instances can be
-- used to conveniently construct arrays from literal values.
-- 'OverloadedLists' extension or 'fromList' can be used to construct an
-- array from a list literal. Similarly, 'OverloadedStrings' extension or
-- 'fromList' can be used to construct an array from a string literal.
-- Pure List APIs
, fromListN
, fromList
-- Monadic APIs
, writeN -- drop new
, write -- full buffer
, writeLastN -- drop old (ring buffer)
-- * Conversion
-- 'GHC.Exts.toList' from "GHC.Exts" can be used to convert an array to a
-- list.
, toList
-- * Pinning & Unpinning
-- | Arrays are created unpinned by default unless pinned versions of
-- creation APIs are used. Look for APIs with @pinned@ prefix in
@ -66,7 +44,29 @@ module Streamly.Data.Array
, unpin
, isPinned
-- * Streams
-- * Construction
-- | When performance matters, the fastest way to generate an array is
-- 'createOf'. 'IsList' and 'IsString' instances can be
-- used to conveniently construct arrays from literal values.
-- 'OverloadedLists' extension or 'fromList' can be used to construct an
-- array from a list literal. Similarly, 'OverloadedStrings' extension or
-- 'fromList' can be used to construct an array from a string literal.
-- ** From Stream
, createOf
, create
, writeLastN -- drop old (ring buffer)
-- ** From List
, fromListN
, fromList
-- * To List
-- 'GHC.Exts.toList' from "GHC.Exts" can be used to convert an array to a
-- list.
, toList
-- * To Stream
, read
, readRev
@ -90,6 +90,10 @@ module Streamly.Data.Array
-- * Re-exports
, Unbox (..)
, Serialize(..)
-- * Deprecated
, writeN -- drop new
, write -- full buffer
)
where
@ -122,7 +126,7 @@ import Prelude hiding (read, length)
--
-- Convert array to stream, transform, and fold back to array:
--
-- >>> amap f arr = Array.read arr & fmap f & Stream.fold Array.write
-- >>> amap f arr = Array.read arr & fmap f & Stream.fold Array.create
-- >>> amap (+1) (Array.fromList [1,2,3::Int])
-- fromList [2,3,4]
--
@ -154,7 +158,7 @@ import Prelude hiding (read, length)
--
-- >>> pure = Stream.fromList [1,2,3] :: Stream Identity Int
-- >>> generally = Stream.morphInner (return . runIdentity)
-- >>> Stream.fold Array.write (generally pure :: Stream IO Int)
-- >>> Stream.fold Array.create (generally pure :: Stream IO Int)
-- fromList [1,2,3]
--
-- == Programming Tips

View File

@ -205,6 +205,8 @@ last = getIndexRev 0
-- Folds with Array as the container
-------------------------------------------------------------------------------
-- XXX We should generate this from Ring.
-- | @writeLastN n@ folds a maximum of @n@ elements from the end of the input
-- stream to an 'Array'.
--
@ -447,7 +449,7 @@ runPipe f arr = P.runPipe (toArrayMinChunk (length arr)) $ f (read arr)
streamTransform :: forall m a b. (MonadIO m, Unbox a, Unbox b)
=> (Stream m a -> Stream m b) -> Array a -> m (Array b)
streamTransform f arr =
Stream.fold (writeWith (length arr)) $ f (read arr)
Stream.fold (createWith (length arr)) $ f (read arr)
-------------------------------------------------------------------------------
-- Casts

View File

@ -45,15 +45,13 @@ module Streamly.Internal.Data.Array.Type
-- *** Stream Folds
, unsafeMakePure
, writeWith
, writeN
, pinnedWriteN
, writeNUnsafe
, pinnedWriteNUnsafe
-- , MA.ArrayUnsafe (..)
, pinnedWriteNAligned
, write
, pinnedWrite
, createOf
, pinnedCreateOf
, unsafeCreateOf
, unsafePinnedCreateOf
, create
, pinnedCreate
, createWith
-- *** From containers
, fromListN
@ -75,8 +73,8 @@ module Streamly.Internal.Data.Array.Type
-- ** Reading
-- *** Indexing
, unsafeIndexIO -- XXX rename to getIndexUnsafeIO
, getIndexUnsafe
, unsafeIndexIO -- XXX unsafeGetIndexIO
, getIndexUnsafe -- XXX unsafeGetIndex
-- *** To Streams
, read
@ -143,6 +141,14 @@ module Streamly.Internal.Data.Array.Type
, toStream
, toStreamRev
, nil
, writeWith
, writeN
, pinnedWriteN
, writeNUnsafe
, pinnedWriteNUnsafe
, pinnedWriteNAligned
, write
, pinnedWrite
)
where
@ -745,17 +751,28 @@ toList s = build (\c n -> toListFB c n s)
-- Folds
-------------------------------------------------------------------------------
-- | @writeN n@ folds a maximum of @n@ elements from the input stream to an
-- | @createOf n@ folds a maximum of @n@ elements from the input stream to an
-- 'Array'.
--
{-# INLINE_NORMAL writeN #-}
writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a)
writeN = fmap unsafeFreeze . MA.writeN
{-# INLINE_NORMAL createOf #-}
createOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a)
createOf = fmap unsafeFreeze . MA.createOf
-- | Like 'fromListN' but creates a pinned array.
{-# INLINE_NORMAL pinnedWriteN #-}
-- XXX Deprecate in major
-- {-# DEPRECATED writeN "Please use createOf instead." #-}
{-# INLINE writeN #-}
writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a)
writeN = createOf
-- | Like 'createOf' but creates a pinned array.
{-# INLINE_NORMAL pinnedCreateOf #-}
pinnedCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a)
pinnedCreateOf = fmap unsafeFreeze . MA.pinnedCreateOf
{-# DEPRECATED pinnedWriteN "Please use pinnedCreateOf instead." #-}
{-# INLINE pinnedWriteN #-}
pinnedWriteN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a)
pinnedWriteN = fmap unsafeFreeze . MA.pinnedCreateOf
pinnedWriteN = pinnedCreateOf
-- | @pinnedWriteNAligned alignment n@ folds a maximum of @n@ elements from the input
-- stream to an 'Array' aligned to the given size.
@ -763,44 +780,74 @@ pinnedWriteN = fmap unsafeFreeze . MA.pinnedCreateOf
-- /Pre-release/
--
{-# INLINE_NORMAL pinnedWriteNAligned #-}
{-# DEPRECATED pinnedWriteNAligned "To be removed." #-}
pinnedWriteNAligned :: forall m a. (MonadIO m, Unbox a)
=> Int -> Int -> Fold m a (Array a)
pinnedWriteNAligned alignSize = fmap unsafeFreeze . MA.pinnedWriteNAligned alignSize
-- | Like 'writeN' but does not check the array bounds when writing. The fold
-- | Like 'createOf' but does not check the array bounds when writing. The fold
-- driver must not call the step function more than 'n' times otherwise it will
-- corrupt the memory and crash. This function exists mainly because any
-- conditional in the step function blocks fusion causing 10x performance
-- slowdown.
--
{-# INLINE_NORMAL writeNUnsafe #-}
{-# INLINE_NORMAL unsafeCreateOf #-}
unsafeCreateOf :: forall m a. (MonadIO m, Unbox a)
=> Int -> Fold m a (Array a)
unsafeCreateOf n = unsafeFreeze <$> MA.unsafeCreateOf n
{-# DEPRECATED writeNUnsafe "Please use unsafeCreateOf instead." #-}
{-# INLINE writeNUnsafe #-}
writeNUnsafe :: forall m a. (MonadIO m, Unbox a)
=> Int -> Fold m a (Array a)
writeNUnsafe n = unsafeFreeze <$> MA.unsafeCreateOf n
writeNUnsafe = unsafeCreateOf
{-# INLINE_NORMAL pinnedWriteNUnsafe #-}
{-# INLINE_NORMAL unsafePinnedCreateOf #-}
unsafePinnedCreateOf :: forall m a. (MonadIO m, Unbox a)
=> Int -> Fold m a (Array a)
unsafePinnedCreateOf n = unsafeFreeze <$> MA.unsafePinnedCreateOf n
{-# DEPRECATED pinnedWriteNUnsafe "Please use unsafePinnedCreateOf instead." #-}
{-# INLINE pinnedWriteNUnsafe #-}
pinnedWriteNUnsafe :: forall m a. (MonadIO m, Unbox a)
=> Int -> Fold m a (Array a)
pinnedWriteNUnsafe n = unsafeFreeze <$> MA.unsafePinnedCreateOf n
pinnedWriteNUnsafe = unsafePinnedCreateOf
{-# INLINE_NORMAL writeWith #-}
{-# INLINE_NORMAL createWith #-}
createWith :: forall m a. (MonadIO m, Unbox a)
=> Int -> Fold m a (Array a)
-- createWith n = FL.rmapM spliceArrays $ toArraysOf n
createWith elemCount = unsafeFreeze <$> MA.createWith elemCount
{-# DEPRECATED writeWith "Please use createWith instead." #-}
{-# INLINE writeWith #-}
writeWith :: forall m a. (MonadIO m, Unbox a)
=> Int -> Fold m a (Array a)
-- writeWith n = FL.rmapM spliceArrays $ toArraysOf n
writeWith elemCount = unsafeFreeze <$> MA.createWith elemCount
writeWith = createWith
-- | Fold the whole input to a single array.
--
-- /Caution! Do not use this on infinite streams./
--
{-# INLINE create #-}
create :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a)
create = fmap unsafeFreeze MA.create
-- XXX Deprecate in major
-- {-# DEPRECATED write "Please use create instead." #-}
{-# INLINE write #-}
write :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a)
write = fmap unsafeFreeze MA.write
write = create
-- | Like 'write' but creates a pinned array.
-- | Like 'create' but creates a pinned array.
{-# INLINE pinnedCreate #-}
pinnedCreate :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a)
pinnedCreate = fmap unsafeFreeze MA.pinnedCreate
{-# DEPRECATED pinnedWrite "Please use pinnedCreate instead." #-}
{-# INLINE pinnedWrite #-}
pinnedWrite :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a)
pinnedWrite = fmap unsafeFreeze MA.pinnedCreate
pinnedWrite = pinnedCreate
-- | Fold "step" has a dependency on "initial", and each step is dependent on
-- the previous invocation of step due to state passing, finally extract

View File

@ -103,7 +103,7 @@ import qualified Control.Monad.Catch as MC
import qualified System.IO as SIO
import Streamly.Data.Fold (groupsOf, drain)
import Streamly.Internal.Data.Array.Type (Array(..), pinnedWriteNUnsafe)
import Streamly.Internal.Data.Array.Type (Array(..))
import Streamly.Internal.Data.Fold.Type (Fold(..))
import Streamly.Data.Stream (Stream)
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
@ -462,7 +462,7 @@ writeChunks path = Fold step initial extract final
writeWith :: (MonadIO m, MonadCatch m)
=> Int -> FilePath -> Fold m Word8 ()
writeWith n path =
groupsOf n (pinnedWriteNUnsafe n) (writeChunks path)
groupsOf n (A.unsafePinnedCreateOf n) (writeChunks path)
{-# DEPRECATED writeWithBufferOf "Please use 'writeWith' instead" #-}
{-# INLINE writeWithBufferOf #-}

View File

@ -40,8 +40,8 @@ module Streamly.Internal.FileSystem.Handle
-- * Streams
, read
, readWith
, readChunksWith
, readWith -- readConcatChunksOf
, readChunksWith -- readChunksOf
, readChunks
-- * Unfolds
@ -59,10 +59,10 @@ module Streamly.Internal.FileSystem.Handle
-- , writeUtf8ByLines
-- , writeByFrames
-- , writeLines
, writeWith
, writeWith -- writeChunksOf
, writeChunks
, writeChunksWith
, writeMaybesWith
, writeChunksWith -- writeCompactChunksOf
, writeMaybesWith -- writeCompactJustsOf
-- * Refolds
, writer
@ -131,7 +131,7 @@ import Streamly.Internal.Data.Fold (Fold)
import Streamly.Internal.Data.Refold.Type (Refold(..))
import Streamly.Internal.Data.Unfold.Type (Unfold(..))
import Streamly.Internal.Data.Array.Type
(Array(..), pinnedWriteNUnsafe, unsafeFreezeWithShrink, byteLength)
(Array(..), unsafeFreezeWithShrink, byteLength)
import Streamly.Internal.Data.Stream.Type (Stream)
-- import Streamly.String (encodeUtf8, decodeUtf8, foldLines)
import Streamly.Internal.System.IO (defaultChunkSize)
@ -489,11 +489,11 @@ writeChunksWithBufferOf = writeChunksWith
-- Bytes in the input stream are collected into a buffer until we have a chunk
-- of @reqSize@ and then written to the IO device.
--
-- >>> writeWith n h = Fold.groupsOf n (Array.writeNUnsafe n) (Handle.writeChunks h)
-- >>> writeWith n h = Fold.groupsOf n (Array.unsafeCreateOf n) (Handle.writeChunks h)
--
{-# INLINE writeWith #-}
writeWith :: MonadIO m => Int -> Handle -> Fold m Word8 ()
writeWith n h = FL.groupsOf n (pinnedWriteNUnsafe n) (writeChunks h)
writeWith n h = FL.groupsOf n (A.unsafePinnedCreateOf n) (writeChunks h)
-- | Same as 'writeWith'
--
@ -511,7 +511,7 @@ writeWithBufferOf = writeWith
writeMaybesWith :: (MonadIO m )
=> Int -> Handle -> Fold m (Maybe Word8) ()
writeMaybesWith n h =
let writeNJusts = FL.lmap fromJust $ A.pinnedWriteN n
let writeNJusts = FL.lmap fromJust $ A.pinnedCreateOf n
writeOnNothing = FL.takeEndBy_ isNothing writeNJusts
in FL.many writeOnNothing (writeChunks h)
@ -521,7 +521,7 @@ writeMaybesWith n h =
{-# INLINE writerWith #-}
writerWith :: MonadIO m => Int -> Refold m Handle Word8 ()
writerWith n =
FL.refoldMany (FL.take n $ pinnedWriteNUnsafe n) chunkWriter
FL.refoldMany (FL.take n $ A.unsafePinnedCreateOf n) chunkWriter
-- | Write a byte stream to a file handle. Accumulates the input in chunks of
-- up to 'Streamly.Internal.Data.Array.Type.defaultChunkSize' before writing

View File

@ -116,7 +116,6 @@ import Prelude hiding (read)
import Streamly.Internal.Control.Concurrent (MonadAsync)
import Streamly.Internal.Control.ForkLifted (fork)
import Streamly.Data.Array (Array)
import Streamly.Internal.Data.Array (pinnedWriteNUnsafe)
import Streamly.Internal.Data.Fold ( Fold(..) )
import Streamly.Data.Stream (Stream)
import Streamly.Internal.Data.Tuple.Strict (Tuple'(..))
@ -132,7 +131,8 @@ import qualified Streamly.Data.Array as A
import qualified Streamly.Data.Fold as FL
import qualified Streamly.Data.Stream as S
import qualified Streamly.Data.Unfold as UF
import qualified Streamly.Internal.Data.Array as A (pinnedChunksOf)
import qualified Streamly.Internal.Data.Array as A
(pinnedChunksOf, unsafePinnedCreateOf)
import qualified Streamly.Internal.Data.Unfold as UF (bracketIO)
import qualified Streamly.Internal.Data.Fold as FL (Step(..), reduce)
@ -435,7 +435,7 @@ writeWithBufferOf
-> PortNumber
-> Fold m Word8 ()
writeWithBufferOf n addr port =
FL.groupsOf n (pinnedWriteNUnsafe n) (writeChunks addr port)
FL.groupsOf n (A.unsafePinnedCreateOf n) (writeChunks addr port)
-- | Write a stream to the supplied IPv4 host address and port number.
--

View File

@ -99,7 +99,7 @@ import qualified Streamly.Data.Stream as S
import qualified Streamly.Data.Unfold as UF
import qualified Streamly.Internal.Data.Array as A
( unsafeFreeze, unsafePinnedAsPtr, byteLength, pinnedChunksOf,
pinnedWriteN, pinnedWriteNUnsafe, lCompactGE )
pinnedCreateOf, unsafePinnedCreateOf, lCompactGE )
import qualified Streamly.Internal.Data.MutArray as MArray
(MutArray(..), unsafePinnedAsPtr, pinnedEmptyOf)
import qualified Streamly.Internal.Data.Stream as S (fromStreamK, Stream(..), Step(..))
@ -505,7 +505,7 @@ putBytesWith n h m = putChunks h $ A.pinnedChunksOf n m
--
{-# INLINE writeWith #-}
writeWith :: MonadIO m => Int -> Socket -> Fold m Word8 ()
writeWith n h = FL.groupsOf n (A.pinnedWriteNUnsafe n) (writeChunks h)
writeWith n h = FL.groupsOf n (A.unsafePinnedCreateOf n) (writeChunks h)
-- | Same as 'writeWith'
--
@ -523,7 +523,7 @@ writeWithBufferOf = writeWith
writeMaybesWith :: (MonadIO m )
=> Int -> Socket -> Fold m (Maybe Word8) ()
writeMaybesWith n h =
let writeNJusts = FL.lmap fromJust $ A.pinnedWriteN n
let writeNJusts = FL.lmap fromJust $ A.pinnedCreateOf n
writeOnNothing = FL.takeEndBy_ isNothing writeNJusts
in FL.many writeOnNothing (writeChunks h)

View File

@ -229,7 +229,7 @@ main =
prop "read . write === id" testFoldUnfold
prop "fromList" testFromList
prop "foldMany with writeNUnsafe concats to original"
(foldManyWith (\n -> Fold.take n (A.writeNUnsafe n)))
(foldManyWith (\n -> Fold.take n (A.unsafeCreateOf n)))
describe "unsafeSlice" $ do
it "partial" $ unsafeSlice 2 4 [1..10]
it "none" $ unsafeSlice 10 0 [1..10]