stream-fusion-0.1.2.4: Faster Haskell lists using stream fusion

Portabilityportable, requires cpp
Stabilityexperimental
Maintainerdons00@gmail.com
Safe HaskellNone

Data.Stream

Contents

Description

Tested with : GHC 6.6

Stream fusion for sequences. Described in:

See the source for the complete story:

Synopsis

The stream data type

data Stream a Source

A stream.

It is important that we never construct a bottom stream, because the fusion rule is not true for bottom streams.

 (replicate 1 True) ++ (tail undefined)

The suspicion is that under fusion the append will force the bottom.

Constructors

forall s . Unlifted s => Stream !(s -> Step a s) !s 

Instances

Functor Stream 
Unlifted (Stream a)

Some stream functions (notably concatMap) need to use a stream as a state

data Step a s Source

A stream step.

A step either ends a stream, skips a value, or yields a value

Constructors

Yield a !s 
Skip !s 
Done 

Conversions with lists

stream :: [a] -> Stream aSource

Construct an abstract stream from a list.

unstream :: Stream a -> [a]Source

Flatten a stream back into a list.

data L a Source

Boxes for user's state. This is the gateway for user's types into unlifted stream states. The L is always safe since it's liftedlazy, exposingseqing it does nothing. S is unlifted and so is only suitable for users states that we know we can be strict in. This requires attention and auditing.

Constructors

L a 

Instances

Unlifted (L a) 

Basic stream functions

append1 :: Stream a -> [a] -> [a]Source

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

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

head :: Stream a -> aSource

last :: Stream a -> aSource

Stream transformations

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

Reducing streams (folds)

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

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

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

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

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

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

Special folds

concat :: Stream [a] -> [a]Source

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

any :: (a -> Bool) -> Stream a -> BoolSource

all :: (a -> Bool) -> Stream a -> BoolSource

sum :: Num a => Stream a -> aSource

product :: Num a => Stream a -> aSource

maximum :: Ord a => Stream a -> aSource

minimum :: Ord a => Stream a -> aSource

Building lists

Scans

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

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

Infinite streams

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

Unfolding

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

Substreams

Extracting substreams

splitAt :: Int -> Stream a -> ([a], [a])Source

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

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

Predicates

Searching streams

Searching by equality

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

lookup :: Eq a => a -> Stream (a, b) -> Maybe bSource

Searching with a predicate

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

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

Indexing streams

index :: Stream a -> Int -> aSource

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

elemIndex :: Eq a => a -> Stream a -> Maybe IntSource

Zipping and unzipping streams

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

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

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

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

unzip :: Stream (a, b) -> ([a], [b])Source

Special streams

Functions on strings

User-supplied comparison (replacing an Ord context)

insertBy :: (a -> a -> Ordering) -> a -> Stream a -> Stream aSource

maximumBy :: (a -> a -> Ordering) -> Stream a -> aSource

minimumBy :: (a -> a -> Ordering) -> Stream a -> aSource

The "generic" operations

genericIndex :: Integral a => Stream b -> a -> bSource

genericSplitAt :: Integral i => i -> Stream a -> ([a], [a])Source

Enum

Monad

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

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

List comprehension desugaring

bind :: (a -> Bool) -> (a -> Stream b) -> Stream a -> Stream bSource

mapFilter :: (a -> Bool) -> (a -> b) -> Stream a -> Stream bSource

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