Stream-0.4.7.2: A library for manipulating infinite lists.
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Stream

Description

Streams are infinite lists. Most operations on streams are completely analogous to the definition in Data.List.

The functions provided in this package are fairly careful about totality, termination, and productivity. None of the functions should diverge, provided you adhere to the preconditions mentioned in the documentation.

Note: I get quite a lot of requests regarding a missing Traversable instance for Streams. This has been left out by design.

Synopsis

The type of streams

data Stream a Source #

An infinite sequence.

Beware: If you use any function from the Eq or Ord class to compare two equal streams, these functions will diverge.

Constructors

Cons a (Stream a) infixr 5 

Instances

Instances details
Applicative Stream Source # 
Instance details

Defined in Data.Stream

Methods

pure :: a -> Stream a Source #

(<*>) :: Stream (a -> b) -> Stream a -> Stream b Source #

liftA2 :: (a -> b -> c) -> Stream a -> Stream b -> Stream c Source #

(*>) :: Stream a -> Stream b -> Stream b Source #

(<*) :: Stream a -> Stream b -> Stream a Source #

Functor Stream Source # 
Instance details

Defined in Data.Stream

Methods

fmap :: (a -> b) -> Stream a -> Stream b Source #

(<$) :: a -> Stream b -> Stream a Source #

Monad Stream Source # 
Instance details

Defined in Data.Stream

Methods

(>>=) :: Stream a -> (a -> Stream b) -> Stream b Source #

(>>) :: Stream a -> Stream b -> Stream b Source #

return :: a -> Stream a Source #

Arbitrary a => Arbitrary (Stream a) Source # 
Instance details

Defined in Data.Stream

Methods

arbitrary :: Gen (Stream a) Source #

shrink :: Stream a -> [Stream a] Source #

CoArbitrary a => CoArbitrary (Stream a) Source # 
Instance details

Defined in Data.Stream

Methods

coarbitrary :: Stream a -> Gen b -> Gen b Source #

Show a => Show (Stream a) Source #

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 show returns an infinite String.

Instance details

Defined in Data.Stream

Eq a => Eq (Stream a) Source # 
Instance details

Defined in Data.Stream

Methods

(==) :: Stream a -> Stream a -> Bool Source #

(/=) :: Stream a -> Stream a -> Bool Source #

Ord a => Ord (Stream a) Source # 
Instance details

Defined in Data.Stream

Methods

compare :: Stream a -> Stream a -> Ordering Source #

(<) :: Stream a -> Stream a -> Bool Source #

(<=) :: Stream a -> Stream a -> Bool Source #

(>) :: Stream a -> Stream a -> Bool Source #

(>=) :: Stream a -> Stream a -> Bool Source #

max :: Stream a -> Stream a -> Stream a Source #

min :: Stream a -> Stream a -> Stream a Source #

Serial a => Serial (Stream a) Source # 
Instance details

Defined in Data.Stream

Methods

series :: Series (Stream a) Source #

Basic functions

(<:>) :: a -> Stream a -> Stream a infixr 5 Source #

The <:> operator is an infix version of the Cons constructor.

head :: Stream a -> a Source #

Extract the first element of the sequence.

tail :: Stream a -> Stream a Source #

Extract the sequence following the head of the stream.

inits :: Stream a -> Stream [a] Source #

The inits function takes a stream xs and returns all the finite prefixes of xs.

Note that this inits is lazier then Data.List.inits:

inits _|_ = [] ::: _|_

while for Data.List.inits:

inits _|_ = _|_

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 b Source #

Apply a function uniformly over all elements of a sequence.

intersperse :: a -> Stream a -> Stream a Source #

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

interleave :: Stream a -> Stream a -> Stream a Source #

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 a Source #

scan yields a stream of successive reduced values from:

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

scan' :: (a -> b -> a) -> a -> Stream b -> Stream a Source #

scan' is a strict scan.

scan1 :: (a -> a -> a) -> Stream a -> Stream a Source #

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

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

scan1' :: (a -> a -> a) -> Stream a -> Stream a Source #

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 a Source #

iterate f x function produces the infinite sequence of repeated applications of f to x.

iterate f x = [x, f x, f (f x), ..]

repeat :: a -> Stream a Source #

repeat x returns a constant stream, where all elements are equal to x.

cycle :: [a] -> Stream a Source #

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 a Source #

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 a Source #

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 a Source #

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.

dropWhile :: (a -> Bool) -> Stream a -> Stream a Source #

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.

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.

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

break :: (a -> Bool) -> Stream a -> ([a], Stream a) Source #

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

Beware: this function may diverge for the same reason as span.

filter :: (a -> Bool) -> Stream a -> Stream a Source #

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 -> Bool Source #

The isPrefix function returns True if the first argument is a prefix of the second.

Indexing streams

(!!) :: Stream a -> Int -> a Source #

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.

elemIndex :: Eq a => a -> Stream a -> Int Source #

The elemIndex function returns the index of the first element in the given stream which is equal (by ==) to the query element,

Beware: elemIndex x xs will diverge if none of the elements of xs equal x.

elemIndices :: Eq a => a -> Stream a -> Stream Int Source #

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.

findIndex :: (a -> Bool) -> Stream a -> Int Source #

The findIndex function takes a predicate and a stream and returns the index of the first element in the stream that satisfies the predicate,

Beware: findIndex p xs will diverge if none of the elements of xs satisfy p.

findIndices :: (a -> Bool) -> Stream a -> Stream Int Source #

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.

zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c Source #

The zipWith function generalizes zip. Rather than tupling the functions, the elements are combined using the function passed as the first argument to zipWith.

unzip :: Stream (a, b) -> (Stream a, Stream b) Source #

The unzip function is the inverse of the zip function.

zip3 :: Stream a -> Stream b -> Stream c -> Stream (a, b, c) Source #

The zip3 function behaves as the zip function, but works on three streams.

zipWith3 :: (a -> b -> c -> d) -> Stream a -> Stream b -> Stream c -> Stream d Source #

The zipWith3 behaves as zipWith but takes three stream arguments.

unzip3 :: Stream (a, b, c) -> (Stream a, Stream b, Stream c) Source #

The unzip3 function is the inverse of the zip function.

distribute :: Functor f => f (Stream a) -> Stream (f a) Source #

The distribute function is similar to the sequenceA function defined in Data.Traversable. Since Streams are not Foldable in general, there is no Traversable instance for streams. They do support a similar notion that only requires the outer type constructor to be functorial.

Functions on streams of characters

words :: Stream Char -> Stream String Source #

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.

unwords :: Stream String -> Stream Char Source #

The unwords function is an inverse operation to words. It joins words with separating spaces.

lines :: Stream Char -> Stream String Source #

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.

unlines :: Stream String -> Stream Char Source #

The unlines function is an inverse operation to lines. It joins lines, after appending a terminating newline to each.

Converting to and from an infinite list

toList :: Stream a -> [a] Source #

The toList converts a stream into an infinite list.

fromList :: [a] -> Stream a Source #

The fromList converts an infinite list to a stream.

Beware: Passing a finite list, will cause an error.