Streams are infinite lists. Most operations on streams are completely analogous to the definition in Data.List.
- data Stream a = Cons a (Stream a)
- (<:>) :: a -> Stream a -> Stream a
- head :: Stream a -> a
- tail :: Stream a -> Stream a
- inits :: Stream a -> Stream [a]
- tails :: Stream a -> Stream (Stream a)
- map :: (a -> b) -> Stream a -> Stream b
- intersperse :: a -> Stream a -> Stream a
- interleave :: Stream a -> Stream a -> Stream a
- scanl :: (a -> b -> a) -> a -> Stream b -> Stream a
- scanl1 :: (a -> a -> a) -> Stream a -> Stream a
- iterate :: (a -> a) -> a -> Stream a
- repeat :: a -> Stream a
- cycle :: [a] -> Stream a
- unfold :: (c -> (a, c)) -> c -> Stream a
- take :: Int -> Stream a -> [a]
- drop :: Int -> Stream a -> Stream a
- splitAt :: Int -> Stream a -> ([a], Stream a)
- takeWhile :: (a -> Bool) -> Stream a -> [a]
- dropWhile :: (a -> Bool) -> Stream a -> Stream a
- span :: (a -> Bool) -> Stream a -> ([a], Stream a)
- break :: (a -> Bool) -> Stream a -> ([a], Stream a)
- filter :: (a -> Bool) -> Stream a -> Stream a
- partition :: (a -> Bool) -> Stream a -> (Stream a, Stream a)
- isPrefixOf :: Eq a => [a] -> Stream a -> Bool
- (!!) :: Stream a -> Int -> a
- zip :: Stream a -> Stream b -> Stream (a, b)
- zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c
- unzip :: Stream (a, b) -> (Stream a, Stream b)
- words :: Stream Char -> Stream String
- unwords :: Stream String -> Stream Char
- lines :: Stream Char -> Stream String
- unlines :: Stream String -> Stream Char
- listToStream :: [a] -> Stream a
- streamToList :: Stream a -> [a]
The type of streams
An infinite sequence.
Basic functions
(<:>) :: a -> Stream a -> Stream aSource
The <:>
operator is an infix version of the Cons
constructor.
inits :: Stream a -> Stream [a]Source
The inits
function takes a stream xs
and returns all the
finite prefixes of xs
.
tails :: Stream a -> Stream (Stream a)Source
The tails
function takes a stream xs
and returns all the
suffixes of xs
.
Stream transformations
map :: (a -> b) -> Stream a -> Stream bSource
Apply a function uniformly over all elements of a sequence.
intersperse :: a -> Stream a -> Stream aSource
intersperse
y
xs
creates an alternating stream of
elements from xs
and y
.
interleave :: Stream a -> Stream a -> Stream aSource
Interleave two Streams xs
and ys
, alternating elements
from each list.
@[x1,x2,...] `interleave` [y1,y2,...] == [x1,y1,x2,y2,...]@
scanl :: (a -> b -> a) -> a -> Stream b -> Stream aSource
scanl
yields a stream of successive reduced values from the
| left:
scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
Building streams
iterate :: (a -> a) -> a -> Stream aSource
iterate
f
x
function produces the infinite sequence
of repeated applications of f
to x
.
iterate f x = [x, f x, f (f x), ..]
cycle :: [a] -> Stream aSource
cycle
xs
returns the infinite repetition of xs
:
cycle [1,2,3] = Cons 1 (Cons 2 (Cons 3 (Cons 1 (Cons 2 ...
unfold :: (c -> (a, c)) -> c -> Stream aSource
The unfold function is similar to the unfold for lists. Note there is no base case: all streams must be infinite.
Extracting sublists
take :: Int -> Stream a -> [a]Source
take
n
xs
returns the first n
elements of xs
.
Beware: passing a negative integer as the first argument will cause an error.
drop :: Int -> Stream a -> Stream aSource
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.
splitAt :: Int -> Stream a -> ([a], Stream a)Source
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.
takeWhile :: (a -> Bool) -> Stream a -> [a]Source
takeWhile
p
xs
returns the longest prefix of the stream
xs
for which the predicate p
holds.
span :: (a -> Bool) -> Stream a -> ([a], Stream a)Source
span
p
xs
returns the longest prefix of xs
that satisfies
p
, together with the remainder of the stream.
filter :: (a -> Bool) -> Stream a -> Stream aSource
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.
partition :: (a -> Bool) -> Stream a -> (Stream a, Stream a)Source
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.
Sublist predicates
isPrefixOf :: Eq a => [a] -> Stream a -> BoolSource
The isPrefix
function returns True
if the first argument is
a prefix of the second.
Indexing streams
(!!) :: Stream a -> Int -> aSource
xs !! n
returns the element of the stream xs
at index
n
. Note that the head of the stream has index 0.
Beware: passing a negative integer as the first argument will cause an error.
Zipping and unzipping streams
zip :: Stream a -> Stream b -> Stream (a, b)Source
The zip
function takes two streams and returns a list of
corresponding pairs.
Functions on streams of characters
words :: Stream Char -> Stream StringSource
The words
function breaks a stream of characters into a
stream of words, which were delimited by white space.
Beware: if the stream of characters xs
does not contain white
space, accessing the tail of words xs
will loop.
lines :: Stream Char -> Stream StringSource
The lines
function breaks a stream of characters into a list
of strings at newline characters. The resulting strings do not
contain newlines.
Beware: if the stream of characters xs
does not contain
newline characters, accessing the tail of lines xs
will loop.
Converting to and from an infinite list
listToStream :: [a] -> Stream aSource
The listToStream
converts an infinite list to a
stream.
Beware: Passing a finite list, will cause an error.
streamToList :: Stream a -> [a]Source
The streamToList
converts a stream into an infinite list.