fused-effects-0.1.0.0: A fast, flexible, fused effect system.

Safe HaskellNone
LanguageHaskell2010

Control.Effect.Error

Synopsis

Documentation

data Error exc m k Source #

Constructors

Throw exc 
Catch (m b) (exc -> m b) (b -> k) 
Instances
Effect (Error exc) Source # 
Instance details

Defined in Control.Effect.Error

Methods

handle :: Functor f => f () -> (forall x. f (m x) -> n (f x)) -> Error exc m (m a) -> Error exc n (n (f a)) Source #

HFunctor (Error exc) Source # 
Instance details

Defined in Control.Effect.Error

Methods

fmap' :: (a -> b) -> Error exc m a -> Error exc m b Source #

hmap :: (forall x. m x -> n x) -> Error exc m a -> Error exc n a Source #

Functor (Error exc m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

fmap :: (a -> b) -> Error exc m a -> Error exc m b #

(<$) :: a -> Error exc m b -> Error exc m a #

(Carrier sig m, Effect sig, Monad m) => Carrier (Error e :+: sig) (ErrorC e m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

ret :: a -> ErrorC e m a Source #

eff :: (Error e :+: sig) (ErrorC e m) (ErrorC e m a) -> ErrorC e m a Source #

throwError :: (Member (Error exc) sig, Carrier sig m) => exc -> m a Source #

Throw an error, escaping the current computation up to the nearest catchError (if any).

run (runError (throwError a)) == Left @Int @Int a

catchError :: (Member (Error exc) sig, Carrier sig m) => m a -> (exc -> m a) -> m a Source #

Run a computation which can throw errors with a handler to run on error.

Errors thrown by the handler will escape up to the nearest enclosing catchError (if any).

run (runError (pure a `catchError` pure)) == Right a
run (runError (throwError a `catchError` pure)) == Right @Int @Int a
run (runError (throwError a `catchError` (throwError @Int))) == Left @Int @Int a

runError :: (Carrier sig m, Effect sig, Monad m) => Eff (ErrorC exc m) a -> m (Either exc a) Source #

Run an Error effect, returning uncaught errors in Left and successful computations’ values in Right.

run (runError (pure a)) == Right @Int @Int a

newtype ErrorC e m a Source #

Constructors

ErrorC 

Fields

Instances
(Carrier sig m, Effect sig, Monad m) => Carrier (Error e :+: sig) (ErrorC e m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

ret :: a -> ErrorC e m a Source #

eff :: (Error e :+: sig) (ErrorC e m) (ErrorC e m a) -> ErrorC e m a Source #