box-0.9.0: boxes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Box.Committer

Description

Synopsis

Documentation

newtype Committer m a Source #

A Committer commits values of type a and signals success or otherwise. A Sink and a Consumer are some other metaphors for this.

A Committer absorbs the value being committed; the value disappears into the opaque thing that is a Committer from the pov of usage.

>>> commit toStdout "I'm committed!"
I'm committed!
True

Constructors

Committer 

Fields

Instances

Instances details
FFunctor Committer Source # 
Instance details

Defined in Box.Committer

Methods

foist :: (forall x. f x -> g x) -> Committer f a -> Committer g a Source #

Contravariant (Committer m) Source # 
Instance details

Defined in Box.Committer

Methods

contramap :: (a' -> a) -> Committer m a -> Committer m a' #

(>$) :: b -> Committer m b -> Committer m a #

Applicative m => Decidable (Committer m) Source # 
Instance details

Defined in Box.Committer

Methods

lose :: (a -> Void) -> Committer m a #

choose :: (a -> Either b c) -> Committer m b -> Committer m c -> Committer m a #

Applicative m => Divisible (Committer m) Source # 
Instance details

Defined in Box.Committer

Methods

divide :: (a -> (b, c)) -> Committer m b -> Committer m c -> Committer m a #

conquer :: Committer m a #

Applicative m => Monoid (Committer m a) Source # 
Instance details

Defined in Box.Committer

Methods

mempty :: Committer m a #

mappend :: Committer m a -> Committer m a -> Committer m a #

mconcat :: [Committer m a] -> Committer m a #

Applicative m => Semigroup (Committer m a) Source # 
Instance details

Defined in Box.Committer

Methods

(<>) :: Committer m a -> Committer m a -> Committer m a #

sconcat :: NonEmpty (Committer m a) -> Committer m a #

stimes :: Integral b => b -> Committer m a -> Committer m a #

type CoCommitter m a = Codensity m (Committer m a) Source #

Committer continuation.

witherC :: Monad m => (b -> m (Maybe a)) -> Committer m a -> Committer m b Source #

A monadic Witherable

>>> glue (witherC (\x -> pure $ bool Nothing (Just x) (even x)) showStdout) <$|> qList [0..5]
0
2
4

listC :: Monad m => Committer m a -> Committer m [a] Source #

Convert a committer to be a list committer. Think mconcat.

>>> glue showStdout <$|> qList [[1..3]]
[1,2,3]
>>> glue (listC showStdout) <$|> qList [[1..3]]
1
2
3

push :: Monad m => Committer (StateT (Seq a) m) a Source #

Push to a state sequence.

>>> import Control.Monad.State.Lazy
>>> import qualified Data.Sequence as Seq
>>> flip execStateT Seq.empty . glue push . foist lift <$|> qList [1..3]
fromList [1,2,3]