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.Type

Description

 
Synopsis

Documentation

data Array a Source #

Constructors

Array ByteArray# Int Int 

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

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

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.

nil :: Prim a => Array a Source #

Construction

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

Splice two immutable arrays creating a new immutable array.

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

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

fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a) Source #

fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a) Source #

Streams of arrays

fromStreamDArraysOf :: (MonadIO m, Prim 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 #

Constructors

OuterLoop s 
InnerLoop s !(Array a) !Int !Int 

flattenArrays :: (MonadIO m, Prim a) => Stream m (Array a) -> Stream m a Source #

data SpliceState s arr1 arr2 Source #

Constructors

SpliceInitial s 
SpliceBuffering s arr2 
SpliceYielding arr1 (SpliceState s arr1 arr2) 
SpliceFinish 

packArraysChunksOf :: forall m a. (MonadIO m, Prim 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 in bytes. 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.

Pre-release

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

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.

Pre-release

Elimination

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

byteLength :: forall a. Prim a => Array a -> Int Source #

foldl' :: Prim a => (b -> a -> b) -> b -> Array a -> b Source #

Strict left-associated fold over the elements of an Array.

foldr :: Prim a => (a -> b -> b) -> b -> Array a -> b Source #

foldr' :: Prim a => (a -> b -> b) -> b -> Array a -> b Source #

Strict right-associated fold over the elements of an Array.

foldlM' :: (Prim a, Monad m) => (b -> a -> m b) -> b -> Array a -> m b Source #

Strict left-associated fold over the elements of an Array.

splitAt :: Int -> [a] -> ([a], [a]) #

splitAt n xs returns a tuple where first element is xs prefix of length n and second element is the remainder of the list:

>>> splitAt 6 "Hello World!"
("Hello ","World!")
>>> splitAt 3 [1,2,3,4,5]
([1,2,3],[4,5])
>>> splitAt 1 [1,2,3]
([1],[2,3])
>>> splitAt 3 [1,2,3]
([1,2,3],[])
>>> splitAt 4 [1,2,3]
([1,2,3],[])
>>> splitAt 0 [1,2,3]
([],[1,2,3])
>>> splitAt (-1) [1,2,3]
([],[1,2,3])

It is equivalent to (take n xs, drop n xs) when n is not _|_ (splitAt _|_ xs = _|_). splitAt is an instance of the more general genericSplitAt, in which n may be of any integral type.

toStreamD :: (Prim a, Monad m) => Array a -> Stream m a Source #

toStreamDRev :: (Prim a, Monad m) => Array a -> Stream m a Source #

toStreamK :: Prim a => Array a -> Stream m a Source #

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

Convert an Array into a list.

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

data ArrayUnsafe a Source #

Constructors

ArrayUnsafe !(Array a) !Int 

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

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

unlines :: (MonadIO m, Prim a) => a -> Stream m (Array a) -> Stream m a Source #

toPtr :: Array a -> Ptr a Source #

withArrayAsPtr :: Array a -> (Ptr a -> IO b) -> IO b Source #