Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype ThrowC e m a = ThrowC {}
- newtype ErrorC e m a = ErrorC {}
- class (forall e. Threads (ExceptT e) p) => ErrorThreads p
- type ReifiesErrorHandler s s' e m = (ReifiesHandler s (Catch e) (InterpretC (ViaReifiedH s') (Throw e) m), ReifiesHandler s' (Throw e) m)
- newtype InterpretErrorC' s s' e m a = InterpretErrorC' {
- unInterpretErrorC' :: InterpretC (ViaReifiedH s) (Catch e) (InterpretC (ViaReifiedH s') (Throw e) m) a
- type InterpretErrorC e m a = forall s s'. ReifiesErrorHandler s s' e m => InterpretErrorC' s s' e m a
- newtype ErrorToIOC' s s' e m a = ErrorToIOC' {
- unErrorToIOC' :: IntroC '[Catch e, Throw e] '[ErrorIO] (InterpretErrorC' s s' e (ErrorIOToIOC m)) a
- type ErrorToIOC e m a = forall s s'. ReifiesErrorHandler s s' e (ErrorIOToIOC m) => ErrorToIOC' s s' e m a
- data OpaqueExc = OpaqueExc Unique Any
- errorToErrorIO :: forall e m a. Effs '[ErrorIO, Embed IO] m => InterpretErrorC e m a -> m (Either e a)
- data ErrorToErrorIOAsExcH
- newtype ErrorToErrorIOAsExcC e m a = ErrorToErrorIOAsExcC {
- unErrorToErrorIOAsExcC :: InterpretC ErrorToErrorIOAsExcH (Catch e) (InterpretC ErrorToErrorIOAsExcH (Throw e) m) a
- errorToErrorIOAsExc :: (Exception e, Eff ErrorIO m) => ErrorToErrorIOAsExcC e m a -> m a
- errorToIO :: forall e m a. (MonadCatch m, Eff (Embed IO) m) => ErrorToIOC e m a -> m (Either e a)
- newtype ErrorToIOAsExcC e m a = ErrorToIOAsExcC {
- unErrorToIOAsExcC :: IntroC '[Catch e, Throw e] '[ErrorIO] (ErrorToErrorIOAsExcC e (ErrorIOToIOC m)) a
- errorToIOAsExc :: (Exception e, MonadCatch m, Carrier m) => ErrorToIOAsExcC e m a -> m a
- newtype InterpretErrorSimpleC e m a = InterpretErrorSimpleC {
- unInterpretErrorSimpleC :: InterpretSimpleC (Catch e) (InterpretSimpleC (Throw e) m) a
- newtype ErrorToIOSimpleC e m a = ErrorToIOSimpleC {
- unErrorToIOSimpleC :: IntroC '[Catch e, Throw e] '[ErrorIO] (InterpretErrorSimpleC e (ErrorIOToIOC m)) a
- errorToErrorIOSimple :: forall e m a p. (Effs '[ErrorIO, Embed IO] m, Threaders '[ReaderThreads] m p) => InterpretErrorSimpleC e m a -> m (Either e 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)
Documentation
Instances
Instances
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 |
type ReifiesErrorHandler s s' e m = (ReifiesHandler s (Catch e) (InterpretC (ViaReifiedH s') (Throw e) m), ReifiesHandler s' (Throw e) m) Source #
newtype InterpretErrorC' s s' e m a Source #
InterpretErrorC' | |
|
Instances
type InterpretErrorC e m a = forall s s'. ReifiesErrorHandler s s' e m => InterpretErrorC' s s' e m a Source #
newtype ErrorToIOC' s s' e m a Source #
ErrorToIOC' | |
|
Instances
type ErrorToIOC e m a = forall s s'. ReifiesErrorHandler s s' e (ErrorIOToIOC m) => ErrorToIOC' s s' e m a Source #
Instances
Show OpaqueExc Source # | |
Exception OpaqueExc Source # | |
Defined in Control.Effect.Internal.Error toException :: OpaqueExc -> SomeException # fromException :: SomeException -> Maybe OpaqueExc # displayException :: OpaqueExc -> String # |
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.
data ErrorToErrorIOAsExcH Source #
Instances
(Eff ErrorIO m, Exception e) => Handler ErrorToErrorIOAsExcH (Throw e) m Source # | |
Defined in Control.Effect.Internal.Error effHandler :: EffHandler (Throw e) m Source # | |
(Eff ErrorIO m, Exception e) => Handler ErrorToErrorIOAsExcH (Catch e) m Source # | |
Defined in Control.Effect.Internal.Error effHandler :: EffHandler (Catch e) m Source # |
newtype ErrorToErrorIOAsExcC e m a Source #
ErrorToErrorIOAsExcC | |
|
Instances
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
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.
newtype ErrorToIOAsExcC e m a Source #
ErrorToIOAsExcC | |
|
Instances
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
newtype InterpretErrorSimpleC e m a Source #
InterpretErrorSimpleC | |
|
Instances
newtype ErrorToIOSimpleC e m a Source #
ErrorToIOSimpleC | |
|
Instances
errorToErrorIOSimple :: forall e m a p. (Effs '[ErrorIO, Embed IO] m, Threaders '[ReaderThreads] m p) => InterpretErrorSimpleC e m a -> m (Either e a) Source #
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.