Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Throw e (m :: * -> *) (a :: *) where
- data Catch e :: Effect where
- type Error e = Bundle '[Throw e, Catch e]
- throw :: Eff (Throw e) m => e -> m a
- catch :: Eff (Catch e) m => m a -> (e -> m a) -> m a
- try :: Eff (Catch e) m => m a -> m (Either e a)
- catchJust :: forall smallExc bigExc m a. Eff (Error bigExc) m => (bigExc -> Maybe smallExc) -> m a -> (smallExc -> m a) -> m a
- tryJust :: forall smallExc bigExc m a. Eff (Error bigExc) m => (bigExc -> Maybe smallExc) -> m a -> m (Either smallExc a)
- note :: Eff (Throw e) m => e -> Maybe a -> m a
- fromEither :: Eff (Throw e) m => Either e a -> m a
- runThrow :: forall e m a p. (Carrier m, Threaders '[ErrorThreads] m p) => ThrowC e m a -> m (Either e a)
- runError :: forall e m a p. (Carrier m, Threaders '[ErrorThreads] m p) => ErrorC e m a -> m (Either e a)
- errorToIO :: forall e m a. (MonadCatch m, Eff (Embed IO) m) => ErrorToIOC e m a -> m (Either e a)
- errorToIOAsExc :: (Exception e, MonadCatch m, Carrier m) => ErrorToIOAsExcC e m a -> m a
- errorToErrorIO :: forall e m a. Effs '[ErrorIO, Embed IO] m => InterpretErrorC e m a -> m (Either e a)
- errorToErrorIOAsExc :: (Exception e, Eff ErrorIO m) => ErrorToErrorIOAsExcC e m a -> m a
- throwToThrow :: forall smallExc bigExc m a. Eff (Throw bigExc) m => (smallExc -> bigExc) -> InterpretReifiedC (Throw smallExc) m a -> m a
- catchToError :: forall smallExc bigExc m a. Eff (Error bigExc) m => (bigExc -> Maybe smallExc) -> InterpretReifiedC (Catch smallExc) m a -> m a
- errorToError :: forall smallExc bigExc m a. Eff (Error bigExc) m => (smallExc -> bigExc) -> (bigExc -> Maybe smallExc) -> InterpretErrorC smallExc m a -> m a
- errorToIOSimple :: forall e m a p. (Eff (Embed IO) m, MonadCatch m, Threaders '[ReaderThreads] m p) => ErrorToIOSimpleC e m a -> m (Either e a)
- errorToErrorIOSimple :: forall e m a p. (Effs '[ErrorIO, Embed IO] m, Threaders '[ReaderThreads] m p) => InterpretErrorSimpleC e m a -> m (Either e a)
- throwToThrowSimple :: forall smallExc bigExc m a p. (Eff (Throw bigExc) m, Threaders '[ReaderThreads] m p) => (smallExc -> bigExc) -> InterpretSimpleC (Throw smallExc) m a -> m a
- catchToErrorSimple :: forall smallExc bigExc m a p. (Eff (Error bigExc) m, Threaders '[ReaderThreads] m p) => (bigExc -> Maybe smallExc) -> InterpretSimpleC (Catch smallExc) m a -> m a
- errorToErrorSimple :: forall smallExc bigExc m a p. (Eff (Error bigExc) m, Threaders '[ReaderThreads] m p) => (smallExc -> bigExc) -> (bigExc -> Maybe smallExc) -> InterpretErrorSimpleC smallExc m a -> m a
- class (forall e. Threads (ExceptT e) p) => ErrorThreads p
- class MonadThrow m => MonadCatch (m :: Type -> Type)
- data ThrowC e m a
- data ErrorC e m a
- type ErrorToIOC e m a = forall s s'. ReifiesErrorHandler s s' e (ErrorIOToIOC m) => ErrorToIOC' s s' e m a
- data ErrorToIOC' s s' e m a
- type ReifiesErrorHandler s s' e m = (ReifiesHandler s (Catch e) (InterpretC (ViaReifiedH s') (Throw e) m), ReifiesHandler s' (Throw e) m)
- type InterpretErrorC e m a = forall s s'. ReifiesErrorHandler s s' e m => InterpretErrorC' s s' e m a
- data InterpretErrorC' s s' e m a
- data ErrorToIOSimpleC e m a
- data InterpretErrorSimpleC e m a
Effects
newtype Throw e (m :: * -> *) (a :: *) where Source #
An effect for throwing exceptions of type e
.
Instances
(Eff ErrorIO m, Exception e) => Handler ErrorToErrorIOAsExcH (Throw e) m Source # | |
Defined in Control.Effect.Internal.Error effHandler :: EffHandler (Throw e) m Source # |
data Catch e :: Effect where Source #
An effect for catching exceptions of type e
.
Instances
(Eff ErrorIO m, Exception e) => Handler ErrorToErrorIOAsExcH (Catch e) m Source # | |
Defined in Control.Effect.Internal.Error effHandler :: EffHandler (Catch e) m Source # |
Actions
catchJust :: forall smallExc bigExc m a. Eff (Error bigExc) m => (bigExc -> Maybe smallExc) -> m a -> (smallExc -> m a) -> m a Source #
tryJust :: forall smallExc bigExc m a. Eff (Error bigExc) m => (bigExc -> Maybe smallExc) -> m a -> m (Either smallExc a) Source #
Main Interpreters
runThrow :: forall e m a p. (Carrier m, Threaders '[ErrorThreads] m p) => ThrowC e m a -> m (Either e a) Source #
runError :: forall e m a p. (Carrier m, Threaders '[ErrorThreads] m p) => ErrorC e m a -> m (Either e a) Source #
errorToIO :: forall e m a. (MonadCatch m, Eff (Embed IO) m) => ErrorToIOC e m a -> m (Either e a) Source #
Runs connected Throw
and Catch
effects -- i.e. Error
--
by making use of IO
exceptions.
Derivs
(ErrorToIOC
e m) =Catch
e ':Throw
e ':Derivs
m
Prims
(ErrorToIOC
e m) =Optional
((->)SomeException
) ':Prims
m
This has a higher-rank type, as it makes use of ErrorToIOC
.
This makes errorToIO
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
errorToIOSimple
, which doesn't have a higher-rank type.
errorToIOAsExc :: (Exception e, MonadCatch m, Carrier m) => ErrorToIOAsExcC e m a -> m a Source #
Runs connected Throw
and Catch
effects -- i.e. Error
--
by treating values of e
as IO
exceptions.
Unlike errorToIO
, values of e
are thrown and caught directly as IO
exceptions. This means that, for example, catchIO
is able to catch
exceptions of e
that you throw with throw
,
and catch
is able to catch
exceptions of type e
that are thrown with throwIO
, or by embed
ded IO
actions.
Derivs
(ErrorToIOAsExcC
e m) =Catch
e ':Throw
e ':Derivs
m
Prims
(ErrorToIOAsExcC
e m) =Optional
((->)SomeException
) ':Prims
m
Since: 0.2.0.0
Other interpreters
errorToErrorIO :: forall e m a. Effs '[ErrorIO, Embed IO] m => InterpretErrorC e m a -> m (Either e a) Source #
Runs connected Throw
and Catch
effects -- i.e. Error
--
by transforming them into ErrorIO
and Embed
IO
This has a higher-rank type, as it makes use of InterpretErrorC
.
This makes errorToErrorIO
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
errorToErrorIOSimple
, which doesn't have a higher-rank type.
errorToErrorIOAsExc :: (Exception e, Eff ErrorIO m) => ErrorToErrorIOAsExcC e m a -> m a Source #
Runs connected Throw
and Catch
effects -- i.e. Error
--
by transforming them into ErrorIO
.
Unlike errorToErrorIO
, values of e
are thrown and caught directly as IO
exceptions. This means that, for example, catchIO
is able to catch
exceptions of e
that you throw with throw
,
and catch
is able to catch exceptions of type e
that
are thrown with throwIO
, or by embed
ded IO
actions.
Derivs
(ErrorToErrorIOAsExcC
e m) =Catch
e ':Throw
e ':Derivs
m
Prims
(ErrorToErrorIOAsExcC
e m) =Prims
m
Since: 0.2.0.0
throwToThrow :: forall smallExc bigExc m a. Eff (Throw bigExc) m => (smallExc -> bigExc) -> InterpretReifiedC (Throw smallExc) m a -> m a Source #
Transforms a
effect into a Throw
smallExc
effect,
by providing a function to convert exceptions of the smaller exception type
Throw
bigExcsmallExc
to the larger exception type bigExc
.
This has a higher-rank type, as it makes use of InterpretReifiedC
.
This makes throwToThrow
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
throwToThrowSimple
, which doesn't have a higher-rank type.
catchToError :: forall smallExc bigExc m a. Eff (Error bigExc) m => (bigExc -> Maybe smallExc) -> InterpretReifiedC (Catch smallExc) m a -> m a Source #
Transforms a
effect into an Catch
smallExc
effect, by
providing a function that identifies when exceptions of the larger exception type
Error
bigExcbigExc
correspond to exceptions of the smaller exception type smallExc
.
This has a higher-rank type, as it makes use of InterpretReifiedC
.
This makes catchToError
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
catchToErrorSimple
, which doesn't have a higher-rank type.
errorToError :: forall smallExc bigExc m a. Eff (Error bigExc) m => (smallExc -> bigExc) -> (bigExc -> Maybe smallExc) -> InterpretErrorC smallExc m a -> m a Source #
Transforms connected Throw
and Catch
effects -- i.e. Error
--
into another Error
effect by providing functions to convert
between the two types of exceptions.
This has a higher-rank type, as it makes use of InterpretErrorC
.
This makes errorToError
very difficult to use partially applied.
In particular, it can't be composed using
..
If performance is secondary, consider using the slower
errorToErrorSimple
, which doesn't have a higher-rank type.
Simple variants
errorToIOSimple :: forall e m a p. (Eff (Embed IO) m, MonadCatch m, Threaders '[ReaderThreads] m p) => ErrorToIOSimpleC e m a -> m (Either e a) Source #
Runs connected Throw
and Catch
effects -- i.e. Error
--
by making use of IO
exceptions.
Derivs
(ErrorToIOSimpleC
e m) =Catch
e ':Throw
e ':Derivs
m
Prims
(ErrorToIOSimpleC
e m) =Optional
((->)SomeException
) ':Prims
m
This is a less performant version of errorToIO
that doesn't have
a higher-rank type, making it much easier to use partially applied.
errorToErrorIOSimple :: forall e m a p. (Effs '[ErrorIO, Embed IO] m, Threaders '[ReaderThreads] m p) => InterpretErrorSimpleC e m a -> m (Either e a) Source #
throwToThrowSimple :: forall smallExc bigExc m a p. (Eff (Throw bigExc) m, Threaders '[ReaderThreads] m p) => (smallExc -> bigExc) -> InterpretSimpleC (Throw smallExc) m a -> m a Source #
Transforms a
effect into a Throw
smallExc
effect,
by providing a function to convert exceptions of the smaller exception type
Throw
bigExcsmallExc
to the larger exception type bigExc
.
This is a less performant version of throwToThrow
that doesn't have
a higher-rank type, making it much easier to use partially applied.
catchToErrorSimple :: forall smallExc bigExc m a p. (Eff (Error bigExc) m, Threaders '[ReaderThreads] m p) => (bigExc -> Maybe smallExc) -> InterpretSimpleC (Catch smallExc) m a -> m a Source #
Transforms a
effect into an Catch
smallExc
effect, by
providing a function that identifies when exceptions of the larger exception type
Error
bigExcbigExc
correspond to exceptions of the smaller exception type smallExc
.
This is a less performant version of catchToError
that doesn't have
a higher-rank type, making it much easier to use partially applied.
errorToErrorSimple :: forall smallExc bigExc m a p. (Eff (Error bigExc) m, Threaders '[ReaderThreads] m p) => (smallExc -> bigExc) -> (bigExc -> Maybe smallExc) -> InterpretErrorSimpleC smallExc m a -> m a Source #
Transforms connected Throw
and Catch
effects -- i.e. Error
--
into another Error
effect by providing functions to convert
between the two types of exceptions.
This is a less performant version of errorToError
that doesn't have
a higher-rank type, making it much easier to use partially applied.
Threading constraints
class (forall e. Threads (ExceptT e) p) => ErrorThreads p Source #
ErrorThreads
accepts the following primitive effects:
Regional
s
Optional
s
(whens
is a functor)BaseControl
b
Unravel
p
ListenPrim
o
(wheno
is aMonoid
)WriterPrim
o
(wheno
is aMonoid
)ReaderPrim
i
Mask
Bracket
Fix
Instances
(forall e. Threads (ExceptT e) p) => ErrorThreads p Source # | |
Defined in Control.Effect.Internal.Error |
MonadCatch
class MonadThrow m => MonadCatch (m :: Type -> Type) #
A class for monads which allow exceptions to be caught, in particular
exceptions which were thrown by throwM
.
Instances should obey the following law:
catch (throwM e) f = f e
Note that the ability to catch an exception does not guarantee that we can
deal with all possible exit points from a computation. Some monads, such as
continuation-based stacks, allow for more than just a success/failure
strategy, and therefore catch
cannot be used by those monads to properly
implement a function such as finally
. For more information, see
MonadMask
.
Instances
Carriers
Instances
Instances
type ErrorToIOC e m a = forall s s'. ReifiesErrorHandler s s' e (ErrorIOToIOC m) => ErrorToIOC' s s' e m a Source #
data ErrorToIOC' s s' e m a Source #
Instances
type ReifiesErrorHandler s s' e m = (ReifiesHandler s (Catch e) (InterpretC (ViaReifiedH s') (Throw e) m), ReifiesHandler s' (Throw e) m) Source #
type InterpretErrorC e m a = forall s s'. ReifiesErrorHandler s s' e m => InterpretErrorC' s s' e m a Source #
data InterpretErrorC' s s' e m a Source #
Instances
data ErrorToIOSimpleC e m a Source #
Instances
data InterpretErrorSimpleC e m a Source #