| Portability | portable (Haskell 2010) | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Trustworthy | 
Data.Stream.Infinite
Contents
Description
- data Stream a = 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
 - scanl' :: (a -> b -> a) -> a -> Stream b -> Stream a
 - scanl1 :: (a -> a -> a) -> Stream a -> Stream a
 - scanl1' :: (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 :: NonEmpty a -> Stream a
 - unfold :: (a -> (b, a)) -> a -> Stream b
 - 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 (NonEmpty a)
 - groupBy :: (a -> a -> Bool) -> Stream a -> Stream (NonEmpty 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)
 - words :: Stream Char -> Stream String
 - unwords :: Stream String -> Stream Char
 - lines :: Stream Char -> Stream String
 - unlines :: Stream String -> Stream Char
 - fromList :: [a] -> Stream a
 
The type of streams
Basic functions
tails :: Stream a -> Stream (Stream a)Source
The tails function takes a stream xs and returns all the
 suffixes of xs.
Stream transformations
intersperse :: a -> Stream a -> Stream aSource
 creates an alternating stream of
 elements from intersperse y xsxs 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:
scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
scanl' :: (a -> b -> a) -> a -> Stream b -> Stream aSource
scanl yields a stream of successive reduced values from:
scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
scanl1' :: (a -> a -> a) -> Stream a -> Stream aSource
scanl1' is a strict scanl 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
 produces the infinite sequence
 of repeated applications of iterate f xf to x.
iterate f x = [x, f x, f (f x), ..]
cycle :: NonEmpty a -> Stream aSource
 returns the infinite repetition of cycle xsxs:
cycle [1,2,3] = Cons 1 (Cons 2 (Cons 3 (Cons 1 (Cons 2 ...
unfold :: (a -> (b, a)) -> a -> Stream bSource
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
 returns the first take n xsn elements of xs.
Beware: passing a negative integer as the first argument will cause an error.
drop :: Int -> Stream a -> Stream aSource
 drops the first drop n xsn 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
 returns a pair consisting of the prefix of 
 splitAt n xsxs 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
 returns the longest prefix of the stream
 takeWhile p xsxs for which the predicate p holds.
span :: (a -> Bool) -> Stream a -> ([a], Stream a)Source
 returns the longest prefix of span p xsxs that satisfies
 p, together with the remainder of the stream.
filter :: (a -> Bool) -> Stream a -> Stream aSource
, removes any elements from filter p xsxs 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 (NonEmpty 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 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.