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

Control.Effect.Carrier.Internal.Intro

Synopsis

Documentation

newtype IntroC (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a Source #

Constructors

IntroC 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

liftBase :: b α -> IntroC top new m α #

MonadBaseControl b m => MonadBaseControl b (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type StM (IntroC top new m) a #

Methods

liftBaseWith :: (RunInBase (IntroC top new m) b -> b a) -> IntroC top new m a #

restoreM :: StM (IntroC top new m) a -> IntroC top new m a #

MonadTrans (IntroC top new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

lift :: Monad m => m a -> IntroC top new m a #

MonadTransControl (IntroC top new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type StT (IntroC top new) a #

Methods

liftWith :: Monad m => (Run (IntroC top new) -> m a) -> IntroC top new m a #

restoreT :: Monad m => m (StT (IntroC top new) a) -> IntroC top new m a #

Monad m => Monad (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

(>>=) :: IntroC top new m a -> (a -> IntroC top new m b) -> IntroC top new m b #

(>>) :: IntroC top new m a -> IntroC top new m b -> IntroC top new m b #

return :: a -> IntroC top new m a #

Functor m => Functor (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

fmap :: (a -> b) -> IntroC top new m a -> IntroC top new m b #

(<$) :: a -> IntroC top new m b -> IntroC top new m a #

MonadFix m => MonadFix (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

mfix :: (a -> IntroC top new m a) -> IntroC top new m a #

MonadFail m => MonadFail (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

fail :: String -> IntroC top new m a #

Applicative m => Applicative (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

pure :: a -> IntroC top new m a #

(<*>) :: IntroC top new m (a -> b) -> IntroC top new m a -> IntroC top new m b #

liftA2 :: (a -> b -> c) -> IntroC top new m a -> IntroC top new m b -> IntroC top new m c #

(*>) :: IntroC top new m a -> IntroC top new m b -> IntroC top new m b #

(<*) :: IntroC top new m a -> IntroC top new m b -> IntroC top new m a #

MonadIO m => MonadIO (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

liftIO :: IO a -> IntroC top new m a #

Alternative m => Alternative (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

empty :: IntroC top new m a #

(<|>) :: IntroC top new m a -> IntroC top new m a -> IntroC top new m a #

some :: IntroC top new m a -> IntroC top new m [a] #

many :: IntroC top new m a -> IntroC top new m [a] #

MonadPlus m => MonadPlus (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

mzero :: IntroC top new m a #

mplus :: IntroC top new m a -> IntroC top new m a -> IntroC top new m a #

MonadThrow m => MonadThrow (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

throwM :: Exception e => e -> IntroC top new m a #

MonadCatch m => MonadCatch (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

catch :: Exception e => IntroC top new m a -> (e -> IntroC top new m a) -> IntroC top new m a #

MonadMask m => MonadMask (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

mask :: ((forall a. IntroC top new m a -> IntroC top new m a) -> IntroC top new m b) -> IntroC top new m b #

uninterruptibleMask :: ((forall a. IntroC top new m a -> IntroC top new m a) -> IntroC top new m b) -> IntroC top new m b #

generalBracket :: IntroC top new m a -> (a -> ExitCase b -> IntroC top new m c) -> (a -> IntroC top new m b) -> IntroC top new m (b, c) #

(Carrier m, KnownList top, KnownList new, IntroConsistent top new m) => Carrier (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type Derivs (IntroC top new m) :: [Effect] Source #

type Prims (IntroC top new m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (IntroC top new m)) (IntroC top new m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (IntroC top new m)) (Prims (IntroC top new m)) (IntroC top new m) z a Source #

algDerivs :: Algebra' (Derivs (IntroC top new m)) (IntroC top new m) a Source #

type StT (IntroC top new) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type StT (IntroC top new) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type Derivs (IntroC top new m) = Append top (RestDerivs top new m)
type Prims (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type Prims (IntroC top new m) = Prims m
type StM (IntroC top new m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type StM (IntroC top new m) a = StM m a

type RestDerivs top new m = StripPrefix new (StripPrefix top (Derivs m)) Source #

type IntroUnderC e = IntroC '[e] Source #

type IntroUnderManyC = IntroC Source #

Synonym for IntroC to match introUnderMany

type HeadEff e m = (IntroConsistent '[] '[e] m, Carrier m) Source #

A constraint that the effect stack of m -- Derivs m -- begins with the effect e.

Note that unlike Eff, this does not give Bundle special treatment.

type HeadEffs new m = (IntroConsistent '[] new m, Carrier m) Source #

A constraint that the effect stack of m -- Derivs m -- begins with new.

Note that unlike Effs, this does not give Bundle special treatment.

type IntroConsistent top new m = Append top (Append new (StripPrefix new (StripPrefix top (Derivs m)))) ~ Derivs m Source #

A constraint that the effect stack of m -- Derivs m -- begins with Append top new.

introUnderMany :: forall top new m a. (KnownList top, KnownList new, IntroConsistent top new m) => IntroUnderManyC top new m a -> m a Source #

Introduce multiple effects under a number of top effects of the effect stack -- or rather, reveal those effects which were previously hidden.

Derivs (IntroC top new m) = Append top (StripPrefix (Append top new) (Derivs m))

introUnder :: forall new e m a. (KnownList new, IntroConsistent '[e] new m) => IntroUnderC e new m a -> m a Source #

Introduce multiple effects under the top effect of the effect stack -- or rather, reveal those effects which were previously hidden.

Derivs (IntroUnderC e new m) = e ': StripPrefix (e ': new) (Derivs m)

introUnder1 :: forall new e m a. IntroConsistent '[e] '[new] m => IntroUnderC e '[new] m a -> m a Source #

Introduce an effect under the top effect of the effect stack -- or rather, reveal that effect which was previously hidden.

Derivs (IntroUnderC e '[new] m) = e ': StripPrefix [e, new] (Derivs m)

intro :: forall new m a. (KnownList new, IntroConsistent '[] new m) => IntroTopC new m a -> m a Source #

Introduce multiple effects on the top of the effect stack -- or rather, reveal effects previously hidden.

Derivs (IntroTopC new m) = StripPrefix new (Derivs m)

intro1 :: forall e m a. IntroConsistent '[] '[e] m => IntroTopC '[e] m a -> m a Source #

Introduce an effect at the top of the stack -- or rather, reveal an effect previously hidden.

Derivs (IntroTopC [e] m) = StripPrefix '[e] (Derivs m)