vector-0.4.2: Efficient Arrays

Portabilitynon-portable
Stabilityexperimental
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>

Data.Vector.Fusion.Stream.Monadic

Contents

Description

Monadic streams

Synopsis

Documentation

data Stream m a Source

Monadic streams

Constructors

forall s . Stream (s -> m (Step s a)) s Size 

Instances

Monad m => Functor (Stream m) 
Eq a => Eq (Stream Id a) 
Ord a => Ord (Stream Id a) 

data Step s a Source

Result of taking a single step in a stream

Constructors

Yield a s

a new element and a new seed

Skip s

just a new seed

Done

end of stream

Size hints

size :: Stream m a -> SizeSource

Size hint of a Stream

sized :: Stream m a -> Size -> Stream m aSource

Attach a Size hint to a Stream

Length

length :: Monad m => Stream m a -> m IntSource

Length of a Stream

null :: Monad m => Stream m a -> m BoolSource

Check if a Stream is empty

Construction

empty :: Monad m => Stream m aSource

Empty Stream

singleton :: Monad m => a -> Stream m aSource

Singleton Stream

cons :: Monad m => a -> Stream m a -> Stream m aSource

Prepend an element

snoc :: Monad m => Stream m a -> a -> Stream m aSource

Append an element

replicate :: Monad m => Int -> a -> Stream m aSource

Replicate a value to a given length

(++) :: Monad m => Stream m a -> Stream m a -> Stream m aSource

Concatenate two Streams

Accessing elements

head :: Monad m => Stream m a -> m aSource

First element of the Stream or error if empty

last :: Monad m => Stream m a -> m aSource

Last element of the Stream or error if empty

(!!) :: Monad m => Stream m a -> Int -> m aSource

Element at the given position

Substreams

extractSource

Arguments

:: Monad m 
=> Stream m a 
-> Int

starting index

-> Int

length

-> Stream m a 

Extract a substream of the given length starting at the given position.

init :: Monad m => Stream m a -> Stream m aSource

All but the last element

tail :: Monad m => Stream m a -> Stream m aSource

All but the first element

take :: Monad m => Int -> Stream m a -> Stream m aSource

The first n elements

drop :: Monad m => Int -> Stream m a -> Stream m aSource

All but the first n elements

Mapping

map :: Monad m => (a -> b) -> Stream m a -> Stream m bSource

Map a function over a Stream

mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m bSource

Map a monadic function over a Stream

mapM_ :: Monad m => (a -> m b) -> Stream m a -> m ()Source

Execute a monadic action for each element of the Stream

trans :: (Monad m, Monad m') => (forall a. m a -> m' a) -> Stream m a -> Stream m' aSource

Transform a Stream to use a different monad

concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m bSource

Zipping

zipWith :: Monad m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m cSource

Zip two Streams with the given function

zipWithM :: Monad m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m cSource

Zip two Streams with the given monadic function

zipWith3 :: Monad m => (a -> b -> c -> d) -> Stream m a -> Stream m b -> Stream m c -> Stream m dSource

Zip three Streams with the given function

zipWith3M :: Monad m => (a -> b -> c -> m d) -> Stream m a -> Stream m b -> Stream m c -> Stream m dSource

Zip three Streams with the given monadic function

Filtering

filter :: Monad m => (a -> Bool) -> Stream m a -> Stream m aSource

Drop elements which do not satisfy the predicate

filterM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m aSource

Drop elements which do not satisfy the monadic predicate

takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m aSource

Longest prefix of elements that satisfy the predicate

takeWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m aSource

Longest prefix of elements that satisfy the monadic predicate

dropWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m aSource

Drop the longest prefix of elements that satisfy the predicate

dropWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m aSource

Drop the longest prefix of elements that satisfy the monadic predicate

Searching

elem :: (Monad m, Eq a) => a -> Stream m a -> m BoolSource

Check whether the Stream contains an element

notElem :: (Monad m, Eq a) => a -> Stream m a -> m BoolSource

Inverse of elem

find :: Monad m => (a -> Bool) -> Stream m a -> m (Maybe a)Source

Yield Just the first element that satisfies the predicate or Nothing if no such element exists.

findM :: Monad m => (a -> m Bool) -> Stream m a -> m (Maybe a)Source

Yield Just the first element that satisfies the monadic predicate or Nothing if no such element exists.

