Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Cont m a where
- newtype Shift r m a where
- data ContBase r a where
- newtype ContC r m a = ContC {}
- newtype ContFastC (r :: *) m a = ContFastC {
- unContFastC :: ContT r m a
- newtype ShiftC r m a = ShiftC {}
- newtype ShiftFastC (r :: *) m a = ShiftFastC {
- unShiftFastC :: ContT r m a
- type ContThreads = FreeThreads
- class (forall s. Threads (ContT s) p) => ContFastThreads p
Documentation
newtype Shift r m a 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.
Instances
MonadBase b m => MonadBase b (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadTrans (ContC s) Source # | |
Defined in Control.Effect.Internal.Cont | |
Monad (ContC r m) Source # | |
Functor (ContC r m) Source # | |
MonadFail m => MonadFail (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
Applicative (ContC r m) Source # | |
MonadIO m => MonadIO (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadThrow m => MonadThrow (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadCatch m => MonadCatch (ContC r m) Source # | |
(Carrier m, Threads (FreeT (ContBase (m r))) (Prims m)) => Carrier (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
type Derivs (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
type Prims (ContC r m) Source # | |
Defined in Control.Effect.Internal.Cont |
newtype ContFastC (r :: *) m a Source #
ContFastC | |
|
Instances
Instances
MonadBase b m => MonadBase b (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadTrans (ShiftC s) Source # | |
Defined in Control.Effect.Internal.Cont | |
Monad (ShiftC r m) Source # | |
Functor (ShiftC r m) Source # | |
MonadFail m => MonadFail (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
Applicative (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadIO m => MonadIO (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadThrow m => MonadThrow (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
MonadCatch m => MonadCatch (ShiftC r m) Source # | |
(Carrier m, Threads (FreeT (ContBase (m r))) (Prims m)) => Carrier (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
type Derivs (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont | |
type Prims (ShiftC r m) Source # | |
Defined in Control.Effect.Internal.Cont |
newtype ShiftFastC (r :: *) m a Source #
ShiftFastC | |
|
Instances
type ContThreads = FreeThreads Source #
ContThreads
accepts the following primitive effects:
Regional
s
Optional
s
(whens
is a functor)Unravel
p
ListenPrim
s
(whens
is aMonoid
)ReaderPrim
i
class (forall s. Threads (ContT s) p) => ContFastThreads p Source #
ContFastThreads
accepts the following primitive effects:
Instances
(forall s. Threads (ContT s) p) => ContFastThreads p Source # | |
Defined in Control.Effect.Internal.Cont |