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

Streamly.Internal.Data.Array

Description

 
Synopsis

Setup

>>> :m
>>> :set -XFlexibleContexts
>>> import Data.Function ((&))
>>> import Data.Functor.Identity (Identity(..))
>>> import System.IO.Unsafe (unsafePerformIO)
>>> import Streamly.Data.Array (Array)
>>> import Streamly.Data.Stream (Stream)
>>> import qualified Streamly.Data.Array as Array
>>> import qualified Streamly.Data.Fold as Fold
>>> import qualified Streamly.Data.Stream as Stream

Design Notes

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.

The Array Type

data Array a Source #

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

Construction

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.

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

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

fromStreamN :: (MonadIO m, Unbox a) => Int -> Stream 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, Unbox a) => Stream 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, chunksOf followed by processing of indvidual arrays in the resulting stream should be preferred.

Pre-release

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.

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.

writeLastN :: (Storable a, Unbox 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.

Elimination

Conversion

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

Convert an Array into a list.

Streams

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

Unfolds

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

Unfold an array into a stream.

readerUnsafe :: forall m a. (Monad m, Unbox 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

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

Unfold an array into a stream in reverse order.

producer :: forall m a. (Monad m, Unbox a) => Producer m (Array a) a Source #

Random Access

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

O(1) Lookup the element at the given index. Index starts from 0.

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

Return element at the specified index without checking the bounds.

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

Like getIndex but indexes the array in reverse from the end.

Pre-release

last :: Unbox a => Array a -> Maybe a Source #

>>> import qualified Streamly.Internal.Data.Array as Array
>>> last arr = Array.getIndexRev arr 0

Pre-release

getIndices :: (Monad m, Unbox a) => Stream 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 :: Unbox a => Array a -> Int Source #

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

null :: Array a -> Bool Source #

>>> import qualified Streamly.Internal.Data.Array.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. Unbox 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.

asBytes :: Array a -> Array Word8 Source #

Cast an Array a into an Array Word8.

castUnsafe :: 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.

See asPtrUnsafe in the Mutable array module for more details.

Unsafe

Pre-release

asCStringUnsafe :: 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 :: 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

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

Subarrays

getSliceUnsafe Source #

Arguments

:: forall a. Unbox a 
=> Int

starting index

-> Int

length of the slice

-> Array a 
-> Array a 

O(1) Slice an array in constant time.

Caution: The bounds of the slice are not checked.

Unsafe

Pre-release

genSlicesFromLen Source #

Arguments

:: forall m a. (Monad m, Unbox a) 
=> Int

from index

-> Int

length of the slice

-> Unfold m (Array a) (Int, Int) 

getSlicesFromLen Source #

Arguments

:: forall m a. (Monad m, Unbox 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, Unbox a) => (a -> Bool) -> Array a -> Stream 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, Unbox a, Unbox b) => (Stream m a -> Stream m b) -> Array a -> m (Array b) Source #

Transform an array into another array using a stream transformation operation.

Pre-release

Folding

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

Fold an array using a stream fold operation.

Pre-release

fold :: forall m a b. (Monad m, Unbox a) => Fold m a b -> Array a -> m b Source #

Fold an array using a Fold.

Pre-release

Deprecated

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