Safe Haskell | None |
---|
Data.Stream
Contents
Description
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
- scan :: (a -> b -> a) -> a -> Stream b -> Stream a
- scan' :: (a -> b -> a) -> a -> Stream b -> Stream a
- scan1 :: (a -> a -> a) -> Stream a -> Stream a
- scan1' :: (a -> a -> a) -> Stream a -> Stream a
- transpose :: Stream (Stream a) -> Stream (Stream a)
- iterate :: (a -> a) -> a -> Stream a
- repeat :: a -> Stream a
- cycle :: [a] -> Stream a
- unfold :: (c -> (a, c)) -> c -> Stream a
- prefix :: [a] -> Stream a -> 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)
- group :: Eq a => Stream a -> Stream [a]
- isPrefixOf :: Eq a => [a] -> Stream a -> Bool
- (!!) :: Stream a -> Int -> a
- elemIndex :: Eq a => a -> Stream a -> Int
- elemIndices :: Eq a => a -> Stream a -> Stream Int
- findIndex :: (a -> Bool) -> Stream a -> Int
- findIndices :: (a -> Bool) -> Stream a -> Stream Int
- 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)
- zip3 :: Stream a -> Stream b -> Stream c -> Stream (a, b, c)
- zipWith3 :: (a -> b -> c -> d) -> Stream a -> Stream b -> Stream c -> Stream d
- unzip3 :: Stream (a, b, c) -> (Stream a, Stream b, Stream c)
- words :: Stream Char -> Stream String
- unwords :: Stream String -> Stream Char
- lines :: Stream Char -> Stream String
- unlines :: Stream String -> Stream Char
- toList :: Stream a -> [a]
- fromList :: [a] -> Stream a
The type of streams
An infinite sequence.
Beware: If you use any function from the Eq
or Ord
class to compare two equal streams, these functions will diverge.
Instances
Monad Stream | |
Functor Stream | |
Applicative Stream | |
Eq a => Eq (Stream a) | |
Ord a => Ord (Stream a) | |
Show a => Show (Stream a) | A Show instance for Streams that takes the right associativity into
account and so doesn't put parenthesis around the tail of the Stream.
Note that |
Arbitrary a => Arbitrary (Stream a) | |
CoArbitrary a => CoArbitrary (Stream a) | |
Serial a => Serial (Stream a) |
Basic functions
(<:>) :: a -> Stream a -> Stream aSource
The <:>
operator is an infix version of the Cons
constructor.
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,...]
scan :: (a -> b -> a) -> a -> Stream b -> Stream aSource
scan
yields a stream of successive reduced values from:
scan f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
scan1' :: (a -> a -> a) -> Stream a -> Stream aSource
scan1'
is a strict scan that has no starting value.
transpose :: Stream (Stream a) -> Stream (Stream a)Source
transpose
computes the transposition of a stream of streams.
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.
prefix :: [a] -> Stream a -> Stream aSource
The prefix
function adds a list as a prefix to an existing
stream. If the list is infinite, it is converted to a Stream and
the second argument is ignored.
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.
group :: Eq a => Stream a -> Stream [a]Source
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,
group $ cycle "Mississippi" = "M" ::: "i" ::: "ss" ::: "i" ::: "ss" ::: "i" ::: "pp" ::: "i" ::: "M" ::: "i" ::: ...
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.
elemIndices :: Eq a => a -> Stream a -> Stream IntSource
The elemIndices
function extends elemIndex
, by returning the
indices of all elements equal to the query element, in ascending order.
Beware: elemIndices
x
xs
will diverge if any suffix of
xs
does not contain x
.
findIndices :: (a -> Bool) -> Stream a -> Stream IntSource
The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending
order.
Beware: findIndices
p
xs
will diverge if all the elements
of any suffix of xs
fails to satisfy p
.
Zipping and unzipping streams
zip :: Stream a -> Stream b -> Stream (a, b)Source
The zip
function takes two streams and returns the stream of
pairs obtained by pairing elements at the same position in both
argument streams.
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.