polysemy-0.2.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.Error

Contents

Synopsis

Effect

data Error e m a where Source #

Constructors

Throw :: e -> Error e m a 
Catch :: forall e m a. m a -> (e -> m a) -> Error e m a 
Instances
type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Polysemy.Error

type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) = "Polysemy.Error"

Actions

throw :: forall e a. forall r. Member (Error e) r => e -> Sem r a Source #

catch :: forall e a. forall r. Member (Error e) r => Sem r a -> (e -> Sem r a) -> Sem r a Source #

Interpretations

runError :: Sem (Error e ': r) a -> Sem r (Either e a) Source #

Run an Error effect in the style of ExceptT.

runErrorInIO Source #

Arguments

:: (Typeable e, Member (Lift IO) r) 
=> (forall x. Sem r x -> IO x)

Strategy for lowering a Sem action down to IO. This is likely some combination of runM and other interpters composed via .@.

-> Sem (Error e ': r) a 
-> Sem r (Either e a) 

Run an Error effect as an IO Exception. This interpretation is significantly faster than runError, at the cost of being less flexible.