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

Control.Effect.Internal.Exceptional

Synopsis

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 waiting on that Async outside of the catching will throw that exception without it being caught.

Constructors

Exceptional (Union '[eff, Catch exc] m a) 

Instances

Instances details
(Member eff (Derivs m), Eff (Catch exc) m) => Handler ExceptionalH (Exceptional eff exc) m Source # 
Instance details

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 Error exc effect. Main combinators are catchSafe and trySafe.

newtype ExceptionallyC (eff :: Effect) (exc :: *) m a Source #

Constructors

ExceptionallyC 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> ExceptionallyC eff exc m α #

MonadBaseControl b m => MonadBaseControl b (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StM (ExceptionallyC eff exc m) a #

Methods

liftBaseWith :: (RunInBase (ExceptionallyC eff exc m) b -> b a) -> ExceptionallyC eff exc m a #

restoreM :: StM (ExceptionallyC eff exc m) a -> ExceptionallyC eff exc m a #

MonadTrans (ExceptionallyC eff exc :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> ExceptionallyC eff exc m a #

MonadTransControl (ExceptionallyC eff exc :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StT (ExceptionallyC eff exc) a #

Methods

liftWith :: Monad m => (Run (ExceptionallyC eff exc) -> m a) -> ExceptionallyC eff exc m a #

restoreT :: Monad m => m (StT (ExceptionallyC eff exc) a) -> ExceptionallyC eff exc m a #

Monad m => Monad (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

(>>=) :: ExceptionallyC eff exc m a -> (a -> ExceptionallyC eff exc m b) -> ExceptionallyC eff exc m b #

(>>) :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m b -> ExceptionallyC eff exc m b #

return :: a -> ExceptionallyC eff exc m a #

Functor m => Functor (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fmap :: (a -> b) -> ExceptionallyC eff exc m a -> ExceptionallyC eff exc m b #

(<$) :: a -> ExceptionallyC eff exc m b -> ExceptionallyC eff exc m a #

MonadFix m => MonadFix (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mfix :: (a -> ExceptionallyC eff exc m a) -> ExceptionallyC eff exc m a #

MonadFail m => MonadFail (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fail :: String -> ExceptionallyC eff exc m a #

Applicative m => Applicative (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

pure :: a -> ExceptionallyC eff exc m a #

(<*>) :: ExceptionallyC eff exc m (a -> b) -> ExceptionallyC eff exc m a -> ExceptionallyC eff exc m b #

liftA2 :: (a -> b -> c) -> ExceptionallyC eff exc m a -> ExceptionallyC eff exc m b -> ExceptionallyC eff exc m c #

(*>) :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m b -> ExceptionallyC eff exc m b #

(<*) :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m b -> ExceptionallyC eff exc m a #

MonadIO m => MonadIO (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftIO :: IO a -> ExceptionallyC eff exc m a #

Alternative m => Alternative (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

empty :: ExceptionallyC eff exc m a #

(<|>) :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m a -> ExceptionallyC eff exc m a #

some :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m [a] #

many :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m [a] #

MonadPlus m => MonadPlus (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mzero :: ExceptionallyC eff exc m a #

mplus :: ExceptionallyC eff exc m a -> ExceptionallyC eff exc m a -> ExceptionallyC eff exc m a #

MonadThrow m => MonadThrow (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

throwM :: Exception e => e -> ExceptionallyC eff exc m a #

MonadCatch m => MonadCatch (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

catch :: Exception e => ExceptionallyC eff exc m a -> (e -> ExceptionallyC eff exc m a) -> ExceptionallyC eff exc m a #

MonadMask m => MonadMask (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mask :: ((forall a. ExceptionallyC eff exc m a -> ExceptionallyC eff exc m a) -> ExceptionallyC eff exc m b) -> ExceptionallyC eff exc m b #

uninterruptibleMask :: ((forall a. ExceptionallyC eff exc m a -> ExceptionallyC eff exc m a) -> ExceptionallyC eff exc m b) -> ExceptionallyC eff exc m b #

generalBracket :: ExceptionallyC eff exc m a -> (a -> ExitCase b -> ExceptionallyC eff exc m c) -> (a -> ExceptionallyC eff exc m b) -> ExceptionallyC eff exc m (b, c) #

Eff (Exceptional eff exc) m => Carrier (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (ExceptionallyC eff exc m) :: [Effect] Source #

type Prims (ExceptionallyC eff exc m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ExceptionallyC eff exc m)) (ExceptionallyC eff exc m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ExceptionallyC eff exc m)) (Prims (ExceptionallyC eff exc m)) (ExceptionallyC eff exc m) z a Source #

algDerivs :: Algebra' (Derivs (ExceptionallyC eff exc m)) (ExceptionallyC eff exc m) a Source #

type StT (ExceptionallyC eff exc :: (Type -> Type) -> Type -> Type) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StT (ExceptionallyC eff exc :: (Type -> Type) -> Type -> Type) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Derivs (ExceptionallyC eff exc m) = Catch exc ': (eff ': Derivs m)
type Prims (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Prims (ExceptionallyC eff exc m) = Prims m
type StM (ExceptionallyC eff exc m) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (ExceptionallyC eff exc m) a = StM m a

data ExceptionalH Source #

Instances

Instances details
(Member eff (Derivs m), Eff (Catch exc) m) => Handler ExceptionalH (Exceptional eff exc) m Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

effHandler :: EffHandler (Exceptional eff exc) m Source #

newtype SafeErrorC exc m a Source #

Constructors

SafeErrorC 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorC exc m α #

MonadBaseControl b m => MonadBaseControl b (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StM (SafeErrorC exc m) a #

Methods

liftBaseWith :: (RunInBase (SafeErrorC exc m) b -> b a) -> SafeErrorC exc m a #

restoreM :: StM (SafeErrorC exc m) a -> SafeErrorC exc m a #

MonadTrans (SafeErrorC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorC exc m a #

MonadTransControl (SafeErrorC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StT (SafeErrorC exc) a #

Methods

liftWith :: Monad m => (Run (SafeErrorC exc) -> m a) -> SafeErrorC exc m a #

restoreT :: Monad m => m (StT (SafeErrorC exc) a) -> SafeErrorC exc m a #

Monad m => Monad (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

(>>=) :: SafeErrorC exc m a -> (a -> SafeErrorC exc m b) -> SafeErrorC exc m b #

(>>) :: SafeErrorC exc m a -> SafeErrorC exc m b -> SafeErrorC exc m b #

return :: a -> SafeErrorC exc m a #

Functor m => Functor (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fmap :: (a -> b) -> SafeErrorC exc m a -> SafeErrorC exc m b #

(<$) :: a -> SafeErrorC exc m b -> SafeErrorC exc m a #

MonadFix m => MonadFix (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mfix :: (a -> SafeErrorC exc m a) -> SafeErrorC exc m a #

MonadFail m => MonadFail (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fail :: String -> SafeErrorC exc m a #

Monad m => Applicative (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

pure :: a -> SafeErrorC exc m a #

(<*>) :: SafeErrorC exc m (a -> b) -> SafeErrorC exc m a -> SafeErrorC exc m b #

liftA2 :: (a -> b -> c) -> SafeErrorC exc m a -> SafeErrorC exc m b -> SafeErrorC exc m c #

(*>) :: SafeErrorC exc m a -> SafeErrorC exc m b -> SafeErrorC exc m b #

(<*) :: SafeErrorC exc m a -> SafeErrorC exc m b -> SafeErrorC exc m a #

MonadIO m => MonadIO (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftIO :: IO a -> SafeErrorC exc m a #

(Monad m, Monoid exc) => Alternative (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

empty :: SafeErrorC exc m a #

(<|>) :: SafeErrorC exc m a -> SafeErrorC exc m a -> SafeErrorC exc m a #

some :: SafeErrorC exc m a -> SafeErrorC exc m [a] #

many :: SafeErrorC exc m a -> SafeErrorC exc m [a] #

(Monad m, Monoid exc) => MonadPlus (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mzero :: SafeErrorC exc m a #

mplus :: SafeErrorC exc m a -> SafeErrorC exc m a -> SafeErrorC exc m a #

MonadThrow m => MonadThrow (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

throwM :: Exception e => e -> SafeErrorC exc m a #

MonadCatch m => MonadCatch (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

catch :: Exception e => SafeErrorC exc m a -> (e -> SafeErrorC exc m a) -> SafeErrorC exc m a #

MonadMask m => MonadMask (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mask :: ((forall a. SafeErrorC exc m a -> SafeErrorC exc m a) -> SafeErrorC exc m b) -> SafeErrorC exc m b #

uninterruptibleMask :: ((forall a. SafeErrorC exc m a -> SafeErrorC exc m a) -> SafeErrorC exc m b) -> SafeErrorC exc m b #

generalBracket :: SafeErrorC exc m a -> (a -> ExitCase b -> SafeErrorC exc m c) -> (a -> SafeErrorC exc m b) -> SafeErrorC exc m (b, c) #

(Carrier m, Threads (ExceptT exc) (Prims m)) => Carrier (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorC exc m) :: [Effect] Source #

type Prims (SafeErrorC exc m) :: [Effect] Source #

type StT (SafeErrorC exc) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StT (SafeErrorC exc) a = StT (CompositionBaseT '[IntroUnderC (SafeError exc) '[Catch exc, Throw exc], SafeErrorToErrorC exc, ErrorC exc]) a
type Derivs (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Derivs (SafeErrorC exc m) = Derivs (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorC exc m)))
type Prims (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Prims (SafeErrorC exc m) = Prims (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorC exc m)))
type StM (SafeErrorC exc m) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (SafeErrorC exc m) a = StM (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorC exc m))) a

newtype SafeErrorToIOC' s s' exc m a Source #

Constructors

SafeErrorToIOC' 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToIOC' s s' exc m α #

MonadBaseControl b m => MonadBaseControl b (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StM (SafeErrorToIOC' s s' exc m) a #

Methods

liftBaseWith :: (RunInBase (SafeErrorToIOC' s s' exc m) b -> b a) -> SafeErrorToIOC' s s' exc m a #

restoreM :: StM (SafeErrorToIOC' s s' exc m) a -> SafeErrorToIOC' s s' exc m a #

MonadTrans (SafeErrorToIOC' s s' exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToIOC' s s' exc m a #

MonadTransControl (SafeErrorToIOC' s s' exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StT (SafeErrorToIOC' s s' exc) a #

Methods

liftWith :: Monad m => (Run (SafeErrorToIOC' s s' exc) -> m a) -> SafeErrorToIOC' s s' exc m a #

restoreT :: Monad m => m (StT (SafeErrorToIOC' s s' exc) a) -> SafeErrorToIOC' s s' exc m a #

Monad m => Monad (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

(>>=) :: SafeErrorToIOC' s s' exc m a -> (a -> SafeErrorToIOC' s s' exc m b) -> SafeErrorToIOC' s s' exc m b #

(>>) :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m b -> SafeErrorToIOC' s s' exc m b #

return :: a -> SafeErrorToIOC' s s' exc m a #

Functor m => Functor (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fmap :: (a -> b) -> SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m b #

(<$) :: a -> SafeErrorToIOC' s s' exc m b -> SafeErrorToIOC' s s' exc m a #

MonadFix m => MonadFix (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mfix :: (a -> SafeErrorToIOC' s s' exc m a) -> SafeErrorToIOC' s s' exc m a #

MonadFail m => MonadFail (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fail :: String -> SafeErrorToIOC' s s' exc m a #

Applicative m => Applicative (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

pure :: a -> SafeErrorToIOC' s s' exc m a #

(<*>) :: SafeErrorToIOC' s s' exc m (a -> b) -> SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m b #

liftA2 :: (a -> b -> c) -> SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m b -> SafeErrorToIOC' s s' exc m c #

(*>) :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m b -> SafeErrorToIOC' s s' exc m b #

(<*) :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m b -> SafeErrorToIOC' s s' exc m a #

MonadIO m => MonadIO (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftIO :: IO a -> SafeErrorToIOC' s s' exc m a #

Alternative m => Alternative (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

empty :: SafeErrorToIOC' s s' exc m a #

(<|>) :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m a #

some :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m [a] #

many :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m [a] #

MonadPlus m => MonadPlus (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mzero :: SafeErrorToIOC' s s' exc m a #

mplus :: SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m a #

MonadThrow m => MonadThrow (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

throwM :: Exception e => e -> SafeErrorToIOC' s s' exc m a #

MonadCatch m => MonadCatch (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

catch :: Exception e => SafeErrorToIOC' s s' exc m a -> (e -> SafeErrorToIOC' s s' exc m a) -> SafeErrorToIOC' s s' exc m a #

MonadMask m => MonadMask (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mask :: ((forall a. SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m a) -> SafeErrorToIOC' s s' exc m b) -> SafeErrorToIOC' s s' exc m b #

uninterruptibleMask :: ((forall a. SafeErrorToIOC' s s' exc m a -> SafeErrorToIOC' s s' exc m a) -> SafeErrorToIOC' s s' exc m b) -> SafeErrorToIOC' s s' exc m b #

generalBracket :: SafeErrorToIOC' s s' exc m a -> (a -> ExitCase b -> SafeErrorToIOC' s s' exc m c) -> (a -> SafeErrorToIOC' s s' exc m b) -> SafeErrorToIOC' s s' exc m (b, c) #

(Eff (Embed IO) m, MonadCatch m, ReifiesErrorHandler s s' exc (ErrorIOToIOC m)) => Carrier (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorToIOC' s s' exc m) :: [Effect] Source #

type Prims (SafeErrorToIOC' s s' exc m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (SafeErrorToIOC' s s' exc m)) (SafeErrorToIOC' s s' exc m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (SafeErrorToIOC' s s' exc m)) (Prims (SafeErrorToIOC' s s' exc m)) (SafeErrorToIOC' s s' exc m) z a Source #

algDerivs :: Algebra' (Derivs (SafeErrorToIOC' s s' exc m)) (SafeErrorToIOC' s s' exc m) a Source #

type StT (SafeErrorToIOC' s s' exc) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StT (SafeErrorToIOC' s s' exc) a = StT (CompositionBaseT '[IntroUnderC (SafeError exc) '[Catch exc, Throw exc], SafeErrorToErrorC exc, ErrorToIOC' s s' exc]) a
type Derivs (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Derivs (SafeErrorToIOC' s s' exc m) = Derivs (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorToIOC' s s' exc m)))
type Prims (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Prims (SafeErrorToIOC' s s' exc m) = Prims (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorToIOC' s s' exc m)))
type StM (SafeErrorToIOC' s s' exc m) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (SafeErrorToIOC' s s' exc m) a = StM (IntroC '[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 Source #

newtype SafeErrorToErrorIOC' s s' exc m a Source #

Constructors

SafeErrorToErrorIOC' 

Instances

Instances details
MonadBase b m => MonadBase b (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToErrorIOC' s s' exc m α #

MonadBaseControl b m => MonadBaseControl b (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StM (SafeErrorToErrorIOC' s s' exc m) a #

Methods

liftBaseWith :: (RunInBase (SafeErrorToErrorIOC' s s' exc m) b -> b a) -> SafeErrorToErrorIOC' s s' exc m a #

restoreM :: StM (SafeErrorToErrorIOC' s s' exc m) a -> SafeErrorToErrorIOC' s s' exc m a #

MonadTrans (SafeErrorToErrorIOC' s s' exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToErrorIOC' s s' exc m a #

MonadTransControl (SafeErrorToErrorIOC' s s' exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StT (SafeErrorToErrorIOC' s s' exc) a #

Methods

liftWith :: Monad m => (Run (SafeErrorToErrorIOC' s s' exc) -> m a) -> SafeErrorToErrorIOC' s s' exc m a #

restoreT :: Monad m => m (StT (SafeErrorToErrorIOC' s s' exc) a) -> SafeErrorToErrorIOC' s s' exc m a #

Monad m => Monad (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

(>>=) :: SafeErrorToErrorIOC' s s' exc m a -> (a -> SafeErrorToErrorIOC' s s' exc m b) -> SafeErrorToErrorIOC' s s' exc m b #

(>>) :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m b -> SafeErrorToErrorIOC' s s' exc m b #

return :: a -> SafeErrorToErrorIOC' s s' exc m a #

Functor m => Functor (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fmap :: (a -> b) -> SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m b #

(<$) :: a -> SafeErrorToErrorIOC' s s' exc m b -> SafeErrorToErrorIOC' s s' exc m a #

MonadFix m => MonadFix (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mfix :: (a -> SafeErrorToErrorIOC' s s' exc m a) -> SafeErrorToErrorIOC' s s' exc m a #

MonadFail m => MonadFail (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fail :: String -> SafeErrorToErrorIOC' s s' exc m a #

Applicative m => Applicative (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

pure :: a -> SafeErrorToErrorIOC' s s' exc m a #

(<*>) :: SafeErrorToErrorIOC' s s' exc m (a -> b) -> SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m b #

liftA2 :: (a -> b -> c) -> SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m b -> SafeErrorToErrorIOC' s s' exc m c #

(*>) :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m b -> SafeErrorToErrorIOC' s s' exc m b #

(<*) :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m b -> SafeErrorToErrorIOC' s s' exc m a #

MonadIO m => MonadIO (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftIO :: IO a -> SafeErrorToErrorIOC' s s' exc m a #

Alternative m => Alternative (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

empty :: SafeErrorToErrorIOC' s s' exc m a #

(<|>) :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m a #

some :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m [a] #

many :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m [a] #

MonadPlus m => MonadPlus (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mzero :: SafeErrorToErrorIOC' s s' exc m a #

mplus :: SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m a #

MonadThrow m => MonadThrow (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

throwM :: Exception e => e -> SafeErrorToErrorIOC' s s' exc m a #

MonadCatch m => MonadCatch (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

catch :: Exception e => SafeErrorToErrorIOC' s s' exc m a -> (e -> SafeErrorToErrorIOC' s s' exc m a) -> SafeErrorToErrorIOC' s s' exc m a #

MonadMask m => MonadMask (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mask :: ((forall a. SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m a) -> SafeErrorToErrorIOC' s s' exc m b) -> SafeErrorToErrorIOC' s s' exc m b #

uninterruptibleMask :: ((forall a. SafeErrorToErrorIOC' s s' exc m a -> SafeErrorToErrorIOC' s s' exc m a) -> SafeErrorToErrorIOC' s s' exc m b) -> SafeErrorToErrorIOC' s s' exc m b #

generalBracket :: SafeErrorToErrorIOC' s s' exc m a -> (a -> ExitCase b -> SafeErrorToErrorIOC' s s' exc m c) -> (a -> SafeErrorToErrorIOC' s s' exc m b) -> SafeErrorToErrorIOC' s s' exc m (b, c) #

(Carrier m, ReifiesErrorHandler s s' exc m) => Carrier (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorToErrorIOC' s s' exc m) :: [Effect] Source #

type Prims (SafeErrorToErrorIOC' s s' exc m) :: [Effect] Source #

type StT (SafeErrorToErrorIOC' s s' exc) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Derivs (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Derivs (SafeErrorToErrorIOC' s s' exc m) = Derivs (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (InterpretErrorC' s s' exc m)))
type Prims (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Prims (SafeErrorToErrorIOC' s s' exc m) = Prims (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (InterpretErrorC' s s' exc m)))
type StM (SafeErrorToErrorIOC' s s' exc m) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (SafeErrorToErrorIOC' s s' exc m) a = StM (IntroC '[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 Source #

newtype SafeErrorToIOSimpleC exc m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToIOSimpleC exc m α #

MonadBaseControl b m => MonadBaseControl b (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StM (SafeErrorToIOSimpleC exc m) a #

MonadTrans (SafeErrorToIOSimpleC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToIOSimpleC exc m a #

Monad m => Monad (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

(>>=) :: SafeErrorToIOSimpleC exc m a -> (a -> SafeErrorToIOSimpleC exc m b) -> SafeErrorToIOSimpleC exc m b #

(>>) :: SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m b -> SafeErrorToIOSimpleC exc m b #

return :: a -> SafeErrorToIOSimpleC exc m a #

Functor m => Functor (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fmap :: (a -> b) -> SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m b #

(<$) :: a -> SafeErrorToIOSimpleC exc m b -> SafeErrorToIOSimpleC exc m a #

MonadFix m => MonadFix (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mfix :: (a -> SafeErrorToIOSimpleC exc m a) -> SafeErrorToIOSimpleC exc m a #

MonadFail m => MonadFail (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fail :: String -> SafeErrorToIOSimpleC exc m a #

Applicative m => Applicative (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

pure :: a -> SafeErrorToIOSimpleC exc m a #

(<*>) :: SafeErrorToIOSimpleC exc m (a -> b) -> SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m b #

liftA2 :: (a -> b -> c) -> SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m b -> SafeErrorToIOSimpleC exc m c #

(*>) :: SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m b -> SafeErrorToIOSimpleC exc m b #

(<*) :: SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m b -> SafeErrorToIOSimpleC exc m a #

MonadIO m => MonadIO (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftIO :: IO a -> SafeErrorToIOSimpleC exc m a #

Alternative m => Alternative (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

MonadPlus m => MonadPlus (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

MonadThrow m => MonadThrow (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

throwM :: Exception e => e -> SafeErrorToIOSimpleC exc m a #

MonadCatch m => MonadCatch (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

catch :: Exception e => SafeErrorToIOSimpleC exc m a -> (e -> SafeErrorToIOSimpleC exc m a) -> SafeErrorToIOSimpleC exc m a #

MonadMask m => MonadMask (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mask :: ((forall a. SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m a) -> SafeErrorToIOSimpleC exc m b) -> SafeErrorToIOSimpleC exc m b #

uninterruptibleMask :: ((forall a. SafeErrorToIOSimpleC exc m a -> SafeErrorToIOSimpleC exc m a) -> SafeErrorToIOSimpleC exc m b) -> SafeErrorToIOSimpleC exc m b #

generalBracket :: SafeErrorToIOSimpleC exc m a -> (a -> ExitCase b -> SafeErrorToIOSimpleC exc m c) -> (a -> SafeErrorToIOSimpleC exc m b) -> SafeErrorToIOSimpleC exc m (b, c) #

(Eff (Embed IO) m, MonadCatch m, Threaders '[ReaderThreads] m p) => Carrier (SafeErrorToIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorToIOSimpleC e m) :: [Effect] Source #

type Prims (SafeErrorToIOSimpleC e m) :: [Effect] Source #

type Derivs (SafeErrorToIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Prims (SafeErrorToIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (SafeErrorToIOSimpleC exc m) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (SafeErrorToIOSimpleC exc m) a = StM (IntroC '[SafeError exc] '[Catch exc, Throw exc] (SafeErrorToErrorC exc (ErrorToIOSimpleC exc m))) a

newtype SafeErrorToErrorIOSimpleC exc m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToErrorIOSimpleC exc m α #

MonadBaseControl b m => MonadBaseControl b (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type StM (SafeErrorToErrorIOSimpleC exc m) a #

MonadTrans (SafeErrorToErrorIOSimpleC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToErrorIOSimpleC exc m a #

Monad m => Monad (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Functor m => Functor (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fmap :: (a -> b) -> SafeErrorToErrorIOSimpleC exc m a -> SafeErrorToErrorIOSimpleC exc m b #

(<$) :: a -> SafeErrorToErrorIOSimpleC exc m b -> SafeErrorToErrorIOSimpleC exc m a #

MonadFix m => MonadFix (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

mfix :: (a -> SafeErrorToErrorIOSimpleC exc m a) -> SafeErrorToErrorIOSimpleC exc m a #

MonadFail m => MonadFail (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

fail :: String -> SafeErrorToErrorIOSimpleC exc m a #

Applicative m => Applicative (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

MonadIO m => MonadIO (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftIO :: IO a -> SafeErrorToErrorIOSimpleC exc m a #

Alternative m => Alternative (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

MonadPlus m => MonadPlus (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

MonadThrow m => MonadThrow (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

throwM :: Exception e => e -> SafeErrorToErrorIOSimpleC exc m a #

MonadCatch m => MonadCatch (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

MonadMask m => MonadMask (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

(Carrier m, Threaders '[ReaderThreads] m p) => Carrier (SafeErrorToErrorIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Derivs (SafeErrorToErrorIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type Prims (SafeErrorToErrorIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

type StM (SafeErrorToErrorIOSimpleC exc m) a Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional