Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hpp.Streamer
Description
Streaming input and output.
- newtype Streamer m i o r = Streamer {
- runStream :: m (StreamStep r i o (Streamer m i o r))
- data StreamStep r i o f
- type Source m o r = Streamer m Void o r
- encase :: Monad m => StreamStep r i o (Streamer m i o r) -> Streamer m i o r
- done :: Monad m => r -> Streamer m i o r
- yield :: Monad m => o -> Streamer m i o ()
- yields :: Monad m => o -> Streamer m i o r -> Streamer m i o r
- awaits :: Monad m => (i -> Streamer m i o r) -> Streamer m i o r
- source :: (Monad m, Foldable f) => f a -> Streamer m i a ()
- liftS :: Functor m => m a -> Streamer m i o a
- nextOutput :: Monad m => Streamer m i o r -> m (Either (Maybe r) (o, Streamer m i o r))
- run :: Monad m => Source m Void r -> m (Maybe r)
- before :: Monad m => Streamer m i o q -> Streamer m i o r -> Streamer m i o r
- (~>) :: Monad m => Streamer m a b r -> Streamer m b c r' -> Streamer m a c r'
- processPrefix :: Monad m => Source m o r -> Streamer m o o r' -> Source m o r
- mapping :: Monad m => (a -> b) -> Streamer m a b r
- filtering :: Monad m => (a -> Bool) -> Streamer m a a r
- mapStream :: Monad m => (a -> b) -> Streamer m i a r -> Streamer m i b r
- mappingMaybe :: Monad m => (a -> Maybe b) -> Streamer m a b r
- onDone :: Monad m => (Maybe r -> Maybe r') -> Streamer m i o r -> Streamer m i o r'
- mapTil :: Monad m => (a -> b) -> Streamer m Void a r -> Streamer m Void b (Streamer m Void a r)
- flattenTil :: Monad m => Source m [i] r -> Source m i (Source m [i] r)
- newtype Chunky m a b = Chunky (a -> Source m b (Chunky m a b))
- metamorph :: Monad m => Chunky m a b -> Streamer m a b ()
Documentation
newtype Streamer m i o r Source #
A stream of steps in a computational context.
Constructors
Streamer | |
Fields
|
Instances
Monad m => Functor (Streamer m i o) Source # | |
Monad m => Applicative (Streamer m i o) Source # | |
Monad m => Alternative (Streamer m r i) Source # | |
(Monad m, HasEnv m) => HasEnv (Streamer m i o) Source # | |
(Monad m, HasHppState m) => HasHppState (Streamer m i o) Source # | |
(Monad m, HasError m) => HasError (Streamer m i o) Source # | |
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
yields :: Monad m => o -> Streamer m i o r -> Streamer m i o r Source #
Yield a value then continue with another 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.
(~>) :: 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.
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.
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
.
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.