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

Control.Effect.Intercept

Synopsis

Effects

data Intercept (e :: Effect) :: Effect where Source #

An effect for intercepting actions of a first-order effect.

Even for this library, proper usage of this effect is very complicated. When properly used, this can be a very useful helper effect, allowing you write interpretations for a class of higher-order effects that wouldn't otherwise be possible.

For more information, see the wiki.

Constructors

Intercept :: Coercible z m => (forall x. e z x -> m x) -> m a -> Intercept e m a 

Instances

Instances details
(FirstOrder e, Eff (Unravel (InterceptB e)) m) => Handler InterceptH (Intercept e) m Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

data InterceptCont (e :: Effect) :: Effect where Source #

A variant of InterceptCont that is significantly more powerful, allowing you to capture the continuation of the program at each use-site of an effect, as well as aborting execution of the parameter computation early.

Constructors

InterceptCont :: Coercible z m => InterceptionMode -> (forall x. (x -> m a) -> e z x -> m a) -> m a -> InterceptCont e m a 

Instances

Instances details
(FirstOrder e, Member e (Derivs m), Eff (Unravel (InterceptB e)) m) => Handler InterceptH (InterceptCont e) m Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Actions

intercept :: Eff (Intercept e) m => (forall x. e m x -> m x) -> m a -> m a Source #

Intercept all uses of an effect within a region.

interceptCont :: Eff (InterceptCont e) m => (forall x. (x -> m a) -> e m x -> m a) -> m a -> m a Source #

Intercept all uses of an effect within a region -- and at each use-site, capture the continuation of the argument computation, and also allow for early abortion (by not invoking the continuation).

interceptCont1 :: Eff (InterceptCont e) m => (forall x. (x -> m a) -> e m x -> m a) -> m a -> m a Source #

Intercept only the first use of an effect within a region -- and at that use-site, capture the continuation of the argument computation, and also allow for early abortion (by not invoking the continuation).

Interpretations

