monad-chronicle-1: These as a transformer, ChronicleT

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.Trans.Chronicle

Contents

Description

Hybrid error/writer monad class that allows both accumulating outputs and aborting computation with a final output.

The expected use case is for computations with a notion of fatal vs. non-fatal errors.

Synopsis

The Chronicle monad

type Chronicle c = ChronicleT c Identity Source #

A chronicle monad parameterized by the output type c.

The return function produces a computation with no output, and >>= combines multiple outputs with <>.

chronicle :: Monad m => These c a -> ChronicleT c m a Source #

The ChronicleT monad transformer

newtype ChronicleT c m a Source #

The ChronicleT monad transformer.

The return function produces a computation with no output, and >>= combines multiple outputs with <>.

Constructors

ChronicleT 

Fields

Instances
(Semigroup c, MonadRWS r w s m) => MonadRWS r w s (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

(Semigroup c, MonadWriter w m) => MonadWriter w (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

writer :: (a, w) -> ChronicleT c m a #

tell :: w -> ChronicleT c m () #

listen :: ChronicleT c m a -> ChronicleT c m (a, w) #

pass :: ChronicleT c m (a, w -> w) -> ChronicleT c m a #

(Semigroup c, MonadState s m) => MonadState s (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

get :: ChronicleT c m s #

put :: s -> ChronicleT c m () #

state :: (s -> (a, s)) -> ChronicleT c m a #

(Semigroup c, MonadReader r m) => MonadReader r (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

ask :: ChronicleT c m r #

local :: (r -> r) -> ChronicleT c m a -> ChronicleT c m a #

reader :: (r -> a) -> ChronicleT c m a #

(Semigroup c, MonadError e m) => MonadError e (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

throwError :: e -> ChronicleT c m a #

catchError :: ChronicleT c m a -> (e -> ChronicleT c m a) -> ChronicleT c m a #

(Semigroup c, Monad m) => MonadChronicle c (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Chronicle.Class

Methods

dictate :: c -> ChronicleT c m () Source #

disclose :: Default a => c -> ChronicleT c m a Source #

confess :: c -> ChronicleT c m a Source #

memento :: ChronicleT c m a -> ChronicleT c m (Either c a) Source #

absolve :: a -> ChronicleT c m a -> ChronicleT c m a Source #

condemn :: ChronicleT c m a -> ChronicleT c m a Source #

retcon :: (c -> c) -> ChronicleT c m a -> ChronicleT c m a Source #

chronicle :: These c a -> ChronicleT c m a Source #

Semigroup c => MonadTrans (ChronicleT c) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

lift :: Monad m => m a -> ChronicleT c m a #

(Semigroup c, Monad m) => Monad (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

(>>=) :: ChronicleT c m a -> (a -> ChronicleT c m b) -> ChronicleT c m b #

(>>) :: ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m b #

return :: a -> ChronicleT c m a #

fail :: String -> ChronicleT c m a #

Functor m => Functor (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

fmap :: (a -> b) -> ChronicleT c m a -> ChronicleT c m b #

(<$) :: a -> ChronicleT c m b -> ChronicleT c m a #

(Semigroup c, MonadFix m) => MonadFix (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

mfix :: (a -> ChronicleT c m a) -> ChronicleT c m a #

(Semigroup c, Applicative m) => Applicative (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

pure :: a -> ChronicleT c m a #

(<*>) :: ChronicleT c m (a -> b) -> ChronicleT c m a -> ChronicleT c m b #

liftA2 :: (a -> b -> c0) -> ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m c0 #

(*>) :: ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m b #

(<*) :: ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m a #

(Semigroup c, Monoid c, Applicative m, Monad m) => Alternative (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

empty :: ChronicleT c m a #

(<|>) :: ChronicleT c m a -> ChronicleT c m a -> ChronicleT c m a #

some :: ChronicleT c m a -> ChronicleT c m [a] #

many :: ChronicleT c m a -> ChronicleT c m [a] #

(Semigroup c, Monoid c, Monad m) => MonadPlus (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

mzero :: ChronicleT c m a #

mplus :: ChronicleT c m a -> ChronicleT c m a -> ChronicleT c m a #

(Semigroup c, MonadIO m) => MonadIO (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

liftIO :: IO a -> ChronicleT c m a #

(Semigroup c, Apply m) => Apply (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

(<.>) :: ChronicleT c m (a -> b) -> ChronicleT c m a -> ChronicleT c m b #

(.>) :: ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m b #

(<.) :: ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m a #

liftF2 :: (a -> b -> c0) -> ChronicleT c m a -> ChronicleT c m b -> ChronicleT c m c0 #

(Semigroup c, Apply m, Monad m) => Bind (ChronicleT c m) Source # 
Instance details

Defined in Control.Monad.Trans.Chronicle

Methods

(>>-) :: ChronicleT c m a -> (a -> ChronicleT c m b) -> ChronicleT c m b #

join :: ChronicleT c m (ChronicleT c m a) -> ChronicleT c m a #

Chronicle operations

dictate :: (Semigroup c, Monad m) => c -> ChronicleT c m () Source #

dictate c is an action that records the output c.

Equivalent to tell for the Writer monad.

disclose :: (Default a, Semigroup c, Monad m) => c -> ChronicleT c m a Source #

disclose c is an action that records the output c and returns a Default value.

This is a convenience function for reporting non-fatal errors in one branch a case, or similar scenarios when there is no meaningful result but a placeholder of sorts is needed in order to continue.

confess :: (Semigroup c, Monad m) => c -> ChronicleT c m a Source #

confess c is an action that ends with a final output c.

Equivalent to throwError for the Error monad.

memento :: (Semigroup c, Monad m) => ChronicleT c m a -> ChronicleT c m (Either c a) Source #

memento m is an action that executes the action m, returning either its record if it ended with confess, or its final value otherwise, with any record added to the current record.

Similar to catchError in the Error monad, but with a notion of non-fatal errors (which are accumulated) vs. fatal errors (which are caught without accumulating).

absolve :: (Semigroup c, Monad m) => a -> ChronicleT c m a -> ChronicleT c m a Source #

absolve x m is an action that executes the action m and discards any record it had. The default value x will be used if m ended via confess.

condemn :: (Semigroup c, Monad m) => ChronicleT c m a -> ChronicleT c m a Source #

condemn m is an action that executes the action m and keeps its value only if it had no record. Otherwise, the value (if any) will be discarded and only the record kept.

This can be seen as converting non-fatal errors into fatal ones.

retcon :: (Semigroup c, Monad m) => (c -> c) -> ChronicleT c m a -> ChronicleT c m a Source #

retcon f m is an action that executes the action m and applies the function f to its output, leaving the return value unchanged.

Equivalent to censor for the Writer monad.