vector-0.10.9.2: Efficient Arrays

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

Data.Vector.Fusion.Stream

Contents

Description

Streams for stream fusion

Synopsis

Types

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

type Stream = Stream Id Source

The type of pure streams

type MStream = Stream Source

Alternative name for monadic streams

In-place markers

inplace :: (forall m. Monad m => Stream m a -> Stream m b) -> Stream a -> Stream b Source

Size hints

size :: Stream a -> Size Source

Size hint of a Stream

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

Attach a Size hint to a Stream

Length information

length :: Stream a -> Int Source

Length of a Stream

null :: Stream a -> Bool Source

Check if a Stream is empty

Construction

singleton :: a -> Stream a Source

Singleton Stream

cons :: a -> Stream a -> Stream a Source

Prepend an element

snoc :: Stream a -> a -> Stream a Source

Append an element

replicate :: Int -> a -> Stream a Source

Replicate a value to a given length

generate :: Int -> (Int -> a) -> Stream a Source

Generate a stream from its indices

(++) :: Stream a -> Stream a -> Stream a infixr 5 Source

Concatenate two Streams

Accessing individual elements

head :: Stream a -> a Source

First element of the Stream or error if empty

last :: Stream a -> a Source

Last element of the Stream or error if empty

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

Element at the given position

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

Element at the given position or Nothing if out of bounds

Substreams

slice Source

Arguments

:: Int

starting index

-> Int

length

-> Stream a 
-> Stream a 

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

init :: Stream a -> Stream a Source

All but the last element

tail :: Stream a -> Stream a Source

All but the first element

take :: Int -> Stream a -> Stream a Source

The first n elements

drop :: Int -> Stream a -> Stream a Source

All but the first n elements

Mapping

map :: (a -> b) -> Stream a -> Stream b Source

Map a function over a Stream

concatMap :: (a -> Stream b) -> Stream a -> Stream b Source

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

Create a Stream of values from a Stream of streamable things

Zipping

indexed :: Stream a -> Stream (Int, a) Source

Pair each element in a Stream with its index

indexedR :: Int -> Stream a -> Stream (Int, a) Source

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

zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c Source

Zip two Streams with the given function

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

Zip three Streams with the given function

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

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

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

zip :: Stream a -> Stream b -> Stream (a, b) Source

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

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

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

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

Filtering

filter :: (a -> Bool) -> Stream a -> Stream a Source

Drop elements which do not satisfy the predicate

takeWhile :: (a -> Bool) -> Stream a -> Stream a Source

Longest prefix of elements that satisfy the predicate

dropWhile :: (a -> Bool) -> Stream a -> Stream a Source

Drop the longest prefix of elements that satisfy the predicate

Searching

elem :: Eq a => a -> Stream a -> Bool infix 4 Source

Check whether the Stream contains an element

notElem :: Eq a => a -> Stream a -> Bool infix 4 Source

Inverse of elem

find :: (a -> Bool) -> Stream a -> Maybe a Source

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

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

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

Folding

foldl :: (a -> b -> a) -> a -> Stream b -> a Source

Left fold

foldl1 :: (a -> a -> a) -> Stream a -> a Source

Left fold on non-empty Streams

foldl' :: (a -> b -> a) -> a -> Stream b -> a Source

Left fold with strict accumulator

foldl1' :: (a -> a -> a) -> Stream a -> a Source

Left fold on non-empty Streams with strict accumulator

foldr :: (a -> b -> b) -> b -> Stream a -> b Source

Right fold

foldr1 :: (a -> a -> a) -> Stream a -> a Source

Right fold on non-empty Streams

Specialised folds

Unfolding

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

Unfold

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

Unfold at most n elements

iterateN :: Int -> (a -> a) -> a -> Stream a Source

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

Scans

prescanl :: (a -> b -> a) -> a -> Stream b -> Stream a Source

Prefix scan

prescanl' :: (a -> b -> a) -> a -> Stream b -> Stream a Source

Prefix scan with strict accumulator

postscanl :: (a -> b -> a) -> a -> Stream b -> Stream a Source

Suffix scan

postscanl' :: (a -> b -> a) -> a -> Stream b -> Stream a Source

Suffix scan with strict accumulator

scanl :: (a -> b -> a) -> a -> Stream b -> Stream a Source

Haskell-style scan

scanl' :: (a -> b -> a) -> a -> Stream b -> Stream a Source

Haskell-style scan with strict accumulator

scanl1 :: (a -> a -> a) -> Stream a -> Stream a Source

Scan over a non-empty Stream

scanl1' :: (a -> a -> a) -> Stream a -> Stream a Source

Scan over a non-empty Stream with a strict accumulator

Enumerations

enumFromStepN :: Num a => a -> a -> Int -> Stream a Source

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

enumFromTo :: Enum a => a -> a -> Stream a Source

Enumerate values

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

enumFromThenTo :: Enum a => a -> a -> a -> Stream a Source

Enumerate values with a given step.

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

Conversions

toList :: Stream a -> [a] Source

Convert a Stream to a list

fromList :: [a] -> Stream a Source

Create a Stream from a list

fromListN :: Int -> [a] -> Stream a Source

Create a Stream from the first n elements of a list

fromListN n xs = fromList (take n xs)

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

Convert a pure stream to a monadic stream

Monadic combinators

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

Apply a monadic action to each element of the stream, producing a monadic stream of results

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

Apply a monadic action to each element of the stream

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

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

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

Yield a monadic stream of elements that satisfy the monadic predicate

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

Monadic fold

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

Monadic fold over non-empty stream

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

Monadic fold with strict accumulator

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

Monad fold over non-empty stream with strict accumulator

eq :: Eq a => Stream a -> Stream a -> Bool Source

Check if two Streams are equal

cmp :: Ord a => Stream a -> Stream a -> Ordering Source

Lexicographically compare two Streams