-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/


-- | A library for manipulating infinite lists.
--   
--   This package implements functions, analogous to those from Data.List,
--   to create and manipulate infinite lists: <tt>data Stream a = Cons a
--   (Stream a)</tt>. It provides alternative definitions for those Prelude
--   functions that make sense for such streams. Note that this package has
--   (almost) nothing to do with the work on <i>Stream Fusion</i> by Duncan
--   Coutts, Roman Leshchinskiy, and Don Stewart.
@package Stream
@version 0.4.7.2


-- | 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.
module Data.Stream

-- | An infinite sequence.
--   
--   <i>Beware</i>: If you use any function from the <tt> Eq </tt> or <tt>
--   Ord </tt> class to compare two equal streams, these functions will
--   diverge.
data Stream a
Cons :: a -> Stream a -> Stream a
infixr 5 `Cons`

-- | The <tt> &lt;:&gt; </tt> operator is an infix version of the
--   <a>Cons</a> constructor.
(<:>) :: a -> Stream a -> Stream a
infixr 5 <:>

-- | Extract the first element of the sequence.
head :: Stream a -> a

-- | Extract the sequence following the head of the stream.
tail :: Stream a -> Stream a

-- | The <a>inits</a> function takes a stream <tt>xs</tt> and returns all
--   the finite prefixes of <tt>xs</tt>.
--   
--   Note that this <a>inits</a> is lazier then <tt>Data.List.inits</tt>:
--   
--   <pre>
--   inits _|_ = [] ::: _|_
--   </pre>
--   
--   while for <tt>Data.List.inits</tt>:
--   
--   <pre>
--   inits _|_ = _|_
--   </pre>
inits :: Stream a -> Stream [a]

-- | The <a>tails</a> function takes a stream <tt>xs</tt> and returns all
--   the suffixes of <tt>xs</tt>.
tails :: Stream a -> Stream (Stream a)

-- | Apply a function uniformly over all elements of a sequence.
map :: (a -> b) -> Stream a -> Stream b

-- | <a>intersperse</a> <tt>y</tt> <tt>xs</tt> creates an alternating
--   stream of elements from <tt>xs</tt> and <tt>y</tt>.
intersperse :: a -> Stream a -> Stream a

-- | Interleave two Streams <tt>xs</tt> and <tt>ys</tt>, alternating
--   elements from each list.
--   
--   <pre>
--   [x1,x2,...] `interleave` [y1,y2,...] == [x1,y1,x2,y2,...]
--   </pre>
interleave :: Stream a -> Stream a -> Stream a

-- | <a>scan</a> yields a stream of successive reduced values from:
--   
--   <pre>
--   scan f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   </pre>
scan :: (a -> b -> a) -> a -> Stream b -> Stream a

-- | <tt>scan'</tt> is a strict scan.
scan' :: (a -> b -> a) -> a -> Stream b -> Stream a

-- | <a>scan1</a> is a variant of <a>scan</a> that has no starting value
--   argument:
--   
--   <pre>
--   scan1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   </pre>
scan1 :: (a -> a -> a) -> Stream a -> Stream a

-- | <tt>scan1'</tt> is a strict scan that has no starting value.
scan1' :: (a -> a -> a) -> Stream a -> Stream a

-- | <a>transpose</a> computes the transposition of a stream of streams.
transpose :: Stream (Stream a) -> Stream (Stream a)

-- | <a>iterate</a> <tt>f</tt> <tt>x</tt> function produces the infinite
--   sequence of repeated applications of <tt>f</tt> to <tt>x</tt>.
--   
--   <pre>
--   iterate f x = [x, f x, f (f x), ..]
--   </pre>
iterate :: (a -> a) -> a -> Stream a

-- | <a>repeat</a> <tt>x</tt> returns a constant stream, where all elements
--   are equal to <tt>x</tt>.
repeat :: a -> Stream a

