Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
To summarize:
- Arrays are finite and fixed in size
- provide O(1) access to elements
- store only data and not functions
- provide efficient IO interfacing
Foldable
instance is not provided because the implementation would be much
less efficient compared to folding via streams. Semigroup
and Monoid
instances should be used with care; concatenating arrays using binary
operations can be highly inefficient. Instead, use
toArray
to concatenate N arrays at
once.
Each array is one pointer visible to the GC. Too many small arrays (e.g. single byte) are only as good as holding those elements in a Haskell list. However, small arrays can be compacted into large ones to reduce the overhead. To hold 32GB memory in 32k sized buffers we need 1 million arrays if we use one array for each chunk. This is still significant to add pressure to GC.
Synopsis
- data Array a
- fromListN :: Storable a => Int -> [a] -> Array a
- fromList :: Storable a => [a] -> Array a
- fromStreamN :: (MonadIO m, Storable a) => Int -> SerialT m a -> m (Array a)
- fromStream :: (MonadIO m, Storable a) => SerialT m a -> m (Array a)
- writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a)
- writeNAligned :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a)
- write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a)
- toList :: Storable a => Array a -> [a]
- toStream :: (Monad m, IsStream t, Storable a) => Array a -> t m a
- toStreamRev :: (Monad m, IsStream t, Storable a) => Array a -> t m a
- read :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a
- unsafeRead :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a
- length :: forall a. Storable a => Array a -> Int
- null :: Storable a => Array a -> Bool
- last :: Storable a => Array a -> Maybe a
- readIndex :: Storable a => Array a -> Int -> Maybe a
- unsafeIndex :: forall a. Storable a => Array a -> Int -> a
- writeIndex :: (MonadIO m, Storable a) => Array a -> Int -> a -> m ()
- streamTransform :: forall m a b. (MonadIO m, Storable a, Storable b) => (SerialT m a -> SerialT m b) -> Array a -> m (Array b)
- streamFold :: (MonadIO m, Storable a) => (SerialT m a -> m b) -> Array a -> m b
- fold :: forall m a b. (MonadIO m, Storable a) => Fold m a b -> Array a -> m b
- lastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a)
Documentation
Instances
Storable a => IsList (Array a) Source # | |
(Storable a, Eq a) => Eq (Array a) Source # | |
(Storable a, Ord a) => Ord (Array a) Source # | |
Defined in Streamly.Internal.Memory.Array.Types | |
(Storable a, Read a, Show a) => Read (Array a) Source # | |
(Show a, Storable a) => Show (Array a) Source # | |
a ~ Char => IsString (Array a) Source # | |
Defined in Streamly.Internal.Memory.Array.Types fromString :: String -> Array a # | |
Storable a => Semigroup (Array a) Source # | |
Storable a => Monoid (Array a) Source # | |
(Storable a, NFData a) => NFData (Array a) Source # | |
Defined in Streamly.Internal.Memory.Array.Types | |
type Item (Array a) Source # | |
Defined in Streamly.Internal.Memory.Array.Types |
Construction
fromListN :: Storable 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.
Since: 0.7.0
fromList :: Storable a => [a] -> Array a Source #
Create an Array
from a list. The list must be of finite size.
Since: 0.7.0
fromStreamN :: (MonadIO m, Storable a) => Int -> SerialT m a -> m (Array a) Source #
Create an Array
from the first N elements of a stream. The array is
allocated to size N, if the stream terminates before N elements then the
array may hold less than N elements.
Internal
fromStream :: (MonadIO m, Storable a) => SerialT m a -> m (Array a) Source #
Create an Array
from a stream. This is useful when we want to create a
single array from a stream of unknown size. writeN
is at least twice
as efficient when the size is already known.
Note that if the input stream is too large memory allocation for the array
may fail. When the stream size is not known, arraysOf
followed by
processing of indvidual arrays in the resulting stream should be preferred.
Internal
writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) Source #
writeN n
folds a maximum of n
elements from the input stream to an
Array
.
Since: 0.7.0
writeNAligned :: forall m a. (MonadIO m, Storable 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.
Internal
write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) Source #
Fold the whole input to a single array.
Caution! Do not use this on infinite streams.
Since: 0.7.0
Elimination
toStream :: (Monad m, IsStream t, Storable a) => Array a -> t m a Source #
Convert an Array
into a stream.
Internal
toStreamRev :: (Monad m, IsStream t, Storable a) => Array a -> t m a Source #
Convert an Array
into a stream in reverse order.
Internal
read :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a Source #
Unfold an array into a stream.
Since: 0.7.0
unsafeRead :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a Source #
Unfold an array into a stream, does not check the end of the array, the user is responsible for terminating the stream within the array bounds. For high performance application where the end condition can be determined by a terminating fold.
Written in the hope that it may be faster than "read", however, in the case for which this was written, "read" proves to be faster even though the core generated with unsafeRead looks simpler.
Internal
Random Access
length :: forall a. Storable a => Array a -> Int Source #
O(1) Get the length of the array i.e. the number of elements in the array.
Since: 0.7.0
readIndex :: Storable a => Array a -> Int -> Maybe a Source #
O(1) Lookup the element at the given index, starting from 0.
Internal
unsafeIndex :: forall a. Storable a => Array a -> Int -> a Source #
Return element at the specified index without checking the bounds.
writeIndex :: (MonadIO m, Storable a) => Array a -> Int -> a -> m () Source #
O(1) Write the given element at the given index in the array. Performs in-place mutation of the array.
Internal
Immutable Transformations
streamTransform :: forall m a b. (MonadIO m, Storable a, Storable b) => (SerialT m a -> SerialT m b) -> Array a -> m (Array b) Source #
Transform an array into another array using a stream transformation operation.
Internal
Folding Arrays
streamFold :: (MonadIO m, Storable a) => (SerialT m a -> m b) -> Array a -> m b Source #
Fold an array using a stream fold operation.
Internal
fold :: forall m a b. (MonadIO m, Storable a) => Fold m a b -> Array a -> m b Source #
Fold an array using a Fold
.
Internal