rivers-0.1.0: Rivers are like Streams, but different.

Data.Rivers.Streams

Contents

Description

My module for streams

Synopsis

Streams

data S v Source

Your standard Streams, renamed to S because S looks like a meandering stream.

Constructors

Cons v (S v) 

Instances

Monad S 
Functor S 
Idiom S 
Enum a => Enum (S a) 
Eq v => Eq (S v) 
Fractional a => Fractional (S a) 
Integral a => Integral (S a) 
Num a => Num (S a) 
Ord v => Ord (S v) 
Read v => Read (S v) 
Real a => Real (S a) 
Show v => Show (S v) 
Arbitrary a => Arbitrary (S a) 
CoArbitrary a => CoArbitrary (S a) 
Serial a => Serial (S a) 

Cons 1, n:

(<||) :: a -> S a -> S aSource

(<<|)Source

Arguments

:: [a] 
-> S a 
-> S a

prepend, Hinze UFP p.3

(|~|) :: S a -> S a -> S aSource

ago :: Integer -> S a -> aSource

z0 :: Num a => S aSource

asum :: Num a => S a -> S aSource

bsum :: Num a => S a -> S aSource

csum :: Num a => S a -> S aSource

diff :: Num a => S a -> S aSource

inv :: Num a => S a -> S aSource

sconst :: Num a => a -> S aSource

times :: Num a => a -> S a -> S aSource

plus :: Num a => S a -> S a -> S aSource

interleave :: S a -> S a -> S aSource

interleave' :: S a -> S a -> S aSource

alternate :: S a -> S a -> S aSource

combStreams :: [[a]] -> [[a]]Source

drop0L :: S a -> S aSource

dropIp1L :: S a -> S aSource

dup :: S a -> S aSource

(Improperly) using Ord

(|!|) :: Ord a => S a -> S a -> S aSource

merge :: Ord a => S a -> S a -> S aSource

union :: Ord a => S a -> S a -> S aSource

(Improperly) using Eq

allEqual :: Eq a => [a] -> BoolSource

group :: Eq a => S a -> S [a]Source

fix :: (a -> a) -> aSource

inits :: S a -> S [a]Source

interleave3 :: S a -> S a -> S aSource

intersperse :: a -> S a -> S aSource

map1 :: (a -> b) -> S a -> S bSource

mapAdjacent :: (a -> a -> b) -> [a] -> [b]Source

turn :: Integral a => a -> [a]Source

Generating Functions

type G v o = [v] -> oSource

A generating function for Streams.

Generating Functions, etc

fromFG :: G a a -> S aSource

revFix :: G a a -> S aSource

rgen :: G a b -> S a -> S bSource

fwdFix :: G a a -> S aSource

grow :: G a b -> S a -> S bSource

hOfFG :: G a b -> bSource

tOfFG :: G a b -> a -> G a bSource

rep :: (S a -> S b) -> G a bSource

rgen' :: G a b -> [a] -> S a -> S bSource

hOfRG :: (G a b, [a]) -> bSource

tOfRG :: (G a b, [a]) -> a -> (G a b, [a])Source

fromRG :: (G a a, [a]) -> S aSource

Gen to Tree:

toT :: G a b -> Tree a bSource

Tree to Gen:

toG :: Tree a b -> G a bSource

Infinite Trees

data Tree a o Source

An infinite Tree. Used to represent Streams

Constructors

Node o (a -> Tree a o) 

Trees

branches :: Tree a b -> a -> Tree a bSource

fromT :: Tree a a -> S aSource

label :: Tree a b -> bSource

Coalgebras

type Coalg c a b = (c -> b, c -> a -> c)Source

Your standard Co-Algebra (dual to Algebra).

Coalgebraic

unfold :: Coalg c a b -> c -> Tree a bSource

cfix :: Coalg c a a -> c -> S aSource

groW :: Coalg c a b -> c -> S a -> S bSource

sMap :: (a -> b) -> S a -> S bSource

sMap2 :: (a -> b -> c) -> S a -> S b -> S cSource

sMap3 :: (a -> b -> c -> d) -> S a -> S b -> S c -> S dSource

sMap4 :: (a -> b -> c -> d -> e) -> S a -> S b -> S c -> S d -> S eSource

sEven :: S a -> S aSource

seven :: S a -> S aSource

sOdd :: S a -> S aSource

sodd :: S a -> S aSource

Using Bool Predicates

sbreak :: (a -> Bool) -> S a -> ([a], S a)Source

sdropWhile :: (a -> Bool) -> S a -> S aSource

stakeWhile :: (a -> Bool) -> S a -> [a]Source

sfilter :: (a -> Bool) -> S a -> S aSource

spartition :: (a -> Bool) -> S a -> (S a, S a)Source

sspan :: (a -> Bool) -> S a -> ([a], S a)Source

scan :: (a -> b -> a) -> a -> S b -> S aSource

scan' :: (a -> b -> a) -> a -> S b -> S aSource

scan1 :: (a -> a -> a) -> S a -> S aSource

