streamly-0.8.3: Dataflow programming and declarative concurrency
Copyright(c) 2020 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Array.Prim.Pinned

Description

 
Synopsis

Documentation

data Array a Source #

Instances

Instances details
a ~ Char => IsString (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

Methods

fromString :: String -> Array a #

Prim a => Monoid (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

Prim a => Semigroup (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Prim a => IsList (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.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)] #

(Prim a, Read a, Show a) => Read (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

(Show a, Prim a) => Show (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

NFData (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

Methods

rnf :: Array a -> () #

(Eq a, Prim a) => Eq (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.Type

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

(Ord a, Prim a) => Ord (Array a) Source #

Lexicographic ordering. Subject to change between major versions.

Instance details

Defined in Streamly.Internal.Data.Array.Prim.Pinned.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.Prim.Pinned.Type

type Item (Array a) = a

Construction

fromListN :: Prim a => Int -> [a] -> Array a Source #

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

fromStreamN :: (MonadIO m, Prim 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, Prim 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 :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) Source #

writeN n folds a maximum of n elements from the input stream to an Array.

Pre-release

write :: (MonadIO m, Prim a) => Fold m a (Array a) Source #

Fold the whole input to a single array.

Caution! Do not use this on infinite streams.

Pre-release

Elimination

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

Convert an Array into a list.

Pre-release

toStream :: (MonadIO m, Prim a) => Array a -> SerialT m a Source #

Convert an Array into a stream.

Pre-release

toStreamRev :: (MonadIO m, Prim a) => Array a -> SerialT m a Source #

Convert an Array into a stream in reverse order.

Pre-release

read :: (MonadIO m, Prim a) => Unfold m (Array a) a Source #

Unfold an array into a stream.

Since: 0.7.0

unsafeRead :: (MonadIO m, Prim 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.

The following might not be true, not that the representation changed. 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

Random Access

null :: Array a -> Bool Source #

null arr = length arr == 0

Pre-release

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

last arr = readIndex arr (length arr - 1)

Pre-release

readIndex :: Prim a => Array a -> Int -> Maybe a Source #

O(1) Lookup the element at the given index, starting from 0.

Pre-release

unsafeIndex :: Prim a => Array a -> Int -> a Source #

Immutable Transformations

Folding Arrays

streamFold :: (MonadIO m, Prim a) => (SerialT m a -> m b) -> Array a -> m b Source #

Fold an array using a stream fold operation.

Pre-release

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

Fold an array using a Fold.

Pre-release

Folds with Array as the container

Streaming array operations

concat :: (MonadIO m, Prim a) => SerialT m (Array a) -> SerialT m a Source #

Convert a stream of arrays into a stream of their elements.

Same as the following but more efficient:

concat = S.concatMap A.read

Pre-release

compact :: (MonadIO m, Prim a) => Int -> SerialT m (Array a) -> SerialT m (Array a) Source #

Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size in bytes.

Pre-release