Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control.Effect.Internal.Exceptional
Synopsis
- newtype Exceptional eff exc m a = Exceptional (Union '[eff, Catch exc] m a)
- type SafeError exc = Exceptional (Throw exc) exc
- newtype ExceptionallyC (eff :: Effect) (exc :: *) m a = ExceptionallyC {
- unExceptionallyC :: m a
- data ExceptionalH
- type ExceptionalC eff exc = InterpretC ExceptionalH (Exceptional eff exc)
- type SafeErrorToErrorC exc = ExceptionalC (Throw exc) exc
- newtype SafeErrorC exc m a = SafeErrorC {
- unSafeErrorC :: IntroUnderC (SafeError exc) '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorC exc m)) a
- newtype SafeErrorToIOC' s s' exc m a = SafeErrorToIOC' {
- unSafeErrorToIOC' :: IntroUnderC (SafeError exc) '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorToIOC' s s' exc m)) a
- type SafeErrorToIOC e m a = forall s s'. ReifiesErrorHandler s s' e (ErrorIOToIOC m) => SafeErrorToIOC' s s' e m a
- newtype SafeErrorToErrorIOC' s s' exc m a = SafeErrorToErrorIOC' {
- unSafeErrorToErrorIOC' :: IntroUnderC (SafeError exc) '[Catch exc, Throw exc] (SafeErrorToErrorC exc (InterpretErrorC' s s' exc m)) a
- type SafeErrorToErrorIOC e m a = forall s s'. ReifiesErrorHandler s s' e m => SafeErrorToErrorIOC' s s' e m a
- newtype SafeErrorToIOSimpleC exc m a = SafeErrorToIOSimpleC {
- unSafeErrorToIOSimpleC :: IntroUnderC (SafeError exc) '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorToIOSimpleC exc m)) a
- newtype SafeErrorToErrorIOSimpleC exc m a = SafeErrorToErrorIOSimpleC {
- unSafeErrorToErrorIOSimpleC :: IntroUnderC (SafeError exc) '[Catch exc, Throw exc] (SafeErrorToErrorC exc (InterpretErrorSimpleC exc m)) a
Documentation
newtype Exceptional eff exc m a Source #
An effect that allows for the safe use of an effect eff
that may
throw exceptions of the type exc
by forcing the user to eventually
catch those exceptions at some point of the program.
The main combinator of Exceptional
is catching
.
This could be unsafe in the presence of Conc
.
If you use catching
on a computation that:
- Spawns an asynchronous computation
- Throws an exception inside the asynchronous computation from a use of
eff
- Returns the
Async
of that asynchronous computation
Then wait
ing on that Async
outside of the catching
will throw that exception
without it being caught.
Constructors
Exceptional (Union '[eff, Catch exc] m a) |
Instances
(Member eff (Derivs m), Eff (Catch exc) m) => Handler ExceptionalH (Exceptional eff exc) m Source # | |
Defined in Control.Effect.Internal.Exceptional Methods effHandler :: EffHandler (Exceptional eff exc) m Source # |
type SafeError exc = Exceptional (Throw exc) exc Source #
A particularly useful specialization of Exceptional
, for gaining
restricted access to an
effect.
Main combinators are Error
exccatchSafe
and
trySafe
.
newtype ExceptionallyC (eff :: Effect) (exc :: *) m a Source #
Constructors
ExceptionallyC | |
Fields
|
Instances
data ExceptionalH Source #
Instances
(Member eff (Derivs m), Eff (Catch exc) m) => Handler ExceptionalH (Exceptional eff exc) m Source # | |
Defined in Control.Effect.Internal.Exceptional Methods effHandler :: EffHandler (Exceptional eff exc) m Source # |
type ExceptionalC eff exc = InterpretC ExceptionalH (Exceptional eff exc) Source #
type SafeErrorToErrorC exc = ExceptionalC (Throw exc) exc Source #
newtype SafeErrorC exc m a Source #
Constructors
SafeErrorC | |
Fields
|
Instances
newtype SafeErrorToIOC' s s' exc m a Source #
Constructors
SafeErrorToIOC' | |
Fields
|
Instances
type SafeErrorToIOC e m a = forall s s'. ReifiesErrorHandler s s' e (ErrorIOToIOC m) => SafeErrorToIOC' s s' e m a Source #
newtype SafeErrorToErrorIOC' s s' exc m a Source #
Constructors
SafeErrorToErrorIOC' | |
Fields
|
Instances
type SafeErrorToErrorIOC e m a = forall s s'. ReifiesErrorHandler s s' e m => SafeErrorToErrorIOC' s s' e m a Source #
newtype SafeErrorToIOSimpleC exc m a Source #
Constructors
SafeErrorToIOSimpleC | |
Fields
|
Instances
newtype SafeErrorToErrorIOSimpleC exc m a Source #
Constructors
SafeErrorToErrorIOSimpleC | |
Fields
|