ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Data.Stream

Description

Monadic streams

Synopsis

Documentation

newtype Stream (m :: Type -> Type) a b Source #

Stream m a b is a computation in some Monad m that delivers a sequence of elements of type a followed by a result of type b.

More concretely, a value of type Stream m a b can be run using runStreamInternal in the Monad m, and it delivers either

  • the final result: Done b, or
  • Yield a str where a is the next element in the stream, and str is the rest of the stream
  • Effect mstr where mstr is some action running in m which generates the rest of the stream.

Stream is itself a Monad, and provides an operation yield that produces a new element of the stream. This makes it convenient to turn existing monadic computations into streams.

The idea is that Stream is useful for making a monadic computation that produces values from time to time. This can be used for knitting together two complex monadic operations, so that the producer does not have to produce all its values before the consumer starts consuming them. We make the producer into a Stream, and the consumer pulls on the stream each time it wants a new value.

Stream is implemented in the "yoneda" style for efficiency. By representing a stream in this manner fmap and >>= operations are accumulated in the function parameters before being applied once when the stream is destroyed. In the old implementation each usage of mapM and >>= would traverse the entire stream in order to apply the substitution at the leaves.

The >>= operation for Stream was a hot-spot in the ticky profile for the ManyConstructors test which called the cg function many times in StgToCmm.hs

Constructors

Stream 

Fields

Instances

Instances details
MonadIO m => MonadIO (Stream m b) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

liftIO :: IO a -> Stream m b a Source #

Applicative (Stream m a) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

pure :: a0 -> Stream m a a0 Source #

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

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

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

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

Functor (Stream f a) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

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

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

Monad (Stream m a) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

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

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

return :: a0 -> Stream m a a0 Source #

data StreamS (m :: Type -> Type) a b Source #

Constructors

Yield a (StreamS m a b) 
Done b 
Effect (m (StreamS m a b)) 

Instances

Instances details
Monad m => Applicative (StreamS m a) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

pure :: a0 -> StreamS m a a0 Source #

(<*>) :: StreamS m a (a0 -> b) -> StreamS m a a0 -> StreamS m a b Source #

liftA2 :: (a0 -> b -> c) -> StreamS m a a0 -> StreamS m a b -> StreamS m a c Source #

(*>) :: StreamS m a a0 -> StreamS m a b -> StreamS m a b Source #

(<*) :: StreamS m a a0 -> StreamS m a b -> StreamS m a a0 Source #

Functor m => Functor (StreamS m a) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

fmap :: (a0 -> b) -> StreamS m a a0 -> StreamS m a b Source #

(<$) :: a0 -> StreamS m a b -> StreamS m a a0 Source #

Monad m => Monad (StreamS m a) Source # 
Instance details

Defined in GHC.Data.Stream

Methods

(>>=) :: StreamS m a a0 -> (a0 -> StreamS m a b) -> StreamS m a b Source #

(>>) :: StreamS m a a0 -> StreamS m a b -> StreamS m a b Source #

return :: a0 -> StreamS m a a0 Source #

runStream :: forall (m :: Type -> Type) r' r. Applicative m => Stream m r' r -> StreamS m r' r Source #

yield :: forall (m :: Type -> Type) a. Monad m => a -> Stream m a () Source #

liftIO :: MonadIO m => IO a -> m a Source #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

collect :: Monad m => Stream m a () -> m [a] Source #

Turn a Stream into an ordinary list, by demanding all the elements.

consume :: (Monad m, Monad n) => Stream m a b -> (forall a1. m a1 -> n a1) -> (a -> n ()) -> n b Source #

fromList :: forall (m :: Type -> Type) a. Monad m => [a] -> Stream m a () Source #

Turn a list into a Stream, by yielding each element in turn.

map :: forall (m :: Type -> Type) a b x. Monad m => (a -> b) -> Stream m a x -> Stream m b x Source #

Apply a function to each element of a Stream, lazily

mapM :: Monad m => (a -> m b) -> Stream m a x -> Stream m b x Source #

Apply a monadic operation to each element of a Stream, lazily

mapAccumL_ :: forall m a b c r. Monad m => (c -> a -> m (c, b)) -> c -> Stream m a r -> Stream m b (c, r) Source #

Note this is not very efficient because it traverses the whole stream before rebuilding it, avoid using it if you can. mapAccumL used to implemented but it wasn't used anywhere in the compiler and has similar efficiency problems.