streamly-core-0.1.0: Streaming, parsers, arrays and more
Copyright(c) 2020 Composewell Technologies
LicenseBSD3-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Array.Type

Description

Synopsis

Documentation

We can use an Unbox constraint in the Array type and the constraint can be automatically provided to a function that pattern matches on the Array type. However, it has huge performance cost, so we do not use it. Investigate a GHC improvement possiblity.

data Array a Source #

Constructors

Array 

Instances

Instances details
a ~ Char => IsString (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

fromString :: String -> Array a #

Unbox a => Monoid (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

Unbox a => Semigroup (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Unbox a => IsList (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Associated Types

type Item (Array a) #

Methods

fromList :: [Item (Array a)] -> Array a #

fromListN :: Int -> [Item (Array a)] -> Array a #

toList :: Array a -> [Item (Array a)] #

(Unbox a, Read a, Show a) => Read (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

(Show a, Unbox a) => Show (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

(Unbox a, Eq a) => Eq (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

(Unbox a, Ord a) => Ord (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

(>=) :: Array a -> Array a -> Bool #

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

type Item (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Type

type Item (Array a) = a

asPtrUnsafe :: MonadIO m => Array a -> (Ptr a -> m b) -> m b Source #

Use an Array a as Ptr a.

See asPtrUnsafe in the Mutable array module for more details.

Unsafe

Pre-release

Freezing and Thawing

unsafeFreeze :: MutArray a -> Array a Source #

Makes an immutable array using the underlying memory of the mutable array.

Please make sure that there are no other references to the mutable array lying around, so that it is never used after freezing it using unsafeFreeze. If the underlying array is mutated, the immutable promise is lost.

Pre-release

unsafeFreezeWithShrink :: Unbox a => MutArray a -> Array a Source #

Similar to unsafeFreeze but uses rightSize on the mutable array first.

unsafeThaw :: Array a -> MutArray a Source #

Makes a mutable array using the underlying memory of the immutable array.

Please make sure that there are no other references to the immutable array lying around, so that it is never used after thawing it using unsafeThaw. If the resulting array is mutated, any references to the older immutable array are mutated as well.

Pre-release

Pinning and Unpinning

pin :: Array a -> IO (Array a) Source #

unpin :: Array a -> IO (Array a) Source #

Construction

splice :: (MonadIO m, Unbox a) => Array a -> Array a -> m (Array a) Source #

fromList :: Unbox a => [a] -> Array a Source #

Create an Array from a list. The list must be of finite size.

fromListN :: Unbox a => Int -> [a] -> Array a Source #

Create an Array from the first N elements of a list. The array is allocated to size N, if the list terminates before N elements then the array may hold less than N elements.

fromListRev :: Unbox a => [a] -> Array a Source #

Create an Array from a list in reverse order. The list must be of finite size.

Pre-release

fromListRevN :: Unbox a => Int -> [a] -> Array a Source #

Create an Array from the first N elements of a list in reverse order. The array is allocated to size N, if the list terminates before N elements then the array may hold less than N elements.

Pre-release

fromStreamDN :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> m (Array a) Source #

fromStreamD :: forall m a. (MonadIO m, Unbox a) => Stream m a -> m (Array a) Source #

Split

Elimination

unsafeIndexIO :: forall a. Unbox a => Int -> Array a -> IO a Source #

Return element at the specified index without checking the bounds.

Unsafe because it does not check the bounds of the array.

unsafeIndex :: forall a. Unbox a => Int -> Array a -> a Source #

Return element at the specified index without checking the bounds.

byteLength :: Array a -> Int Source #

O(1) Get the byte length of the array.

length :: Unbox a => Array a -> Int Source #

O(1) Get the length of the array i.e. the number of elements in the array.

foldl' :: forall a b. Unbox a => (b -> a -> b) -> b -> Array a -> b Source #

foldr :: Unbox a => (a -> b -> b) -> b -> Array a -> b Source #

splitAt :: Unbox a => Int -> Array a -> (Array a, Array a) Source #

Create two slices of an array without copying the original array. The specified index i is the first index of the second slice.

toStreamD :: forall m a. (Monad m, Unbox a) => Array a -> Stream m a Source #

toStreamDRev :: forall m a. (Monad m, Unbox a) => Array a -> Stream m a Source #

toStreamK :: forall m a. (Monad m, Unbox a) => Array a -> StreamK m a Source #

toStreamKRev :: forall m a. (Monad m, Unbox a) => Array a -> StreamK m a Source #

toStream :: (Monad m, Unbox a) => Array a -> Stream m a Source #

Deprecated: Please use read instead.

Same as read

toStreamRev :: (Monad m, Unbox a) => Array a -> Stream m a Source #

Deprecated: Please use readRev instead.

Same as readRev

read :: (Monad m, Unbox a) => Array a -> Stream m a Source #

Convert an Array into a stream.

Pre-release

readRev :: (Monad m, Unbox a) => Array a -> Stream m a Source #

Convert an Array into a stream in reverse order.

Pre-release

readerRev :: forall m a. (Monad m, Unbox a) => Unfold m (Array a) a Source #

Unfold an array into a stream in reverse order.

toList :: Unbox a => Array a -> [a] Source #

Convert an Array into a list.

Folds

writeWith :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) Source #

writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) Source #

writeN n folds a maximum of n elements from the input stream to an Array.

writeNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) Source #

Like writeN 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.

writeNAligned :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> Fold m a (Array a) Source #

writeNAligned alignment n folds a maximum of n elements from the input stream to an Array aligned to the given size.

Pre-release

write :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a) Source #

Fold the whole input to a single array.

Caution! Do not use this on infinite streams.

Streams of arrays

chunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (Array a) Source #

chunksOf n stream groups the elements in the input stream into arrays of n elements each.

Same as the following but may be more efficient:

>>> chunksOf n = Stream.foldMany (Array.writeN n)

Pre-release

bufferChunks :: (MonadIO m, Unbox a) => Stream m a -> m (StreamK m (Array a)) Source #

flattenArrays :: forall m a. (MonadIO m, Unbox a) => Stream m (Array a) -> Stream m a Source #

Use the "read" unfold instead.

flattenArrays = unfoldMany read

We can try this if there are any fusion issues in the unfold.

flattenArraysRev :: forall m a. (MonadIO m, Unbox a) => Stream m (Array a) -> Stream m a Source #

Use the "readRev" unfold instead.

flattenArrays = unfoldMany readRev

We can try this if there are any fusion issues in the unfold.