| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Box.Emitter
Description
Synopsis
- newtype Emitter m a = Emitter {}
- type CoEmitter m a = Codensity m (Emitter m a)
- toListM :: Monad m => Emitter m a -> m [a]
- witherE :: Monad m => (a -> m (Maybe b)) -> Emitter m a -> Emitter m b
- readE :: (Functor m, Read a) => Emitter m Text -> Emitter m (Either Text a)
- unlistE :: Monad m => Emitter m [a] -> Emitter (StateT [a] m) a
- takeE :: Monad m => Int -> Emitter m a -> Emitter (StateT Int m) a
- takeUntilE :: Monad m => (a -> Bool) -> Emitter m a -> Emitter m a
- pop :: Monad m => Emitter (StateT (Seq a) m) a
Documentation
an Emitter emits values of type Maybe a. Source & Producer are also appropriate metaphors.
An Emitter reaches into itself for the value to emit, where itself is an opaque thing from the pov of usage.
>>>e = Emitter (pure (Just "I'm emitted"))>>>emit eJust "I'm emitted"
>>>emit memptyNothing
Instances
| FoldableM Emitter Source # | This fold completes on the first Nothing emitted, which may not be what you want. |
| FFunctor Emitter Source # | |
| Monad m => Monad (Emitter m) Source # | |
| Functor m => Functor (Emitter m) Source # | |
| Applicative m => Applicative (Emitter m) Source # | |
| (Monad m, Alternative m) => Alternative (Emitter m) Source # | |
| (Alternative m, Monad m) => MonadPlus (Emitter m) Source # | |
| (Alternative m, Monad m) => Semigroup (Emitter m a) Source # | |
| (Alternative m, Monad m) => Monoid (Emitter m a) Source # | |
toListM :: Monad m => Emitter m a -> m [a] Source #
Collect emits into a list, and close on the first Nothing.
>>>toListM <$|> qList [1..3][1,2,3]
witherE :: Monad m => (a -> m (Maybe b)) -> Emitter m a -> Emitter m b Source #
A monadic Witherable
>>>close $ toListM <$> witherE (\x -> bool (print x >> pure Nothing) (pure (Just x)) (even x)) <$> (qList [1..3])1 3 [2]
readE :: (Functor m, Read a) => Emitter m Text -> Emitter m (Either Text a) Source #
Read parse Emitter, returning the original text on error
>>>process (toListM . readE) (qList ["1","2","3","four"]) :: IO [Either Text Int][Right 1,Right 2,Right 3,Left "four"]
unlistE :: Monad m => Emitter m [a] -> Emitter (StateT [a] m) a Source #
Convert a list emitter to a (Stateful) element emitter.
>>>import Control.Monad.State.Lazy>>>close $ flip runStateT [] . toListM . unlistE <$> (qList [[0..3],[5..7]])([0,1,2,3,5,6,7],[])
takeE :: Monad m => Int -> Emitter m a -> Emitter (StateT Int m) a Source #
Take n emits.
>>>import Control.Monad.State.Lazy>>>close $ flip evalStateT 0 <$> toListM . takeE 4 <$> qList [0..][0,1,2,3]