Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD3-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
See notes in Streamly.Internal.Data.Array.Foreign.Mut.Type
Synopsis
- data Array a = Array {
- aStart :: !(ForeignPtr a)
- aEnd :: !(Ptr a)
- unsafeFreeze :: Array a -> Array a
- unsafeFreezeWithShrink :: Storable a => Array a -> Array a
- unsafeThaw :: Array a -> Array a
- spliceTwo :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a)
- fromPtr :: Int -> Ptr a -> Array a
- fromAddr# :: Int -> Addr# -> Array a
- fromCString# :: Addr# -> Array Word8
- fromList :: Storable a => [a] -> Array a
- fromListN :: Storable a => Int -> [a] -> Array a
- fromStreamDN :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> m (Array a)
- fromStreamD :: forall m a. (MonadIO m, Storable a) => Stream m a -> m (Array a)
- breakOn :: MonadIO m => Word8 -> Array Word8 -> m (Array Word8, Maybe (Array Word8))
- unsafeIndexIO :: forall a. Storable a => Array a -> Int -> IO a
- unsafeIndex :: forall a. Storable a => Array a -> Int -> a
- byteLength :: Array a -> Int
- length :: forall a. Storable a => Array a -> Int
- foldl' :: forall a b. Storable a => (b -> a -> b) -> b -> Array a -> b
- foldr :: Storable a => (a -> b -> b) -> b -> Array a -> b
- splitAt :: forall a. Storable a => Int -> Array a -> (Array a, Array a)
- readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a
- toStreamD :: forall m a. (Monad m, Storable a) => Array a -> Stream m a
- toStreamDRev :: forall m a. (Monad m, Storable a) => Array a -> Stream m a
- toStreamK :: forall t m a. (IsStream t, Storable a) => Array a -> t m a
- toStreamKRev :: forall t m a. (IsStream t, Storable a) => Array a -> t m 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
- toList :: Storable a => Array a -> [a]
- toArrayMinChunk :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a)
- writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a)
- writeNUnsafe :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a)
- data ArrayUnsafe a = ArrayUnsafe !(ForeignPtr a) !(Ptr a)
- writeNAligned :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a)
- writeNAlignedUnmanaged :: 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)
- writeAligned :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a)
- arraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a)
- bufferChunks :: (MonadIO m, Storable a) => Stream m a -> m (Stream m (Array a))
- flattenArrays :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a
- flattenArraysRev :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a
- defaultChunkSize :: Int
- mkChunkSize :: Int -> Int
- mkChunkSizeKB :: Int -> Int
- unsafeInlineIO :: IO a -> a
- memcpy :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
- memcmp :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool
- bytesToElemCount :: Storable a => a -> Int -> Int
Documentation
We can use a Storable
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.
XXX Rename the fields to better names.
Array | |
|
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 # | |
(Storable a, NFData a) => 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 |
Freezing and Thawing
unsafeFreeze :: Array a -> Array a Source #
Returns an immutable array using the same underlying pointers of the mutable array. If the underlying array is mutated, the immutable promise is lost. Please make sure that the mutable array is never used after freezing it using unsafeFreeze.
unsafeFreezeWithShrink :: Storable a => Array a -> Array a Source #
Similar to unsafeFreeze
but uses shrinkToFit
on the mutable array
first.
unsafeThaw :: Array a -> Array a Source #
Returns a mutable array using the same underlying pointers of the immutable array. If the resulting array is mutated, the older immutable array is mutated as well. Please make sure that the immutable array is never used after thawing it using unsafeThaw.
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
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
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
Split
Elimination
unsafeIndexIO :: forall a. Storable a => Array a -> Int -> 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. Storable a => Array a -> Int -> 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.
Since: 0.7.0
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
splitAt :: forall a. Storable 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.
Since: 0.7.0
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
toStream :: (Monad m, IsStream t, Storable a) => Array a -> t m a Source #
Convert an Array
into a stream.
Pre-release
toStreamRev :: (Monad m, IsStream t, Storable a) => Array a -> t m a Source #
Convert an Array
into a stream in reverse order.
Pre-release
Folds
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
writeNUnsafe :: forall m a. (MonadIO m, Storable 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.
Since: 0.7.0
data ArrayUnsafe a Source #
ArrayUnsafe !(ForeignPtr a) !(Ptr a) |
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
writeNAlignedUnmanaged :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) Source #
writeNAlignedUnmanaged n
folds a maximum of n
elements from the input
stream to an Array
aligned to the given size and using unmanaged memory.
This could be useful to allocate memory that we need to allocate only once
in the lifetime of the program.
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
writeAligned :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) Source #
Like write
but the array memory is aligned according to the specified
alignment size. This could be useful when we have specific alignment, for
example, cache aligned arrays for lookup table etc.
Caution! Do not use this on infinite streams.
Since: 0.7.0
Streams of arrays
arraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a) Source #
arraysOf n stream
groups the input stream into a stream of
arrays of size n.
flattenArrays :: forall m a. (MonadIO m, Storable 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, Storable 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.
Utilities
defaultChunkSize :: Int Source #
Default maximum buffer size in bytes, for reading from and writing to IO devices, the value is 32KB minus GHC allocation overhead, which is a few bytes, so that the actual allocation is 32KB.
mkChunkSize :: Int -> Int Source #
mkChunkSizeKB :: Int -> Int Source #
unsafeInlineIO :: IO a -> a Source #