-- 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: data Stream a = Cons a -- (Stream a). 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 Stream Fusion 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. -- -- Beware: If you use any function from the Eq or -- Ord class to compare two equal streams, these functions will -- diverge. data Stream a Cons :: a -> Stream a -> Stream a infixr 5 `Cons` -- | The <:> operator is an infix version of the -- Cons 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 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 _|_ = _|_
--   
inits :: Stream a -> Stream [a] -- | The tails function takes a stream xs and returns all -- the suffixes of xs. tails :: Stream a -> Stream (Stream a) -- | Apply a function uniformly over all elements of a sequence. map :: (a -> b) -> Stream a -> Stream b -- | intersperse y xs creates an alternating -- stream of elements from xs and y. intersperse :: a -> Stream a -> Stream a -- | Interleave two Streams xs and ys, alternating -- elements from each list. -- --
--   [x1,x2,...] `interleave` [y1,y2,...] == [x1,y1,x2,y2,...]
--   
interleave :: Stream a -> Stream a -> Stream a -- | 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 -- | scan' is a strict scan. scan' :: (a -> b -> a) -> a -> Stream b -> Stream a -- | 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 -- | scan1' is a strict scan that has no starting value. scan1' :: (a -> a -> a) -> Stream a -> Stream a -- | transpose computes the transposition of a stream of streams. transpose :: Stream (Stream a) -> Stream (Stream a) -- | iterate f x function produces the infinite -- sequence of repeated applications of f to x. -- --
--   iterate f x = [x, f x, f (f x), ..]
--   
iterate :: (a -> a) -> a -> Stream a -- | repeat x returns a constant stream, where all elements -- are equal to x. repeat :: a -> Stream a -- | cycle xs returns the infinite repetition of -- xs: -- --
--   cycle [1,2,3] = Cons 1 (Cons 2 (Cons 3 (Cons 1 (Cons 2 ...
--   
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 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. prefix :: [a] -> Stream a -> Stream a -- | take n xs returns the first n -- elements of xs. -- -- Beware: passing a negative integer as the first argument will -- cause an error. take :: Int -> Stream a -> [a] -- | 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. drop :: Int -> Stream a -> Stream a -- | 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. splitAt :: Int -> Stream a -> ([a], Stream a) -- | takeWhile p xs returns the longest prefix of -- the stream xs for which the predicate p holds. takeWhile :: (a -> Bool) -> Stream a -> [a] -- | 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. dropWhile :: (a -> Bool) -> Stream a -> Stream a -- | 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. span :: (a -> Bool) -> Stream a -> ([a], Stream a) -- | The break p function is equivalent to span -- not . p. -- -- Beware: this function may diverge for the same reason as -- span. break :: (a -> Bool) -> Stream a -> ([a], Stream a) -- | 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. filter :: (a -> Bool) -> Stream a -> Stream a -- | 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. partition :: (a -> Bool) -> Stream a -> (Stream a, Stream a) -- | 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" ::: ...
--   
group :: Eq a => Stream a -> Stream [a] -- | The isPrefix function returns True if the first -- argument is a prefix of the second. isPrefixOf :: Eq a => [a] -> Stream a -> Bool -- | 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. (!!) :: Stream a -> Int -> a -- | 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. elemIndex :: Eq a => a -> Stream a -> Int -- | 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. elemIndices :: Eq a => a -> Stream a -> Stream Int -- | 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. findIndex :: (a -> Bool) -> Stream a -> Int -- | 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. findIndices :: (a -> Bool) -> Stream a -> Stream Int -- | The zip 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 zipWith function generalizes zip. Rather than -- tupling the functions, the elements are combined using the function -- passed as the first argument to zipWith. zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c -- | The unzip function is the inverse of the zip function. unzip :: Stream (a, b) -> (Stream a, Stream b) -- | The zip3 function behaves as the zip function, but works -- on three streams. zip3 :: Stream a -> Stream b -> Stream c -> Stream (a, b, c) -- | The zipWith3 behaves as zipWith but takes three stream -- arguments. zipWith3 :: (a -> b -> c -> d) -> Stream a -> Stream b -> Stream c -> Stream d -- | The unzip3 function is the inverse of the zip function. unzip3 :: Stream (a, b, c) -> (Stream a, Stream b, Stream c) -- | 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. distribute :: Functor f => f (Stream a) -> Stream (f a) -- | 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. words :: Stream Char -> Stream String -- | The unwords function is an inverse operation to words. -- It joins words with separating spaces. unwords :: Stream String -> Stream Char -- | 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. lines :: Stream Char -> Stream String -- | The unlines function is an inverse operation to lines. -- It joins lines, after appending a terminating newline to each. unlines :: Stream String -> Stream Char -- | The toList converts a stream into an infinite list. toList :: Stream a -> [a] -- | The fromList converts an infinite list to a stream. -- -- Beware: 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)