vector-0.10.12.2: Efficient Arrays

Copyright(c) Roman Leshchinskiy 2008-2010
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Fusion.Stream.Monadic

Contents

Description

Monadic stream combinators.

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

data SPEC Source

Constructors

SPEC 
SPEC2 

Size hints

size :: Stream m a -> Size Source

Size hint of a Stream

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

Attach a Size hint to a Stream

Length

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

Length of a Stream

null :: Monad m => Stream m a -> m Bool Source

Check if a Stream is empty

Construction

empty :: Monad m => Stream m a Source

Empty Stream

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

Singleton Stream

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

Prepend an element

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

Append an element

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

Replicate a value to a given length

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

Yield a Stream of values obtained by performing the monadic action the given number of times

generate :: Monad m => Int -> (Int -> a) -> Stream m a Source

generateM :: Monad m => Int -> (Int -> m a) -> Stream m a Source

Generate a stream from its indices

(++) :: Monad m => Stream m a -> Stream m a -> Stream m a infixr 5 Source

Concatenate two Streams

Accessing elements

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

First element of the Stream or error if empty

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

Last element of the Stream or error if empty

(!!) :: Monad m => Stream m a -> Int -> m a infixl 9 Source

Element at the given position

(!?) :: Monad m => Stream m a -> Int -> m (Maybe a) infixl 9 Source

Element at the given position or Nothing if out of bounds

Substreams

slice Source

Arguments

:: Monad m 
=> Int

starting index

-> Int

length

-> Stream m a 
-> Stream m a 

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

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

All but the last element

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

All but the first element

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

The first n elements

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

All but the first n elements

Mapping

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

Map a function over a Stream

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

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' a Source

Transform a Stream to use a different monad

unbox :: Monad m => Stream m (Box a) -> Stream m a Source

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

flatten :: Monad m => (a -> m s) -> (s -> m (Step s b)) -> Size -> Stream m a -> Stream m b Source

Create a Stream of values from a Stream of streamable things

Zipping

indexed :: Monad m => Stream m a -> Stream m (Int, a) Source

Pair each element in a Stream with its index

indexedR :: Monad m => Int -> Stream m a -> Stream m (Int, a) Source

Pair each element in a Stream with its index, starting from the right and counting down

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

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

Zip two Streams with the given monadic function

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

zipWith4M :: Monad m => (a -> b -> c -> d -> m e) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e Source

zipWith5M :: Monad m => (a -> b -> c -> d -> e -> m f) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e -> Stream m f Source

zipWith6M :: Monad m => (a -> b -> c -> d -> e -> f -> m g) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e -> Stream m f -> Stream m g Source

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

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

zipWith4 :: Monad m => (a -> b -> c -> d -> e) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e Source

zipWith5 :: Monad m => (a -> b -> c -> d -> e -> f) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e -> Stream m f Source

zipWith6 :: Monad m => (a -> b -> c -> d -> e -> f -> g) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e -> Stream m f -> Stream m g Source

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

zip3 :: Monad m => Stream m a -> Stream m b -> Stream m c -> Stream m (a, b, c) Source

zip4 :: Monad m => Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m (a, b, c, d) Source

zip5 :: Monad m => Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e -> Stream m (a, b, c, d, e) Source

zip6 :: Monad m => Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e -> Stream m f -> Stream m (a, b, c, d, e, f) Source

Filtering

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

Drop elements which do not satisfy the predicate

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

Drop elements which do not satisfy the monadic predicate

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

Longest prefix of elements that satisfy the predicate

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

Longest prefix of elements that satisfy the monadic predicate

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

Drop the longest prefix of elements that satisfy the predicate

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

Drop the longest prefix of elements that satisfy the monadic predicate

Searching

elem :: (Monad m, Eq a) => a -> Stream m a -> m Bool infix 4 Source

Check whether the Stream contains an element

notElem :: (Monad m, Eq a) => a -> Stream m a -> m Bool infix 4 Source

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 a Source

Left fold

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

Left fold with a monadic operator

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

Left fold over a non-empty Stream

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

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

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

Same as foldlM

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

Same as foldl1M

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

Left fold with a strict accumulator

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

Left fold with a strict accumulator and a monadic operator

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

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

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

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 a Source

Same as foldlM'

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

Same as foldl1M'

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

Right fold

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

Right fold with a monadic operator

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

Right fold over a non-empty stream

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

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

Specialised folds

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

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

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

Unfolding

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

Unfold

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

Unfold with a monadic function

unfoldrN :: Monad m => Int -> (s -> Maybe (a, s)) -> s -> Stream m a Source

Unfold at most n elements

unfoldrNM :: Monad m => Int -> (s -> m (Maybe (a, s))) -> s -> Stream m a Source

Unfold at most n elements with a monadic functions

iterateN :: Monad m => Int -> (a -> a) -> a -> Stream m a Source

Apply function n times to value. Zeroth element is original value.

iterateNM :: Monad m => Int -> (a -> m a) -> a -> Stream m a Source

Apply monadic function n times to value. Zeroth element is original value.

Scans

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

Prefix scan

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

Prefix scan with a monadic operator

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

Prefix scan with strict accumulator

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

Prefix scan with strict accumulator and a monadic operator

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

Suffix scan

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

Suffix scan with a monadic operator

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

Suffix scan with strict accumulator

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

Suffix scan with strict acccumulator and a monadic operator

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

Haskell-style scan

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

Haskell-style scan with a monadic operator

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

Haskell-style scan with strict accumulator

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

Haskell-style scan with strict accumulator and a monadic operator

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

Scan over a non-empty Stream

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

Scan over a non-empty Stream with a monadic operator

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

Scan over a non-empty Stream with a strict accumulator

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

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

Enumerations

enumFromStepN :: (Num a, Monad m) => a -> a -> Int -> Stream m a Source

Yield a Stream of the given length containing the values x, x+y, x+y+y etc.

enumFromTo :: (Enum a, Monad m) => a -> a -> Stream m a Source

Enumerate values

WARNING: This operation can be very inefficient. If at all possible, use enumFromStepN instead.

enumFromThenTo :: (Enum a, Monad m) => a -> a -> a -> Stream m a Source

Enumerate values with a given step.

WARNING: This operation is very inefficient. If at all possible, use enumFromStepN instead.

Conversions

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

Convert a Stream to a list

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

Convert a list to a Stream

fromListN :: Monad m => Int -> [a] -> Stream m a Source

Convert the first n elements of a list to a Stream

unsafeFromList :: Monad m => Size -> [a] -> Stream m a Source

Convert a list to a Stream with the given Size hint.