Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Array a = Array {}
- withNewArray :: forall a. Storable a => Int -> (Ptr a -> IO ()) -> IO (Array a)
- newArray :: forall a. Storable a => Int -> IO (Array a)
- unsafeSnoc :: forall a. Storable a => Array a -> a -> IO (Array a)
- snoc :: forall a. Storable a => Array a -> a -> IO (Array a)
- spliceWithDoubling :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a)
- spliceTwo :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a)
- 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)
- fromStreamDArraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a)
- data FlattenState s a
- = OuterLoop s
- | InnerLoop s !(ForeignPtr a) !(Ptr a) !(Ptr 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
- packArraysChunksOf :: (MonadIO m, Storable a) => Int -> Stream m (Array a) -> Stream m (Array a)
- lpackArraysChunksOf :: (MonadIO m, Storable a) => Int -> Fold m (Array a) () -> Fold m (Array a) ()
- groupIOVecsOf :: MonadIO m => Int -> Int -> Stream m (Array a) -> Stream m (Array IOVec)
- splitOn :: MonadIO m => Word8 -> Stream m (Array Word8) -> Stream m (Array Word8)
- 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
- length :: forall a. Storable a => Array a -> Int
- byteLength :: Array a -> Int
- byteCapacity :: 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)
- 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
- 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)
- 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)
- defaultChunkSize :: Int
- mkChunkSize :: Int -> Int
- mkChunkSizeKB :: Int -> Int
- unsafeInlineIO :: IO a -> a
- realloc :: forall a. Storable a => Int -> Array a -> IO (Array a)
- shrinkToFit :: forall a. Storable a => Array a -> IO (Array a)
- memcpy :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
- memcmp :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool
- bytesToElemCount :: Storable a => a -> Int -> Int
- unlines :: forall m a. (MonadIO m, Storable a) => a -> Stream m (Array a) -> Stream m 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
withNewArray :: forall a. Storable a => Int -> (Ptr a -> IO ()) -> IO (Array a) Source #
Allocate an Array of the given size and run an IO action passing the array start pointer.
newArray :: forall a. Storable a => Int -> IO (Array a) Source #
Allocate an array that can hold count
items. The memory of the array is
uninitialized.
Note that this is internal routine, the reference to this array cannot be given out until the array has been written to and frozen.
fromList :: Storable a => [a] -> Array a Source #
Create an Array
from a list. The list must be of finite size.
Since: 0.7.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
Streams of arrays
fromStreamDArraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a) Source #
fromStreamArraysOf n stream
groups the input stream into a stream of
arrays of size n.
data FlattenState s a Source #
OuterLoop s | |
InnerLoop s !(ForeignPtr a) !(Ptr a) !(Ptr a) |
flattenArraysRev :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a Source #
packArraysChunksOf :: (MonadIO m, Storable a) => Int -> Stream m (Array a) -> Stream m (Array a) Source #
Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size. Note that if a single array is bigger than the specified size we do not split it to fit. When we coalesce multiple arrays if the size would exceed the specified size we do not coalesce therefore the actual array size may be less than the specified chunk size.
Since: 0.7.0
lpackArraysChunksOf :: (MonadIO m, Storable a) => Int -> Fold m (Array a) () -> Fold m (Array a) () Source #
groupIOVecsOf :: MonadIO m => Int -> Int -> Stream m (Array a) -> Stream m (Array IOVec) Source #
groupIOVecsOf maxBytes maxEntries
groups arrays in the incoming stream
to create a stream of IOVec
arrays with a maximum of maxBytes
bytes in
each array and a maximum of maxEntries
entries in each array.
Since: 0.7.0
splitOn :: MonadIO m => Word8 -> Stream m (Array Word8) -> Stream m (Array Word8) Source #
Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.
Since: 0.7.0
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.
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
byteLength :: Array a -> Int Source #
O(1) Get the byte length of the array.
Since: 0.7.0
byteCapacity :: Array a -> Int Source #
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
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
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
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
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.
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
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
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 #