scan1' :: (a -> a -> a) -> S a -> S aSource

scycle :: [a] -> S aSource

Drivers

siterate :: (a -> a) -> a -> S aSource

Heads and Tails

shead :: S a -> aSource

stail :: S a -> S aSource

tail2 :: S a -> S aSource

tails :: S a -> S (S a)Source

Indexed

stake :: Integer -> S a -> [a]Source

sdrop :: Int -> S a -> S aSource

ssplitAt :: Int -> S a -> ([a], S a)Source

smerge :: S a -> S a -> S aSource

Zips and Unzips

sunzip :: S (a, b) -> (S a, S b)Source

szipWith :: (a -> b -> c) -> S a -> S b -> S cSource

transpose :: S (S a) -> S (S a)Source

Utility Functions

main :: IO ()Source

unzip, specialized to Stream tuples

filter p xs, removes any elements from xs that do not satisfy p.

Beware: this function may diverge if there is no element of xs that satisfies p, e.g. filter odd (repeat 0) will loop.

takeWhile p xs returns the longest prefix of the stream xs for which the predicate p holds.

dropWhile p xs returns the suffix remaining after takeWhile p xs.

Beware: this function may diverge if every element of xs satisfies p, e.g. dropWhile even (repeat 0) will loop.

sspan p xs returns the longest prefix of xs that satisfies p, together with the remainder of the stream.

The break p function is equivalent to span not . p.

The splitAt function takes an integer n and a stream xs and returns a pair consisting of the prefix of xs of length n and the remaining stream immediately following this prefix.

Beware: passing a negative integer as the first argument will cause an error.

The partition function takes a predicate p and a stream xs, and returns a pair of streams. The first stream corresponds to the elements of xs for which p holds; the second stream corresponds to the elements of xs for which p does not hold.

Beware: One of the elements of the tuple may be undefined. For example, fst (partition even (repeat 0)) == repeat 0; on the other hand snd (partition even (repeat 0)) is undefined.

The group function takes a stream and returns a stream of lists such that flattening the resulting stream is equal to the argument. Moreover, each sublist in the resulting stream contains only equal elements. For example,

drop n xs drops the first n elements off the front of the sequence xs.

Beware: passing a negative integer as the first argument will cause an error.

The stails function takes a stream xs and returns all the suffixes of xs.

merge, version 2 [Hinze UFP p.35]

map, version 1 | map, version 2 | map2, really zip?

from Unique Fixed Point p.35

union for streams

Interleave two Streams xs and ys, alternating elements from each list.

 [x1,x2,...] `interleave` [y1,y2,...] == [x1,y1,x2,y2,...]

intersperse y xs creates an alternating stream of elements from xs and y.

infix prepend

turn something

cycle xs returns the infinite repetition of xs:

 cycle [1,2,3] = Cons 1 (Cons 2 (Cons 3 (Cons 1 (Cons 2 ...

Arithmatic, Jumping, ...

multiplication | stream inversion | finite (forward) difference | duplicate the head of the stream | even (indexed) elements | odd (indexed) elements | even (indexed) elements, v2 | odd (indexed) elements, v2 | drop function, results in (4*n - 1) | drop function, results in (2*n) | an alternative tail function

a kind of sum function | right inverse of diff

from Hinze UFP p.45

from Hinze UFP p.49

from Hinze UFP p.4

iterate (inductively) over a stream

this can't be stopped?

from Hinze UFP p.39

from Hinze UFP p.41

2D operator?

from Hinze UFP p.45

from Hinze UFP p.45

mutually recursive

from Hinze UFP p.45

from Hinze UFP p.45

 scan f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]

scan' is a strict scan.

scan1 is a variant of scan that has no starting value argument:

 scan1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]

scan1' is a strict scan that has no starting value.

transpose computes the transposition of a stream of streams.

from Hinze UFP p.45

from Hinze UFP p.45

standard fix-point function | standard fix-point function, specialized to Streams (forward ordering) | standard fix-point function, specialized to Streams (reverse ordering)

transform a generator to a Stream operator | transform a generator to a Stream operator - v2? | transform a Stream operator to a generator | transform a generator, along with a reversed list, into a Stream operator

smart constructor for Tree labels | smart constructor for Tree branches | translate a Tree to a Generator | translate a Generator to a Tree | translate a Tree element to a Stream element | translate a Generator element to a Stream element | fromFG helper function (head) | fromFG helper function (tail) | fromRG: translate a Generator (and a reversed list) to a Stream element | fromRG helper function (head) | fromRG helper function (tail)

unfold operator, specialized to Co-Algebras | standard fix-point function, specialized to Co-Algebras | generate a Stream operator, given a Co-Algebra

utility function to lookup sequence in OEIS | utility function to check of all elements of a list are equal | utility function to unwrap a (known good) Maybe | utility function to map over adjacent elements in a list

Power Series Glasses

Horner's Rule on Streams

s = sconst (shead t) + (z |*| stail s)

implies

z |*| s = 0 <|| s