-- | <a>cycle</a> <tt>xs</tt> returns the infinite repetition of
--   <tt>xs</tt>:
--   
--   <pre>
--   cycle [1,2,3] = Cons 1 (Cons 2 (Cons 3 (Cons 1 (Cons 2 ...
--   </pre>
cycle :: [a] -> Stream a

-- | The unfold function is similar to the unfold for lists. Note there is
--   no base case: all streams must be infinite.
unfold :: (c -> (a, c)) -> c -> Stream a

-- | The <a>prefix</a> 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.
prefix :: [a] -> Stream a -> Stream a

-- | <a>take</a> <tt>n</tt> <tt>xs</tt> returns the first <tt>n</tt>
--   elements of <tt>xs</tt>.
--   
--   <i>Beware</i>: passing a negative integer as the first argument will
--   cause an error.
take :: Int -> Stream a -> [a]

-- | <a>drop</a> <tt>n</tt> <tt>xs</tt> drops the first <tt>n</tt> elements
--   off the front of the sequence <tt>xs</tt>.
--   
--   <i>Beware</i>: passing a negative integer as the first argument will
--   cause an error.
drop :: Int -> Stream a -> Stream a

-- | The <a>splitAt</a> function takes an integer <tt>n</tt> and a stream
--   <tt>xs</tt> and returns a pair consisting of the prefix of <tt>xs</tt>
--   of length <tt>n</tt> and the remaining stream immediately following
--   this prefix.
--   
--   <i>Beware</i>: passing a negative integer as the first argument will
--   cause an error.
splitAt :: Int -> Stream a -> ([a], Stream a)

-- | <a>takeWhile</a> <tt>p</tt> <tt>xs</tt> returns the longest prefix of
--   the stream <tt>xs</tt> for which the predicate <tt>p</tt> holds.
takeWhile :: (a -> Bool) -> Stream a -> [a]

-- | <a>dropWhile</a> <tt>p</tt> <tt>xs</tt> returns the suffix remaining
--   after <a>takeWhile</a> <tt>p</tt> <tt>xs</tt>.
--   
--   <i>Beware</i>: this function may diverge if every element of
--   <tt>xs</tt> satisfies <tt>p</tt>, e.g. <tt>dropWhile even (repeat
--   0)</tt> will loop.
dropWhile :: (a -> Bool) -> Stream a -> Stream a

-- | <a>span</a> <tt>p</tt> <tt>xs</tt> returns the longest prefix of
--   <tt>xs</tt> that satisfies <tt>p</tt>, together with the remainder of
--   the stream.
--   
--   <i>Beware</i>: this function may diverge if every element of
--   <tt>xs</tt> satisfies <tt>p</tt>, e.g. <tt>span even (repeat 0)</tt>
--   will loop.
span :: (a -> Bool) -> Stream a -> ([a], Stream a)

-- | The <a>break</a> <tt>p</tt> function is equivalent to <a>span</a>
--   <tt>not . p</tt>.
--   
--   <i>Beware</i>: this function may diverge for the same reason as
--   <tt>span</tt>.
break :: (a -> Bool) -> Stream a -> ([a], Stream a)

-- | <a>filter</a> <tt>p</tt> <tt>xs</tt>, removes any elements from
--   <tt>xs</tt> that do not satisfy <tt>p</tt>.
--   
--   <i>Beware</i>: this function may diverge if there is no element of
--   <tt>xs</tt> that satisfies <tt>p</tt>, e.g. <tt>filter odd (repeat
--   0)</tt> will loop.
filter :: (a -> Bool) -> Stream a -> Stream a

-- | The <a>partition</a> function takes a predicate <tt>p</tt> and a
--   stream <tt>xs</tt>, and returns a pair of streams. The first stream
--   corresponds to the elements of <tt>xs</tt> for which <tt>p</tt> holds;
--   the second stream corresponds to the elements of <tt>xs</tt> for which
--   <tt>p</tt> does not hold.
--   
--   <i>Beware</i>: One of the elements of the tuple may be undefined. For
--   example, <tt>fst (partition even (repeat 0)) == repeat 0</tt>; on the
--   other hand <tt>snd (partition even (repeat 0))</tt> is undefined.
partition :: (a -> Bool) -> Stream a -> (Stream a, Stream a)

-- | The <a>group</a> 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,
--   
--   <pre>
--   group $ cycle "Mississippi" = "M" ::: "i" ::: "ss" ::: "i" ::: "ss" ::: "i" ::: "pp" ::: "i" ::: "M" ::: "i" ::: ...
--   </pre>
group :: Eq a => Stream a -> Stream [a]

-- | The <tt>isPrefix</tt> function returns <tt>True</tt> if the first
--   argument is a prefix of the second.
isPrefixOf :: Eq a => [a] -> Stream a -> Bool

-- | <tt>xs !! n</tt> returns the element of the stream <tt>xs</tt> at
--   index <tt>n</tt>. Note that the head of the stream has index 0.
--   
--   <i>Beware</i>: passing a negative integer as the first argument will
--   cause an error.
(!!) :: Stream a -> Int -> a

-- | The <a>elemIndex</a> function returns the index of the first element
--   in the given stream which is equal (by <a>==</a>) to the query
--   element,
--   
--   <i>Beware</i>: <a>elemIndex</a> <tt>x</tt> <tt>xs</tt> will diverge if
--   none of the elements of <tt>xs</tt> equal <tt>x</tt>.
elemIndex :: Eq a => a -> Stream a -> Int

-- | The <a>elemIndices</a> function extends <a>elemIndex</a>, by returning
--   the indices of all elements equal to the query element, in ascending
--   order.
--   
--   <i>Beware</i>: <a>elemIndices</a> <tt>x</tt> <tt>xs</tt> will diverge
--   if any suffix of <tt>xs</tt> does not contain <tt>x</tt>.
elemIndices :: Eq a => a -> Stream a -> Stream Int

-- | The <a>findIndex</a> function takes a predicate and a stream and
--   returns the index of the first element in the stream that satisfies
--   the predicate,
--   
--   <i>Beware</i>: <a>findIndex</a> <tt>p</tt> <tt>xs</tt> will diverge if
--   none of the elements of <tt>xs</tt> satisfy <tt>p</tt>.
findIndex :: (a -> Bool) -> Stream a -> Int

-- | The <a>findIndices</a> function extends <a>findIndex</a>, by returning
--   the indices of all elements satisfying the predicate, in ascending
--   order.
--   
--   <i>Beware</i>: <a>findIndices</a> <tt>p</tt> <tt>xs</tt> will diverge
--   if all the elements of any suffix of <tt>xs</tt> fails to satisfy
--   <tt>p</tt>.
findIndices :: (a -> Bool) -> Stream a -> Stream Int

-- | The <a>zip</a> function takes two streams and returns the stream of
--   pairs obtained by pairing elements at the same position in both
--   argument streams.
zip :: Stream a -> Stream b -> Stream (a, b)

-- | The <a>zipWith</a> function generalizes <a>zip</a>. Rather than
--   tupling the functions, the elements are combined using the function
--   passed as the first argument to <a>zipWith</a>.
zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c

-- | The <a>unzip</a> function is the inverse of the <a>zip</a> function.
unzip :: Stream (a, b) -> (Stream a, Stream b)

-- | The <a>zip3</a> function behaves as the <a>zip</a> function, but works
--   on three streams.
zip3 :: Stream a -> Stream b -> Stream c -> Stream (a, b, c)

-- | The <a>zipWith3</a> behaves as <a>zipWith</a> but takes three stream
--   arguments.
zipWith3 :: (a -> b -> c -> d) -> Stream a -> Stream b -> Stream c -> Stream d

-- | The <a>unzip3</a> function is the inverse of the <a>zip</a> function.
unzip3 :: Stream (a, b, c) -> (Stream a, Stream b, Stream c)

-- | The <a>distribute</a> function is similar to the <a>sequenceA</a>
--   function defined in Data.Traversable. Since <tt>Streams</tt> are not
--   <a>Foldable</a> in general, there is no <a>Traversable</a> instance
--   for streams. They do support a similar notion that only requires the
--   outer type constructor to be functorial.
distribute :: Functor f => f (Stream a) -> Stream (f a)

-- | The <a>words</a> function breaks a stream of characters into a stream
--   of words, which were delimited by white space.
--   
--   <i>Beware</i>: if the stream of characters <tt>xs</tt> does not
--   contain white space, accessing the tail of <tt>words xs</tt> will
--   loop.
words :: Stream Char -> Stream String

-- | The <a>unwords</a> function is an inverse operation to <a>words</a>.
--   It joins words with separating spaces.
unwords :: Stream String -> Stream Char

-- | The <a>lines</a> function breaks a stream of characters into a list of
--   strings at newline characters. The resulting strings do not contain
--   newlines.
--   
--   <i>Beware</i>: if the stream of characters <tt>xs</tt> does not
--   contain newline characters, accessing the tail of <tt>lines xs</tt>
--   will loop.
lines :: Stream Char -> Stream String

-- | The <a>unlines</a> function is an inverse operation to <a>lines</a>.
--   It joins lines, after appending a terminating newline to each.
unlines :: Stream String -> Stream Char

-- | The <a>toList</a> converts a stream into an infinite list.
toList :: Stream a -> [a]

-- | The <a>fromList</a> converts an infinite list to a stream.
--   
--   <i>Beware</i>: Passing a finite list, will cause an error.
fromList :: [a] -> Stream a
instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Stream.Stream a)
instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Stream.Stream a)
instance GHC.Base.Functor Data.Stream.Stream
instance GHC.Base.Applicative Data.Stream.Stream
instance GHC.Base.Monad Data.Stream.Stream
instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Data.Stream.Stream a)
instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Data.Stream.Stream a)
instance Test.LazySmallCheck.Serial a => Test.LazySmallCheck.Serial (Data.Stream.Stream a)
instance GHC.Show.Show a => GHC.Show.Show (Data.Stream.Stream a)