polysemy-1.2.3.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 r a. MemberWithError (Error e) r => e -> Sem r a Source #

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

fromEither :: Member (Error e) r => Either e a -> Sem r a Source #

Upgrade an Either into an Error effect.

Since: 0.5.1.0

fromEitherM :: forall e m r a. (Member (Error e) r, Member (Embed m) r) => m (Either e a) -> Sem r a Source #

A combinator doing embed and fromEither at the same time. Useful for interoperating with IO.

Since: 0.5.1.0

Interpretations

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

Run an Error effect in the style of ExceptT.

mapError :: forall e1 e2 r a. Member (Error e2) r => (e1 -> e2) -> Sem (Error e1 ': r) a -> Sem r a Source #

Transform one Error into another. This function can be used to aggregate multiple errors into a single type.

Since: 1.0.0.0

errorToIOFinal :: (Typeable e, Member (Final IO) r) => Sem (Error e ': r) a -> Sem r (Either e a) Source #

Run an Error effect as an IO Exception through final IO. This interpretation is significantly faster than runError.

Beware: Effects that aren't interpreted in terms of IO will have local state semantics in regards to Error effects interpreted this way. See Final.

Since: 1.2.0.0

lowerError Source #

Arguments

:: (Typeable e, Member (Embed 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 interpreters composed via .@.

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

Deprecated: Use errorToIOFinal instead

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

Since: 1.0.0.0