----------------------------------------------------------------------------- -- | -- Module : Data.Stream -- Copyright : (c) Ross Paterson 2003 -- License : BSD-style (see the LICENSE file in the distribution) -- -- Maintainer : ross@soi.city.ac.uk -- Stability : experimental -- Portability : portable -- -- Infinite sequences. module Data.Stream where -- | An infinite sequence. data Stream a = Cons { shd :: a, -- ^ head of the stream stl :: Stream a -- ^ tail of the stream } instance Functor Stream where fmap f xs = Cons (f (shd xs)) (fmap f (stl xs)) instance Monad Stream where return x = let return_x = Cons x return_x in return_x xs >>= f = Cons (shd (f (shd xs))) (stl xs >>= f) -- | Lazy zip of a pair of streams. zipStream :: Stream a -> Stream b -> Stream (a, b) zipStream xs ys = Cons (shd xs, shd ys) (zipStream (stl xs) (stl ys)) -- | Lazy unzip of a pair of streams. unzipStream :: Stream (a, b) -> (Stream a, Stream b) unzipStream xys = (fmap fst xys, fmap snd xys) -- | An infinite sequence obtained by padding the list with 'undefined'. listToStream :: [a] -> Stream a listToStream = foldr Cons (error "listToStream") -- | The infinite list corresponding to a stream. streamToList :: Stream a -> [a] streamToList xs = shd xs : streamToList (stl xs)