hpp-0.3.0.0: A Haskell pre-processor

Safe HaskellNone
LanguageHaskell2010

Hpp.Streamer

Description

Streaming input and output.

Synopsis

Documentation

newtype Streamer m i o r Source

A stream of steps in a computational context.

Constructors

Streamer 

Fields

runStream :: m (StreamStep r i o (Streamer m i o r))
 

Instances

data StreamStep r i o f Source

Basic pipe.

Constructors

Await (i -> f) f 
Yield !o f 
Done (Maybe r) 

Instances

type Source m o r = Streamer m Void o r Source

A stream of steps that never awaits anything from upstream.

encase :: Monad m => StreamStep r i o (Streamer m i o r) -> Streamer m i o r Source

Package a step into a Streamer

done :: Monad m => r -> Streamer m i o r Source

The end of a stream.

yield :: Monad m => o -> Streamer m i o () Source

Yield a value downstream, then finish.

yields :: Monad m => o -> Streamer m i o r -> Streamer m i o r Source

Yield a value then continue with another Streamer.

awaits :: Monad m => (i -> Streamer m i o r) -> Streamer m i o r Source

Package a function that returns a Streamer into a Streamer.

source :: (Monad m, Foldable f) => f a -> Streamer m i a () Source

Feed values downstream.

liftS :: Functor m => m a -> Streamer m i o a Source

Lift a monadic value into a Streamer

nextOutput :: Monad m => Streamer m i o r -> m (Either (Maybe r) (o, Streamer m i o r)) Source

Compute the next step of a Streamer.

run :: Monad m => Source m Void r -> m (Maybe r) Source

A source whose outputs have all been sunk may be run for its effects and return value.

before :: Monad m => Streamer m i o q -> Streamer m i o r -> Streamer m i o r Source

x before y runs x to completion, discards its Done value, then becomes y.

(~>) :: Monad m => Streamer m a b r -> Streamer m b c r' -> Streamer m a c r' infixl 9 Source

upstream ~> downstream composes two streams such that values flow from upstream to downstream.

processPrefix :: Monad m => Source m o r -> Streamer m o o r' -> Source m o r Source

processPrefix src snk is like ~> except that when snk finishes, the composite Streamer becomes the remaining src.

mapping :: Monad m => (a -> b) -> Streamer m a b r Source

Apply a function to each value in a stream.

filtering :: Monad m => (a -> Bool) -> Streamer m a a r Source

Discard all values that do not satisfy a predicate.

mapStream :: Monad m => (a -> b) -> Streamer m i a r -> Streamer m i b r Source

Map a function over the values yielded by a stream.

mappingMaybe :: Monad m => (a -> Maybe b) -> Streamer m a b r Source

A combined filter and map.

onDone :: Monad m => (Maybe r -> Maybe r') -> Streamer m i o r -> Streamer m i o r' Source

Apply a function to the ending value of a stream.

mapTil :: Monad m => (a -> b) -> Streamer m Void a r -> Streamer m Void b (Streamer m Void a r) Source

See flattenTil for an explanation.

flattenTil :: Monad m => Source m [i] r -> Source m i (Source m [i] r) Source

Flatten out chunks of inputs into individual values. The returned Source smuggles the remaining original Source in an Await constructor, while the flattened source continues on with the "empty" part of the Await step. The upshot is that the value may be used a regular Source, but it can also be swapped back into the original Source.

newtype Chunky m a b Source

A function that produces an output stream that finishes with another such function. Think of the input to this function as coming from upstream, while the closure of the streamed output may be used to thread state.

Constructors

Chunky (a -> Source m b (Chunky m a b)) 

metamorph :: Monad m => Chunky m a b -> Streamer m a b () Source

This is something like a composition of an unfold with a fold. We fold the upstream values into some state carried by a Chunky, then unfold that state in the Chunky's output stream.