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
- fromPtr :: Int -> Ptr a -> Array a
- fromAddr# :: Int -> Addr# -> Array a
- fromCString# :: Addr# -> Array Word8
- 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)
- writeLastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a)
- toList :: Storable a => Array a -> [a]
- toStream :: (Monad m, Storable a) => Array a -> SerialT m a
- toStreamRev :: (Monad m, Storable a) => Array a -> SerialT 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
- readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a
- producer :: forall m a. (Monad m, Storable a) => Producer m (Array a) a
- getIndex :: forall a. Storable a => Array a -> Int -> Maybe a
- unsafeIndex :: forall a. Storable a => Int -> Array a -> a
- getIndexRev :: forall a. Storable a => Int -> Array a -> Maybe a
- last :: Storable a => Array a -> Maybe a
- getIndices :: (Monad m, Storable a) => SerialT m Int -> Unfold m (Array a) a
- getIndicesFromThenTo :: Unfold m (Int, Int, Int, Array a) a
- length :: forall a. Storable a => Array a -> Int
- null :: Array a -> Bool
- binarySearch :: a -> Array a -> Maybe Int
- findIndicesOf :: (a -> Bool) -> Unfold Identity (Array a) Int
- cast :: forall a b. Storable b => Array a -> Maybe (Array b)
- asBytes :: Array a -> Array Word8
- unsafeCast :: Array a -> Array b
- asPtrUnsafe :: MonadIO m => Array a -> (Ptr a -> m b) -> m b
- unsafeAsCString :: Array a -> (CString -> IO b) -> IO b
- unsafeFreeze :: Array a -> Array a
- unsafeThaw :: Array a -> Array a
- getSliceUnsafe :: forall a. Storable a => Int -> Int -> Array a -> Array a
- genSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Int, Int)
- getSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Array a)
- splitOn :: (Monad m, Storable a) => (a -> Bool) -> Array a -> SerialT m (Array a)
- 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
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.Data.Array.Foreign.Type | |
(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.Data.Array.Foreign.Type fromString :: String -> Array a # | |
Storable a => Semigroup (Array a) Source # | |
Storable a => Monoid (Array a) Source # | |
NFData (Array a) Source # | |
Defined in Streamly.Internal.Data.Array.Foreign.Type | |
type Item (Array a) Source # | |
Defined in Streamly.Internal.Data.Array.Foreign.Type |
Construction
fromPtr :: Int -> Ptr a -> Array a Source #
Create an Array
of the given number of elements of type a
from a read
only pointer Ptr a
. The pointer is not freed when the array is garbage
collected. This API is unsafe for the following reasons:
- The pointer must point to static pinned memory or foreign memory that does not require freeing..
- The pointer must be legally accessible upto the given length.
- To guarantee that the array is immutable, the contents of the address must be guaranteed to not change.
Unsafe
Pre-release
fromAddr# :: Int -> Addr# -> Array a Source #
Create an Array Word8
of the given length from a static, read only
machine address Addr#
. See fromPtr
for safety caveats.
A common use case for this API is to create an array from a static unboxed
string literal. GHC string literals are of type Addr#
, and must contain
characters that can be encoded in a byte i.e. characters or literal bytes in
the range from 0-255.
>>>
import Data.Word (Word8)
>>>
Array.fromAddr# 5 "hello world!"# :: Array Word8
[104,101,108,108,111]
>>>
Array.fromAddr# 3 "\255\NUL\255"# :: Array Word8
[255,0,255]
See also: fromString#
Unsafe
Time complexity: O(1)
Pre-release
fromCString# :: Addr# -> Array Word8 Source #
Generate a byte array from an Addr#
that contains a sequence of NUL
(0
) terminated bytes. The array would not include the NUL byte. The
address must be in static read-only memory and must be legally accessible up
to and including the first NUL byte.
An unboxed string literal (e.g. "hello"#
) is a common example of an
Addr#
in static read only memory. It represents the UTF8 encoded sequence
of bytes terminated by a NUL byte (a CString
) corresponding to the
given unicode string.
>>>
Array.fromCString# "hello world!"#
[104,101,108,108,111,32,119,111,114,108,100,33]
>>>
Array.fromCString# "\255\NUL\255"#
[255]
See also: fromAddr#
Unsafe
Time complexity: O(n) (computes the length of the string)
Pre-release
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 (Streamly.Memory.Array)
Since: 0.8.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 (Streamly.Memory.Array)
Since: 0.8.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.
Pre-release
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.
Pre-release
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 (Streamly.Memory.Array)
Since: 0.8.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.
Pre-release
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 (Streamly.Memory.Array)
Since: 0.8.0
writeLastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a) Source #
writeLastN n
folds a maximum of n
elements from the end of the input
stream to an Array
.
Since: 0.8.0
Elimination
toStream :: (Monad m, Storable a) => Array a -> SerialT m a Source #
Convert an Array
into a stream.
Pre-release
toStreamRev :: (Monad m, Storable a) => Array a -> SerialT m a Source #
Convert an Array
into a stream in reverse order.
Pre-release
read :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a Source #
Unfold an array into a stream.
Since 0.7.0 (Streamly.Memory.Array)
Since: 0.8.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.
Pre-release
readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a Source #
Unfold an array into a stream in reverse order.
Since: 0.8.0
Random Access
getIndex :: forall a. Storable a => Array a -> Int -> Maybe a Source #
O(1) Lookup the element at the given index. Index starts from 0.
Since: 0.8.0
unsafeIndex :: forall a. Storable a => Int -> Array a -> a Source #
Return element at the specified index without checking the bounds.
getIndexRev :: forall a. Storable a => Int -> Array a -> Maybe a Source #
Like getIndex
but indexes the array in reverse from the end.
Pre-release
last :: Storable a => Array a -> Maybe a Source #
>>>
import qualified Streamly.Internal.Data.Array.Foreign as Array
>>>
last arr = Array.getIndexRev arr 0
Pre-release
getIndices :: (Monad m, Storable a) => SerialT m Int -> Unfold m (Array a) a Source #
Given a stream of array indices, read the elements on those indices from the supplied Array. An exception is thrown if an index is out of bounds.
This is the most general operation. We can implement other operations in terms of this:
read = let u = lmap (arr -> (0, length arr - 1)) Unfold.enumerateFromTo in Unfold.lmap f (getIndices arr) readRev = let i = length arr - 1 in Unfold.lmap f (getIndicesFromThenTo i (i - 1) 0)
Pre-release
getIndicesFromThenTo :: Unfold m (Int, Int, Int, Array a) a Source #
Unfolds (from, then, to, array)
generating a finite stream whose first
element is the array value from the index from
and the successive elements
are from the indices in increments of then
up to to
. Index enumeration
can occur downwards or upwards depending on whether then
comes before or
after from
.
getIndicesFromThenTo = let f (from, next, to, arr) = (Stream.enumerateFromThenTo from next to, arr) in Unfold.lmap f getIndices
Unimplemented
Size
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 (Streamly.Memory.Array)
Since: 0.8.0
null :: Array a -> Bool Source #
>>>
import qualified Streamly.Internal.Data.Array.Foreign.Type as Array
>>>
null arr = Array.byteLength arr == 0
Pre-release
Search
binarySearch :: a -> Array a -> Maybe Int Source #
Given a sorted array, perform a binary search to find the given element. Returns the index of the element if found.
Unimplemented
findIndicesOf :: (a -> Bool) -> Unfold Identity (Array a) Int Source #
Perform a linear search to find all the indices where a given element is present in an array.
Unimplemented
Casting
cast :: forall a b. Storable b => Array a -> Maybe (Array b) Source #
Cast an array having elements of type a
into an array having elements of
type b
. The length of the array should be a multiple of the size of the
target element otherwise Nothing
is returned.
Since: 0.8.0
unsafeCast :: Array a -> Array b Source #
Cast an array having elements of type a
into an array having elements of
type b
. The array size must be a multiple of the size of type b
otherwise accessing the last element of the array may result into a crash or
a random value.
Pre-release
asPtrUnsafe :: MonadIO m => Array a -> (Ptr a -> m b) -> m b Source #
Use an Array a
as Ptr a
.
Unsafe
Pre-release
unsafeAsCString :: Array a -> (CString -> IO b) -> IO b Source #
Convert an array of any type into a null terminated CString Ptr.
Unsafe
O(n) Time: (creates a copy of the array)
Pre-release
unsafeFreeze :: Array 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
unsafeThaw :: Array a -> Array 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
Subarrays
O(1) Slice an array in constant time.
Caution: The bounds of the slice are not checked.
Unsafe
Pre-release
:: forall m a. (Monad m, Storable a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (Array a) (Array a) |
Generate a stream of slices of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length.
Pre-release/
splitOn :: (Monad m, Storable a) => (a -> Bool) -> Array a -> SerialT m (Array a) Source #
Split the array into a stream of slices using a predicate. The element matching the predicate is dropped.
Pre-release
Streaming Operations
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.
Pre-release