streamly-core-0.2.2: Streaming, parsers, arrays, serialization and more
Copyright(c) 2019 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Array.Generic

Description

 
Synopsis

Documentation

data Array a Source #

Constructors

Array 

Fields

Instances

Instances details
Read a => Read (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Generic

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

Defined in Streamly.Internal.Data.Array.Generic

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

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

Defined in Streamly.Internal.Data.Array.Generic

Methods

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

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

Ord a => Ord (Array a) Source # 
Instance details

Defined in Streamly.Internal.Data.Array.Generic

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 #

Construction

createOf :: MonadIO m => Int -> Fold m a (Array a) Source #

create :: MonadIO m => Fold m a (Array a) Source #

Fold the whole input to a single array.

Caution! Do not use this on infinite streams.

writeWith :: MonadIO m => Int -> Fold m a (Array a) Source #

writeLastN :: MonadIO m => Int -> Fold m a (Array a) Source #

fromStreamN :: MonadIO m => Int -> Stream m a -> m (Array a) Source #

fromStream :: MonadIO m => Stream m a -> m (Array a) Source #

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

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

chunksOf :: forall m a. MonadIO m => Int -> Stream m a -> Stream m (Array a) Source #

Elimination

reader :: Monad m => Unfold m (Array a) a Source #

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

read :: Monad m => Array a -> Stream m a Source #

readRev :: Monad m => Array a -> Stream m a Source #

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

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

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

fold :: Monad m => Fold m a b -> Array a -> m b Source #

Random Access

getIndexUnsafe :: Int -> Array a -> a Source #

O(1) Lookup the element at the given index. Index starts from 0. Does not check the bounds.

Since: 0.8.0

getIndex :: Int -> Array a -> Maybe a Source #

Lookup the element at the given index. Index starts from 0.

strip :: (a -> Bool) -> Array a -> Array a Source #

Truncate the array at the beginning and end as long as the predicate holds true. Returns a slice of the original array.

Deprecated

writeN :: MonadIO m => Int -> Fold m a (Array a) Source #

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