vector-0.3: Efficient Arrays

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

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 IdSource

The type of pure streams

type MStream = StreamSource

Alternative name for monadic streams

Size hints

size :: Stream a -> SizeSource

Size hint of a Stream

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

Attach a Size hint to a Stream

Length information

length :: Stream a -> IntSource

Length of a Stream

null :: Stream a -> BoolSource

Check if a Stream is empty

Construction

singleton :: a -> Stream aSource

Singleton Stream

cons :: a -> Stream a -> Stream aSource

Prepend an element

snoc :: Stream a -> a -> Stream aSource

Append an element

replicate :: Int -> a -> Stream aSource

Replicate a value to a given length

(++) :: Stream a -> Stream a -> Stream aSource

Concatenate two Streams

Accessing individual elements

head :: Stream a -> aSource

First element of the Stream or error if empty

last :: Stream a -> aSource

Last element of the Stream or error if empty

(!!) :: Stream a -> Int -> aSource

Element at the given position

Substreams

extractSource

Arguments

:: Stream a 
-> Int

starting index

-> Int

length

-> Stream a 

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

init :: Stream a -> Stream aSource

All but the last element

tail :: Stream a -> Stream aSource

All but the first element

take :: Int -> Stream a -> Stream aSource

The first n elements

drop :: Int -> Stream a -> Stream aSource

All but the first n elements

Mapping

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

Map a function over a Stream

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

Zipping

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

Zip two Streams with the given function

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

Zip three Streams with the given function

Filtering

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

Drop elements which do not satisfy the predicate

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

Longest prefix of elements that satisfy the predicate

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

Drop the longest prefix of elements that satisfy the predicate

Searching

elem :: Eq a => a -> Stream a -> BoolSource

Check whether the Stream contains an element

notElem :: Eq a => a -> Stream a -> BoolSource

Inverse of elem

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

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

findIndex :: (a -> Bool) -> Stream a -> Maybe IntSource

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 -> aSource

Left fold

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

Left fold on non-empty Streams

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

Left fold with strict accumulator

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

Left fold on non-empty Streams with strict accumulator

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

Right fold

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

Right fold on non-empty Streams

Specialised folds

Unfolding

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

Unfold

Scans

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

Prefix scan

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

Prefix scan with strict accumulator

Conversions

toList :: Stream a -> [a]Source

Convert a Stream to a list

fromList :: [a] -> Stream aSource

Create a Stream from a list

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

Convert a pure stream to a monadic stream

Monadic combinators

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

Apply a monadic action to each element of the stream

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

Monadic fold