error-continuations-0.1.0.0: Error Continuations

Copyright(c) Eitan Chatav, 2015
LicensePublicDomain
Maintainereitan.chatav@gmail.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Trans.EitherCont

Description

The EitherContT type and API provide an idiomatic way to handle errors in continuation passing style over some base monad.

Synopsis

Documentation

newtype EitherContT a l m r Source

The EitherContT a l m r type encodes a sum type monad transformer in continuation passing style which is separately monadic in both l and r. Interestingly, this property holds for any type constructor m.

Constructors

EitherContT

Construct a continuation-passing computation from a function.

Fields

runEitherContT :: (l -> m a) -> (r -> m a) -> m a

The result of running a CPS computation with given failure and success continuations.

Instances

MonadError l (EitherContT a l m)

The MonadError function catchError is weaker than catchEC since it must not change the error type.

MonadTrans (EitherContT a l)

EitherContT a l m r is a monad transformer for m in r.

Monad (EitherContT a l m)

The Monad instance encodes monadicity of EitherContT a l m r in r.

Functor (EitherContT a l m)

The Functor instance encodes functoriality of EitherContT a l m r in r.

Applicative (EitherContT a l m)

The Applicative instance encodes applicativity of EitherContT a l m r in r.

MonadCont (EitherContT a l m)

Call with current success continuation.

fmapL :: (l -> l') -> EitherContT a l m r -> EitherContT a l' m r Source

fmapL encodes functoriality of EitherContT a l m r in l.

bimapEC :: (l -> l') -> (r -> r') -> EitherContT a l m r -> EitherContT a l' m r' Source

bimapEC encodes bifunctoriality of EitherContT a l m r in l and r.

bimapEC f id = fmapL f
bimapEC id f = fmap f

throwEC :: l -> EitherContT a l m r Source

throwEC encodes the applicative/monadic unit of EitherContT a l m r in l.

apL :: EitherContT a (l -> l') m r -> EitherContT a l m r -> EitherContT a l' m r Source

apL encodes applicativity of EitherContT a l m r in l.

catchEC :: EitherContT a l m r -> (l -> EitherContT a l' m r) -> EitherContT a l' m r Source

throwEC and catchEC encode monadicity of EitherContT a l m r in l. The usual monad laws hold with throwEC taking the role of return and catchEC taking the role of >>=.

throwEC l `catchEC` f = f l
ec `catchEC` throwEC = ec
(ec `catchEC` f) `catchEC` g = ec `catchEC` (\l -> f l `catchEC` g)

handleEC :: (l -> EitherContT a l' m r) -> EitherContT a l m r -> EitherContT a l' m r Source

handleEC is a flipped catchEC.

(<?<) :: (l' -> EitherContT a l'' m r) -> (l -> EitherContT a l' m r) -> l -> EitherContT a l'' m r Source

A right-to-left, point free way to compose handlers. The monad laws look more elegant, expressed in terms of <?<.

throwEC <?< f = f = f <?< throwEC
(h <?< g) <?< f = h <?< (g <?< f)

(>?>) :: (l -> EitherContT a l' m r) -> (l' -> EitherContT a l'' m r) -> l -> EitherContT a l'' m r Source

A left-to-right, point free way to compose handlers.

liftL :: Monad m => m l -> EitherContT a l m r Source

EitherContT a l m r is a monad transformer for m in l.

flipEC :: EitherContT a l m r -> EitherContT a r m l Source

flipEC encodes the symmetry of l and r in EitherContT a l m r.

flipEC . flipEC = id

mapEitherContT :: (m a -> m a) -> EitherContT a l m r -> EitherContT a l m r Source

Apply a function to transform the result of a continuation-passing computation.

withEitherContTR :: ((r' -> m a) -> r -> m a) -> EitherContT a l m r -> EitherContT a l m r' Source

Apply a function to transform the success continuation passed to a continuation-passing computation.

withEitherContTL :: ((l' -> m a) -> l -> m a) -> EitherContT a l m r -> EitherContT a l' m r Source

Apply a function to transform the failure continuation passed to an continuation-passing computation.

callCCL :: ((l -> EitherContT a l' m r) -> EitherContT a l m r) -> EitherContT a l m r Source

Call with current failure continuation.

lowerMonadError :: MonadError l m => EitherContT r l m r -> m r Source

lowerMonadError runs the continuation-passing computation, throwing on failure and returning on success.

liftMonadError :: MonadError l m => m r -> EitherContT a l m r Source

liftMonadError embeds a MonadError computation m r into EitherContT a l m r.

liftMonadError and lowerMonadError are one-sided inverses, making MonadError l m => m r a retract of EitherContT r l m r.

lowerMonadError . liftMonadError = id