findIndex :: Monad m => (a -> Bool) -> Stream m a -> m (Maybe Int)Source

Yield Just the index of the first element that satisfies the predicate or Nothing if no such element exists.

findIndexM :: Monad m => (a -> m Bool) -> Stream m a -> m (Maybe Int)Source

Yield Just the index of the first element that satisfies the monadic predicate or Nothing if no such element exists.

Folding

foldl :: Monad m => (a -> b -> a) -> a -> Stream m b -> m aSource

Left fold

foldlM :: Monad m => (a -> b -> m a) -> a -> Stream m b -> m aSource

Left fold with a monadic operator

foldl1 :: Monad m => (a -> a -> a) -> Stream m a -> m aSource

Left fold over a non-empty Stream

foldl1M :: Monad m => (a -> a -> m a) -> Stream m a -> m aSource

Left fold over a non-empty Stream with a monadic operator

foldM :: Monad m => (a -> b -> m a) -> a -> Stream m b -> m aSource

Same as foldlM

fold1M :: Monad m => (a -> a -> m a) -> Stream m a -> m aSource

Same as foldl1M

foldl' :: Monad m => (a -> b -> a) -> a -> Stream m b -> m aSource

Left fold with a strict accumulator

foldlM' :: Monad m => (a -> b -> m a) -> a -> Stream m b -> m aSource

Left fold with a strict accumulator and a monadic operator

foldl1' :: Monad m => (a -> a -> a) -> Stream m a -> m aSource

Left fold over a non-empty Stream with a strict accumulator

foldl1M' :: Monad m => (a -> a -> m a) -> Stream m a -> m aSource

Left fold over a non-empty Stream with a strict accumulator and a monadic operator

foldM' :: Monad m => (a -> b -> m a) -> a -> Stream m b -> m aSource

Same as foldlM'

fold1M' :: Monad m => (a -> a -> m a) -> Stream m a -> m aSource

Same as foldl1M'

foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m bSource

Right fold

foldrM :: Monad m => (a -> b -> m b) -> b -> Stream m a -> m bSource

Right fold with a monadic operator

foldr1 :: Monad m => (a -> a -> a) -> Stream m a -> m aSource

Right fold over a non-empty stream

foldr1M :: Monad m => (a -> a -> m a) -> Stream m a -> m aSource

Right fold over a non-empty stream with a monadic operator

Specialised folds

and :: Monad m => Stream m Bool -> m BoolSource

or :: Monad m => Stream m Bool -> m BoolSource

concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m bSource

Unfolding

unfoldr :: Monad m => (s -> Maybe (a, s)) -> s -> Stream m aSource

Unfold

unfoldrM :: Monad m => (s -> m (Maybe (a, s))) -> s -> Stream m aSource

Unfold with a monadic function

Scans

prescanl :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m aSource

Prefix scan

prescanlM :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m aSource

Prefix scan with a monadic operator

prescanl' :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m aSource

Prefix scan with strict accumulator

prescanlM' :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m aSource

Prefix scan with strict accumulator and a monadic operator

postscanl :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m aSource

Suffix scan

postscanlM :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m aSource

Suffix scan with a monadic operator

postscanl' :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m aSource

Suffix scan with strict accumulator

postscanlM' :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m aSource

Suffix scan with strict acccumulator and a monadic operator

scanl :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m aSource

Haskell-style scan

scanlM :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m aSource

Haskell-style scan with a monadic operator

scanl' :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m aSource

Haskell-style scan with strict accumulator

scanlM' :: Monad m => (a -> b -> m a) -> a -> Stream m b -> Stream m aSource

Haskell-style scan with strict accumulator and a monadic operator

scanl1 :: Monad m => (a -> a -> a) -> Stream m a -> Stream m aSource

Scan over a non-empty Stream

scanl1M :: Monad m => (a -> a -> m a) -> Stream m a -> Stream m aSource

Scan over a non-empty Stream with a monadic operator

scanl1' :: Monad m => (a -> a -> a) -> Stream m a -> Stream m aSource

Scan over a non-empty Stream with a strict accumulator

scanl1M' :: Monad m => (a -> a -> m a) -> Stream m a -> Stream m aSource

Scan over a non-empty Stream with a strict accumulator and a monadic operator

Conversions

toList :: Monad m => Stream m a -> m [a]Source

Convert a Stream to a list

fromList :: Monad m => [a] -> Stream m aSource

Convert a list to a Stream