in-other-words-0.1.1.0: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Fail

Synopsis

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.

Constructors

Fail :: String -> Fail m a 

Interpretations

runFail :: forall m a p. (Threaders '[ErrorThreads] m p, Carrier m) => FailC m a -> m (Either String a) Source #

Run a Fail effect purely, by returning Left failureMessage upon a pattern match failure.

FailC has an MonadFail instance based on the Fail effect it interprets.

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 (\_ -> throw exc) (do { Just a <- pure Nothing; return a})
= throw exc

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

failToAlt :: Eff Alt m => FailToAltC m a -> m a Source #

Transform a Fail effect to an Alt effect by having a pattern match failure be empty.

You can use this in application code to locally get access to a MonadFail instance (since FailToAltC has a MonadFail instance based on the Fail effect this interprets).

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:

Instances

Instances details
(forall e. Threads (ExceptT e) p) => ErrorThreads p Source # 
Instance details

Defined in Control.Effect.Internal.Error

Carriers

newtype InterpretFailC h m a Source #

Like InterpretC specialized to interpret Fail, but with a MonadFail instance based on the interpreted Fail.

Constructors

InterpretFailC 

Instances

Instances details
MonadBase b m => MonadBase b (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftBase :: b α -> InterpretFailC h m α #

MonadBaseControl b m => MonadBaseControl b (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type StM (InterpretFailC h m) a #

Methods

liftBaseWith :: (RunInBase (InterpretFailC h m) b -> b a) -> InterpretFailC h m a #

restoreM :: StM (InterpretFailC h m) a -> InterpretFailC h m a #

MonadTrans (InterpretFailC h) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

lift :: Monad m => m a -> InterpretFailC h m a #

MonadTransControl (InterpretFailC h) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type StT (InterpretFailC h) a #

Methods

liftWith :: Monad m => (Run (InterpretFailC h) -> m a) -> InterpretFailC h m a #

restoreT :: Monad m => m (StT (InterpretFailC h) a) -> InterpretFailC h m a #

Monad m => Monad (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

(>>=) :: InterpretFailC h m a -> (a -> InterpretFailC h m b) -> InterpretFailC h m b #

(>>) :: InterpretFailC h m a -> InterpretFailC h m b -> InterpretFailC h m b #

return :: a -> InterpretFailC h m a #

Functor m => Functor (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

fmap :: (a -> b) -> InterpretFailC h m a -> InterpretFailC h m b #

(<$) :: a -> InterpretFailC h m b -> InterpretFailC h m a #

MonadFix m => MonadFix (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

mfix :: (a -> InterpretFailC h m a) -> InterpretFailC h m a #

Handler h Fail m => MonadFail (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

fail :: String -> InterpretFailC h m a #

Applicative m => Applicative (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

pure :: a -> InterpretFailC h m a #

(<*>) :: InterpretFailC h m (a -> b) -> InterpretFailC h m a -> InterpretFailC h m b #

liftA2 :: (a -> b -> c) -> InterpretFailC h m a -> InterpretFailC h m b -> InterpretFailC h m c #

(*>) :: InterpretFailC h m a -> InterpretFailC h m b -> InterpretFailC h m b #

(<*) :: InterpretFailC h m a -> InterpretFailC h m b -> InterpretFailC h m a #

MonadIO m => MonadIO (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftIO :: IO a -> InterpretFailC h m a #

Alternative m => Alternative (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

empty :: InterpretFailC h m a #

(<|>) :: InterpretFailC h m a -> InterpretFailC h m a -> InterpretFailC h m a #

some :: InterpretFailC h m a -> InterpretFailC h m [a] #

many :: InterpretFailC h m a -> InterpretFailC h m [a] #

MonadPlus m => MonadPlus (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

mzero :: InterpretFailC h m a #

mplus :: InterpretFailC h m a -> InterpretFailC h m a -> InterpretFailC h m a #

MonadThrow m => MonadThrow (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

throwM :: Exception e => e -> InterpretFailC h m a #

MonadCatch m => MonadCatch (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

catch :: Exception e => InterpretFailC h m a -> (e -> InterpretFailC h m a) -> InterpretFailC h m a #

MonadMask m => MonadMask (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

mask :: ((forall a. InterpretFailC h m a -> InterpretFailC h m a) -> InterpretFailC h m b) -> InterpretFailC h m b #

uninterruptibleMask :: ((forall a. InterpretFailC h m a -> InterpretFailC h m a) -> InterpretFailC h m b) -> InterpretFailC h m b #

generalBracket :: InterpretFailC h m a -> (a -> ExitCase b -> InterpretFailC h m c) -> (a -> InterpretFailC h m b) -> InterpretFailC h m (b, c) #

Handler h Fail m => Carrier (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type Derivs (InterpretFailC h m) :: [Effect] Source #

type Prims (InterpretFailC h m) :: [Effect] Source #

type StT (InterpretFailC h) a Source # 
Instance details

Defined in Control.Effect.Fail

type StT (InterpretFailC h) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

type Prims (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

type StM (InterpretFailC h m) a Source # 
Instance details

Defined in Control.Effect.Fail

type StM (InterpretFailC h m) a = StM (InterpretC h Fail m) a

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.

Instances

Instances details
MonadTrans InterpretFailSimpleC Source # 
Instance details

Defined in Control.Effect.Fail

Methods

lift :: Monad m => m a -> InterpretFailSimpleC m a #

MonadBase b m => MonadBase b (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftBase :: b α -> InterpretFailSimpleC m α #

MonadBaseControl b m => MonadBaseControl b (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type StM (InterpretFailSimpleC m) a #

Monad m => Monad (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Functor m => Functor (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

MonadFix m => MonadFix (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

mfix :: (a -> InterpretFailSimpleC m a) -> InterpretFailSimpleC m a #

(Monad m, Carrier (InterpretSimpleC Fail m)) => MonadFail (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Applicative m => Applicative (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

MonadIO m => MonadIO (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftIO :: IO a -> InterpretFailSimpleC m a #

Alternative m => Alternative (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

MonadPlus m => MonadPlus (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

MonadThrow m => MonadThrow (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

throwM :: Exception e => e -> InterpretFailSimpleC m a #

MonadCatch m => MonadCatch (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

MonadMask m => MonadMask (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

(Monad m, Carrier (InterpretSimpleC Fail m)) => Carrier (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type Derivs (InterpretFailSimpleC m) :: [Effect] Source #

type Prims (InterpretFailSimpleC m) :: [Effect] Source #

type Derivs (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

type Prims (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

type StM (InterpretFailSimpleC m) a Source # 
Instance details

Defined in Control.Effect.Fail