| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Effect.Fail
Synopsis
- newtype Fail (m :: * -> *) (a :: *) where
- runFail :: forall m a p. (Threaders '[ErrorThreads] m p, Carrier m) => FailC m a -> m (Either String a)
- failToThrow :: Eff (Throw e) m => (String -> e) -> InterpretFailReifiedC m a -> m a
- failToNonDet :: Eff NonDet m => FailToNonDetC m a -> m a
- failToAlt :: Eff Alt m => FailToAltC m a -> m a
- failToThrowSimple :: forall e m a p. (Eff (Throw e) m, Threaders '[ReaderThreads] m p) => (String -> e) -> InterpretFailSimpleC m a -> m a
- class (forall e. Threads (ExceptT e) p) => ErrorThreads p
- type FailC = CompositionC '[ReinterpretC FailH Fail '[Throw String], ThrowC String]
- newtype InterpretFailC h m a = InterpretFailC {- unInterpretFailC :: InterpretC h Fail m a
 
- type InterpretFailReifiedC m a = forall s. ReifiesHandler s Fail m => InterpretFailC (ViaReifiedH s) m a
- type FailToNonDetC = InterpretFailC FailToNonDetH
- type FailToAltC = InterpretFailC FailToAltH
- newtype InterpretFailSimpleC m a = InterpretFailSimpleC {}
Effects
newtype Fail (m :: * -> *) (a :: *) where Source #
An effect corresponding to the MonadFail type class.
Effly's MonadFail instance is based
 on this effect; by having access to Fail, you're able to invoke
 handle pattern-match failure automatically inside of effect handlers.
Each Fail interpreter's associated carrier
 has an MonadFail instance based on
 how it interprets Fail. This means you can use
 an Fail interpreter to locally gain access to an MonadFail
 instance inside of application code.
Interpretations
runFail :: forall m a p. (Threaders '[ErrorThreads] m p, Carrier m) => FailC m a -> m (Either String a) Source #
failToThrow :: Eff (Throw e) m => (String -> e) -> InterpretFailReifiedC m a -> m a Source #
Transform a Fail effect to a Throw effect by providing a function
 to transform a pattern match failure into an exception.
You can use this in application code to locally get access to a MonadFail
 instance (since InterpretFailReifiedC has a MonadFail instance based
 on the Fail effect this interprets).
For example:
failToThrow(\_ ->throwexc) (do { Just a <- pure Nothing; return a}) =throwexc
This has a higher-rank type, as it makes use of InterpretFailReifiedC.
 This makes failToThrow very difficult to use partially applied.
 In particular, it can't be composed using .
If performance is secondary, consider using the slower failToThrowSimple,
 which doesn't have a higher-rank type. However, you typically don't
 want to use failToThrowSimple in application code, since failToThrowSimple
 emits a ReaderThreads threading constraint (see Threaders).
failToNonDet :: Eff NonDet m => FailToNonDetC m a -> m a Source #
Transform a Fail effect to a NonDet effect by having a
 pattern match failure be lose.
You can use this in application code to locally get access to a MonadFail
 instance (since FailToNonDetC has a MonadFail instance based
 on the Fail effect this interprets).
For example:
failToNonDet(do { Just a <- pure Nothing; return a}) =lose
Simple variants of interpretations
failToThrowSimple :: forall e m a p. (Eff (Throw e) m, Threaders '[ReaderThreads] m p) => (String -> e) -> InterpretFailSimpleC m a -> m a Source #
Transform a Fail effect to a Throw effect by providing a function
 to transform a pattern match failure into an exception.
This is a less performant version of failToThrow that doesn't have
 a higher-rank type, making it much easier to use partially applied.
Unlike failToThrow, you typically don't want to use this in
 application code, since this emits a ReaderThreads
 threading constraint (see Threaders).
Threading constraints
class (forall e. Threads (ExceptT e) p) => ErrorThreads p Source #
ErrorThreads accepts the following primitive effects:
- Regional- s
- Optional- s(when- sis a functor)
- BaseControl- b
- Unravel- p
- ListenPrim- o(when- ois a- Monoid)
- WriterPrim- o(when- ois a- Monoid)
- ReaderPrim- i
- Mask
- Bracket
- Fix
Instances
| (forall e. Threads (ExceptT e) p) => ErrorThreads p Source # | |
| Defined in Control.Effect.Internal.Error | |
Carriers
type FailC = CompositionC '[ReinterpretC FailH Fail '[Throw String], ThrowC String] Source #
newtype InterpretFailC h m a Source #
Like InterpretC specialized to interpret Fail, but with a MonadFail
 instance based on the interpreted Fail.
Constructors
| InterpretFailC | |
| Fields 
 | |
Instances
type InterpretFailReifiedC m a = forall s. ReifiesHandler s Fail m => InterpretFailC (ViaReifiedH s) m a Source #
type FailToNonDetC = InterpretFailC FailToNonDetH Source #
type FailToAltC = InterpretFailC FailToAltH Source #
newtype InterpretFailSimpleC m a Source #
Like InterpretSimpleC specialized to interpret Fail, but with
 a MonadFail instance based on the interpreted Fail.
Constructors
| InterpretFailSimpleC | |
| Fields | |