runInterceptCont :: forall e m a p. (FirstOrder e, Carrier m, Member e (Derivs m), Threaders '[SteppedThreads] m p) => InterceptContC e m a -> m a Source #

Run Intercept e, InterceptCont e and e effects, provided that e is first-order and also part of the remaining effect stack.

There are three very important things to note here:

  • e must be first-order.
  • Any action of e made by a handler run after runInterceptCont won't get be intercepted. What this means is that you typically want to run the handler for e immediately after runInterceptCont.
  • This imposes the very restrictive primitive effect Unravel. Most notably, neither StateThreads nor WriterThreads accepts it. Because of that, this module offers various alternatives of several common State and Tell interpreters with threading constraints that do accept Unravel.
Derivs (InterceptContC e m) = InterceptCont e ': Intercept e ': e ': Derivs m
Prims  (InterceptContC e m) = Unravel (InterceptB e) ': Prims m

runInterceptR :: forall e m a p. (FirstOrder e, Member e (Derivs m), Carrier m, Threaders '[ReaderThreads] m p) => InterceptRC e m a -> m a Source #

Run Intercept e and e effects, provided e is first-order and part of the effect stack.

runInterceptR differs from runInterceptCont in four different ways:

There are some interpreters -- such as bracketToIO and concToIO -- that runInterceptCont can't be used together with in any capacity due to its SteppedThreads threading constraint. In these cases, runInterceptR can be used instead.

Derivs (InterceptRC e m) = Intercept e ': e ': 'Derivs m'
Prims  (InterceptRC e m) = Unlift (ReaderT (ReifiedFOHandler e m)) ': 'Derivs m'

Interpretations for other effects

runStateStepped :: forall s m a p. (Carrier m, Threaders '[SteppedThreads] m p) => s -> SteppedC (State s) m a -> m (s, a) Source #

A variant of runState with a SteppedThreads threading constraint instead of a StateThreads threading constraint.

runTellStepped :: forall w m a p. (Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => SteppedC (Tell w) m a -> m (w, a) Source #

A variant of runTell with a SteppedThreads threading constraint instead of a StateThreads threading constraint.

runTellListStepped :: forall o m a p. (Carrier m, Threaders '[SteppedThreads] m p) => SteppedC (Tell o) m a -> m ([o], a) Source #

A variant of runTell with a SteppedThreads threading constraint instead of a StateThreads threading constraint.

runListenStepped :: forall w m a p. (Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => ListenSteppedC w m a -> m (w, a) Source #

A variant of runListen with a SteppedThreads threading constraint instead of a StateThreads threading constraint.

Derivs (ListenSteppedC w m) = Listen w ': Tell w ': Derivs m
Prims (ListenSteppedC w m) = ListenPrim w ': Derivs m

Threading constraints

type SteppedThreads = FreeThreads Source #

SteppedThreads accepts the following primitive effects:

Carriers

data InterceptRC (e :: Effect) m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

liftBase :: b α -> InterceptRC e m α #

MonadBaseControl b m => MonadBaseControl b (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Associated Types

type StM (InterceptRC e m) a #

Methods

liftBaseWith :: (RunInBase (InterceptRC e m) b -> b a) -> InterceptRC e m a #

restoreM :: StM (InterceptRC e m) a -> InterceptRC e m a #

MonadTrans (InterceptRC e) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

lift :: Monad m => m a -> InterceptRC e m a #

Monad m => Monad (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

(>>=) :: InterceptRC e m a -> (a -> InterceptRC e m b) -> InterceptRC e m b #

(>>) :: InterceptRC e m a -> InterceptRC e m b -> InterceptRC e m b #

return :: a -> InterceptRC e m a #

Functor m => Functor (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

fmap :: (a -> b) -> InterceptRC e m a -> InterceptRC e m b #

(<$) :: a -> InterceptRC e m b -> InterceptRC e m a #

MonadFix m => MonadFix (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

mfix :: (a -> InterceptRC e m a) -> InterceptRC e m a #

MonadFail m => MonadFail (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

fail :: String -> InterceptRC e m a #

Applicative m => Applicative (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

pure :: a -> InterceptRC e m a #

(<*>) :: InterceptRC e m (a -> b) -> InterceptRC e m a -> InterceptRC e m b #

liftA2 :: (a -> b -> c) -> InterceptRC e m a -> InterceptRC e m b -> InterceptRC e m c #

(*>) :: InterceptRC e m a -> InterceptRC e m b -> InterceptRC e m b #

(<*) :: InterceptRC e m a -> InterceptRC e m b -> InterceptRC e m a #

MonadIO m => MonadIO (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

liftIO :: IO a -> InterceptRC e m a #

Alternative m => Alternative (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

empty :: InterceptRC e m a #

(<|>) :: InterceptRC e m a -> InterceptRC e m a -> InterceptRC e m a #

some :: InterceptRC e m a -> InterceptRC e m [a] #

many :: InterceptRC e m a -> InterceptRC e m [a] #

MonadPlus m => MonadPlus (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

mzero :: InterceptRC e m a #

mplus :: InterceptRC e m a -> InterceptRC e m a -> InterceptRC e m a #

MonadThrow m => MonadThrow (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

throwM :: Exception e0 => e0 -> InterceptRC e m a #

MonadCatch m => MonadCatch (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

catch :: Exception e0 => InterceptRC e m a -> (e0 -> InterceptRC e m a) -> InterceptRC e m a #

MonadMask m => MonadMask (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

mask :: ((forall a. InterceptRC e m a -> InterceptRC e m a) -> InterceptRC e m b) -> InterceptRC e m b #

uninterruptibleMask :: ((forall a. InterceptRC e m a -> InterceptRC e m a) -> InterceptRC e m b) -> InterceptRC e m b #

generalBracket :: InterceptRC e m a -> (a -> ExitCase b -> InterceptRC e m c) -> (a -> InterceptRC e m b) -> InterceptRC e m (b, c) #

(FirstOrder e, Carrier m, Threads (ReaderT (ReifiedFOHandler e m)) (Prims m)) => Carrier (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Associated Types

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

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

type Derivs (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

type Derivs (InterceptRC e m) = Intercept e ': (e ': Derivs m)
type Prims (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

type StM (InterceptRC e m) a Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

type StM (InterceptRC e m) a = StM (ReaderT (ReifiedFOHandler e m) m) a

data SteppedC (e :: Effect) m a Source #

A carrier for any first-order effect e that allows for dividing a computation into several steps, where each step is seperated by the use of the effect.

This can be used to implement coroutines.

Instances

Instances details
(Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => PrimHandler ListenSteppedH (ListenPrim w) (SteppedC (Tell w :: (Type -> Type) -> Type -> Type) m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

(FirstOrder e, Carrier m, Threaders '[SteppedThreads] m p) => PrimHandler InterceptH (Unravel (InterceptB e)) (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

MonadBase b m => MonadBase b (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

liftBase :: b α -> SteppedC e m α #

MonadTrans (SteppedC e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

lift :: Monad m => m a -> SteppedC e m a #

Monad (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

(>>=) :: SteppedC e m a -> (a -> SteppedC e m b) -> SteppedC e m b #

(>>) :: SteppedC e m a -> SteppedC e m b -> SteppedC e m b #

return :: a -> SteppedC e m a #

Functor (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

fmap :: (a -> b) -> SteppedC e m a -> SteppedC e m b #

(<$) :: a -> SteppedC e m b -> SteppedC e m a #

MonadFail m => MonadFail (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

fail :: String -> SteppedC e m a #

Applicative (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

pure :: a -> SteppedC e m a #

(<*>) :: SteppedC e m (a -> b) -> SteppedC e m a -> SteppedC e m b #

liftA2 :: (a -> b -> c) -> SteppedC e m a -> SteppedC e m b -> SteppedC e m c #

(*>) :: SteppedC e m a -> SteppedC e m b -> SteppedC e m b #

(<*) :: SteppedC e m a -> SteppedC e m b -> SteppedC e m a #

MonadIO m => MonadIO (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

liftIO :: IO a -> SteppedC e m a #

MonadThrow m => MonadThrow (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

throwM :: Exception e0 => e0 -> SteppedC e m a #

MonadCatch m => MonadCatch (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

catch :: Exception e0 => SteppedC e m a -> (e0 -> SteppedC e m a) -> SteppedC e m a #

(Threads (FreeT (FOEff e)) (Prims m), Carrier m) => Carrier (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Associated Types

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

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

type Derivs (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

type Derivs (SteppedC e m) = e ': Derivs m
type Prims (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

type Prims (SteppedC e m) = Prims m