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

Control.Effect.Cont

Synopsis

Effects

newtype Cont :: Effect where Source #

An effect for abortive continuations.

Constructors

CallCC :: ((forall b. a -> m b) -> m a) -> Cont m a 

newtype Shift r :: Effect where Source #

An effect for non-abortive continuations of a program that eventually produces a result of type r.

This isn't quite as powerful as proper delimited continuations, as this doesn't provide any equivalent of the reset operator.

This can be useful as a helper effect.

Constructors

Shift :: ((a -> m r) -> m r) -> Shift r m a 

Actions

callCC :: Eff Cont m => ((forall b. a -> m b) -> m a) -> m a Source #

Call with current continuation. The argument computation is provided the continuation of the program at the point that callCC was invoked. If the continuation is executed, then control will immediately abort and jump to the point callCC was invoked, which will then return the argument provided to the continuation.

The way higher-order actions interact with the continuation depends on the interpretation of Cont. In general, you cannot expect to interact with the continuation in any meaningful way: for example, you should not assume that you will be able to catch an exception thrown at some point in the future of the computation by using catch on the continuation.

shift :: Eff (Shift r) m => ((a -> m r) -> m r) -> m a Source #

Non-abortive call with current continuation. The argument computation is provided the continuation of the program at the point that shift was invoked. If the continuation is executed, then control will jump to the point shift was invoked, which will then return the argument provided to the continuation.

Once the program finishes, and produces an r, control will jump back to where the continuation was executed, and return that r. From that point, you may decide whether or not to modify the final r, or invoke the continuation again with a different argument.

You can also use shift to abort the execution of the program early by simply not executing the provided continuation, and instead provide the final r directly.

The way higher-order actions interact with the continuation depends on the interpretation of Shift. In general, you cannot expect to interact with the continuation in any meaningful way: for example, you should not assume that you will be able to catch an exception thrown at some point in the future of the computation by using catch on the continuation.

Interpretations

runCont :: forall a m p. (Carrier m, Threaders '[ContThreads] m p) => ContC a m a -> m a Source #

Run a Cont effect.

Derivs (ContC r m) = Cont ': Derivs m
Prims  (ContC r m) = Prims m

runShift :: forall r m p. (Carrier m, Threaders '[ContThreads] m p) => ShiftC r m r -> m r Source #

Run a Shift r effect if the program returns r.

Derivs (ShiftC r m) = Shift r ': Derivs m
Prims  (ShiftC r m) = Prims m

contToShift :: Eff (Shift r) m => ContToShiftC r m a -> m a Source #

Transform a Cont effect into a Shift r effect.

Threading constraints

type ContThreads = FreeThreads Source #

ContThreads accepts the following primitive effects:

Carriers

data ContC r m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

liftBase :: b α -> ContC r m α #

MonadTrans (ContC s) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

lift :: Monad m => m a -> ContC s m a #

Monad (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

(>>=) :: ContC r m a -> (a -> ContC r m b) -> ContC r m b #

(>>) :: ContC r m a -> ContC r m b -> ContC r m b #

return :: a -> ContC r m a #

Functor (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

fmap :: (a -> b) -> ContC r m a -> ContC r m b #

(<$) :: a -> ContC r m b -> ContC r m a #

MonadFail m => MonadFail (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

fail :: String -> ContC r m a #

Applicative (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

pure :: a -> ContC r m a #

(<*>) :: ContC r m (a -> b) -> ContC r m a -> ContC r m b #

liftA2 :: (a -> b -> c) -> ContC r m a -> ContC r m b -> ContC r m c #

(*>) :: ContC r m a -> ContC r m b -> ContC r m b #

(<*) :: ContC r m a -> ContC r m b -> ContC r m a #

MonadIO m => MonadIO (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

liftIO :: IO a -> ContC r m a #

MonadThrow m => MonadThrow (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

throwM :: Exception e => e -> ContC r m a #

MonadCatch m => MonadCatch (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

catch :: Exception e => ContC r m a -> (e -> ContC r m a) -> ContC r m a #

(Carrier m, Threads (FreeT (ContBase (m r) r)) (Prims m)) => Carrier (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Associated Types

type Derivs (ContC r m) :: [Effect] Source #

type Prims (ContC r m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ContC r m)) (ContC r m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ContC r m)) (Prims (ContC r m)) (ContC r m) z a Source #

algDerivs :: Algebra' (Derivs (ContC r m)) (ContC r m) a Source #

type Derivs (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

type Derivs (ContC r m) = Cont ': Derivs m
type Prims (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

type Prims (ContC r m) = Prims m

data ShiftC r m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

liftBase :: b α -> ShiftC r m α #

MonadTrans (ShiftC s) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

lift :: Monad m => m a -> ShiftC s m a #

Monad (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

(>>=) :: ShiftC r m a -> (a -> ShiftC r m b) -> ShiftC r m b #

(>>) :: ShiftC r m a -> ShiftC r m b -> ShiftC r m b #

return :: a -> ShiftC r m a #

Functor (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

fmap :: (a -> b) -> ShiftC r m a -> ShiftC r m b #

(<$) :: a -> ShiftC r m b -> ShiftC r m a #

MonadFail m => MonadFail (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

fail :: String -> ShiftC r m a #

Applicative (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

pure :: a -> ShiftC r m a #

(<*>) :: ShiftC r m (a -> b) -> ShiftC r m a -> ShiftC r m b #

liftA2 :: (a -> b -> c) -> ShiftC r m a -> ShiftC r m b -> ShiftC r m c #

(*>) :: ShiftC r m a -> ShiftC r m b -> ShiftC r m b #

(<*) :: ShiftC r m a -> ShiftC r m b -> ShiftC r m a #

MonadIO m => MonadIO (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

liftIO :: IO a -> ShiftC r m a #

MonadThrow m => MonadThrow (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

throwM :: Exception e => e -> ShiftC r m a #

MonadCatch m => MonadCatch (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

catch :: Exception e => ShiftC r m a -> (e -> ShiftC r m a) -> ShiftC r m a #

(Carrier m, Threads (FreeT (ContBase (m r) r)) (Prims m)) => Carrier (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Associated Types

type Derivs (ShiftC r m) :: [Effect] Source #

type Prims (ShiftC r m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ShiftC r m)) (ShiftC r m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ShiftC r m)) (Prims (ShiftC r m)) (ShiftC r m) z a Source #

algDerivs :: Algebra' (Derivs (ShiftC r m)) (ShiftC r m) a Source #

type Derivs (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

type Derivs (ShiftC r m) = Shift r ': Derivs m
type Prims (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

type Prims (ShiftC r m) = Prims m

type ContToShiftC r = InterpretC (ContToShiftH r) Cont Source #