Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- axiom :: a :~: b
- pattern Any :: forall a. a -> Any
- anyCo :: forall a. Coercion a Any
- null# :: Any
- unIO :: IO a -> State# RealWorld -> (# State# RealWorld, a #)
- data Dict c = c => Dict
- type family DictRep c
- newtype WithDict c r = WithDict {
- unWithDict :: c => r
- reflectDict :: forall c r. DictRep c -> (c => r) -> r
- type Effect = (Type -> Type) -> Type -> Type
- class eff :< effs where
- reifyIndex :: Int
- class effs1 :<< effs2 where
- reifySubIndex :: Int
- newtype eff :<# effs = ReflectIndex# {
- reifyIndex# :: Int#
- pattern IndexDict# :: forall eff effs. () => eff :< effs => eff :<# effs
- newtype Eff effs a = Eff# {}
- pattern Eff :: (Registers -> IO (Registers, a)) -> Eff effs a
- newtype EVM a = EVM# {
- unEVM# :: Registers# -> IO (Result a)
- data Result a = Result Registers# ~a
- pattern EVM :: (Registers -> IO (Registers, a)) -> EVM a
- packIOResult :: IO (Registers, a) -> IO (Result a)
- newtype Registers# = Registers# (# PromptId, Targets# #)
- data Registers = BoxRegisters {}
- pattern Registers :: PromptId -> Targets -> Registers
- initialRegisters :: Registers
- newtype PromptId = PromptId# Int#
- pattern PromptId :: Int -> PromptId
- data Unwind
- data Capture a where
- data CaptureMode
- captureVM :: forall a b. Capture a -> IO b
- promptVM :: forall a b. IO (Registers, a) -> (a -> IO b) -> (PromptId -> Any -> IO b) -> (Capture a -> IO b) -> IO b
- promptVM_ :: forall a. IO (Registers, a) -> Registers -> (Capture a -> IO (Registers, a)) -> IO (Registers, a)
- controlVM :: ((a -> EVM b) -> IO (Registers, b)) -> IO (Registers, a)
- parameterizeVM :: (Registers -> Registers) -> EVM a -> EVM a
- newtype Targets# = Targets# (SmallArray# Any)
- newtype Targets = Targets (SmallArray Any)
- pattern BoxTargets :: Targets# -> Targets
- noTargets :: Targets
- lookupTarget :: forall effs eff. (DebugCallStack, eff :< effs) => Targets -> Handler eff
- pushTarget :: Handler eff -> Targets -> Targets
- dropTargets :: DebugCallStack => Int -> Targets -> Targets
- run :: Eff '[] a -> a
- newtype Handle eff effs i r effs' a = Handle# {
- runHandle# :: Registers# -> Eff effs' a
- pattern Handle :: (Registers -> Eff effs' a) -> Handle eff effs i r effs' a
- newtype Handler eff = Handler# {
- runHandler# :: forall effs a. (eff :<# effs) -> eff (Eff effs) a -> Eff effs a
- newtype WrappedHandler eff = WrapHandler (forall effs a. eff :< effs => eff (Eff effs) a -> Eff effs a)
- pattern Handler :: (forall effs a. eff :< effs => eff (Eff effs) a -> Eff effs a) -> Handler eff
- send :: forall eff a effs. eff :< effs => eff (Eff effs) a -> Eff effs a
- handle :: forall eff a r effs. (a -> Eff effs r) -> (forall effs' b. eff :< effs' => eff (Eff effs') b -> Handle eff effs a r effs' b) -> Eff (eff ': effs) a -> Eff effs r
- handleVM :: forall eff a r effs. (a -> Eff effs r) -> (Registers# -> Handler eff) -> Eff (eff ': effs) a -> Eff effs r
- locally :: Eff effs' a -> Handle eff effs i r effs' a
- liftH :: Eff (eff ': effs) a -> Handle eff effs i r effs' a
- abort :: r -> Handle eff effs i r effs' a
- control :: ((a -> Eff effs r) -> Eff effs r) -> Handle eff effs i r effs' a
- control0 :: ((a -> Eff (eff ': effs) i) -> Eff effs r) -> Handle eff effs i r effs' a
- class Lift effs1 effs2 where
- liftTargets :: Targets -> Targets
- lift :: forall effs1 effs2 a. Lift effs1 effs2 => Eff effs1 a -> Eff effs2 a
- lift1 :: forall eff effs a. Eff effs a -> Eff (eff ': effs) a
- data IOE :: Effect where
- unsafeIOToEff :: IO a -> Eff effs a
- runIO :: Eff '[IOE] a -> IO a
- data State s :: Effect where
- evalState :: s -> Eff (State s ': effs) a -> Eff effs a
- data NonDet :: Effect where
Documentation
pattern Any :: forall a. a -> Any Source #
A restricted form of unsafeCoerce
that only works for converting to/from
Any
. Still just as unsafe, but makes it slightly more difficult to
accidentally misuse.
Used to explicitly overwrite references to values that should not be retained by the GC.
WithDict | |
|
reflectDict :: forall c r. DictRep c -> (c => r) -> r Source #
class eff :< effs where Source #
reifyIndex :: Int Source #
Instances
eff :< effs => eff :< (eff' ': effs) Source # | |
Defined in Control.Effect.Internal reifyIndex :: Int Source # | |
eff :< (eff ': effs) Source # | |
Defined in Control.Effect.Internal reifyIndex :: Int Source # | |
type DictRep (eff :< effs) Source # | |
Defined in Control.Effect.Internal |
class effs1 :<< effs2 where Source #
reifySubIndex :: Int Source #
Instances
(effs2 ~ (eff ': effs3), effs1 :<< effs3) => effs1 :<< effs2 Source # | |
Defined in Control.Effect.Internal reifySubIndex :: Int Source # | |
effs :<< effs Source # | |
Defined in Control.Effect.Internal reifySubIndex :: Int Source # | |
type DictRep (effs1 :<< effs2) Source # | |
Defined in Control.Effect.Internal |
pattern IndexDict# :: forall eff effs. () => eff :< effs => eff :<# effs Source #
All eff
computations operate in the Eff
monad. Eff
computations are
parameterized by a type-level list that specifies which effects they are
allowed to perform. For example, a computation of type
can raise exceptions of type Eff
'[Error
e, Reader
r, State
s] ae
, can access a global environment of type
r
, and can read and modify a single cell of mutable state of type s
.
To run an Eff
computation that performs effects, the effects must be
explicitly handled. Functions that handle effects are called
effect handlers, and they usually have types like the following:
runX ::Eff
(X ': effs) a ->Eff
effs a
Note that the argument to runX
can perform the X
effect, but the result
cannot! Any X
operations have been handled by runX
, which interprets
their meaning. Examples of effect handlers include
runError
, runReader
, and
runState
.
After all effects have been handled, the resulting computation will have type
, a computation that performs no effects. A computation with
this type is pure, so it can be converted to an ordinary value using Eff
'[] arun
.
Some effects cannot be handled locally, but instead require performing I/O.
These effects will delegate to the IOE
effect, which provides low-level
interop with Haskell’s built-in IO
monad. After all other effects have been
handled, a computation of type
can be converted to an
ordinary Eff
'[IOE
] a
computation using IO
arunIO
.
EVM# | |
|
Result Registers# ~a |
newtype Registers# Source #
Registers# (# PromptId, Targets# #) |
Instances
Show Unwind Source # | |
Exception Unwind Source # | |
Defined in Control.Effect.Internal toException :: Unwind -> SomeException # fromException :: SomeException -> Maybe Unwind # displayException :: Unwind -> String # |
Capture | |
|
data CaptureMode Source #
IncludePrompt | The captured continuation should include the prompt being captured up to.
This mode corresponds to the |
ExcludePrompt | The captured continuation should include frames up to the the prompt, but
not the prompt itself. This mode corresponds to the |
:: IO (Registers, a) | |
-> (a -> IO b) | return handler |
-> (PromptId -> Any -> IO b) | abort handler |
-> (Capture a -> IO b) | capture handler |
-> IO b |
Runs an EVM
action with a new prompt installed. The arguments specify
what happens when control exits the action.
:: IO (Registers, a) | |
-> Registers | registers to restore on normal return |
-> (Capture a -> IO (Registers, a)) | capture handler |
-> IO (Registers, a) |
Like promptVM
, but for prompts that cannot be the target of a capture or
abort (that is, prompts that only install winders/unwinders).
pattern BoxTargets :: Targets# -> Targets Source #
lookupTarget :: forall effs eff. (DebugCallStack, eff :< effs) => Targets -> Handler eff Source #
dropTargets :: DebugCallStack => Int -> Targets -> Targets Source #
newtype Handle eff effs i r effs' a Source #
The monad that effect handlers run in.
- The
eff
parameter is the effect being handled, and theeffs
parameter includes the other effects in scope at the point of thehandle
call (used byliftH
). - The
i
parameter is the return type of the handled computation before the exit handler has been applied (used bycontrol0
). - The
r
parameter is the final return type of the handled computation (used byabort
,control
, andcontrol0
). - The
effs'
parameter is the list of effects in scope at the point of the originatingsend
call (used bylocally
).
See handle
for more details.
Handle# | |
|
Instances
Monad (Handle eff effs i r effs') Source # | |
Functor (Handle eff effs i r effs') Source # | |
Applicative (Handle eff effs i r effs') Source # | |
Defined in Control.Effect.Internal pure :: a -> Handle eff effs i r effs' a # (<*>) :: Handle eff effs i r effs' (a -> b) -> Handle eff effs i r effs' a -> Handle eff effs i r effs' b # liftA2 :: (a -> b -> c) -> Handle eff effs i r effs' a -> Handle eff effs i r effs' b -> Handle eff effs i r effs' c # (*>) :: Handle eff effs i r effs' a -> Handle eff effs i r effs' b -> Handle eff effs i r effs' b # (<*) :: Handle eff effs i r effs' a -> Handle eff effs i r effs' b -> Handle eff effs i r effs' a # |
Handler# | |
|
newtype WrappedHandler eff Source #
WrapHandler (forall effs a. eff :< effs => eff (Eff effs) a -> Eff effs a) |
pattern Handler :: (forall effs a. eff :< effs => eff (Eff effs) a -> Eff effs a) -> Handler eff Source #
:: (a -> Eff effs r) | The exit handler, aka the action to take on normal returns (often just |
-> (forall effs' b. eff :< effs' => eff (Eff effs') b -> Handle eff effs a r effs' b) | The handler function. |
-> Eff (eff ': effs) a | The action to handle. |
-> Eff effs r |
Handles the topmost effect in an Eff
computation. The given handler
function must provide an interpretation for each effectful operation. The
handler runs in the restrictive Handle
monad, which generally uses one of
the following core Handle
operations:
liftH
— Runs an action in the context of the originalhandle
call. This is the most common way to handle an effect.abort
— Aborts the computation to thehandle
call and returns a value directly. This is usually used to implement exception-like operations.control
— Captures the current continuation up to and including thehandle
call and aborts, passing the captured continuation to the handler. This can be used to implement complex control operators such as coroutines or resumable exceptions.control0
— Likecontrol
, but does not include thehandle
call itself in the captured continuation, so a different handler may be installed before resuming the computation.locally
— Runs an action directly in the context of the originatingsend
call. This can be used to implement “scoped” operations likelocal
andcatch
.
See the documentation for each of the above functions for examples and more details.
handleVM :: forall eff a r effs. (a -> Eff effs r) -> (Registers# -> Handler eff) -> Eff (eff ': effs) a -> Eff effs r Source #
class Lift effs1 effs2 where Source #
liftTargets :: Targets -> Targets Source #
Instances
effs1 :<< effs2 => Lift effs1 effs2 Source # | |
Defined in Control.Effect.Internal liftTargets :: Targets -> Targets Source # | |
Lift ('[] :: [Effect]) effs Source # | |
Defined in Control.Effect.Internal liftTargets :: Targets -> Targets Source # | |
(eff :< effs2, Lift effs1 effs2) => Lift (eff ': effs1) effs2 Source # | |
Defined in Control.Effect.Internal liftTargets :: Targets -> Targets Source # |
lift :: forall effs1 effs2 a. Lift effs1 effs2 => Eff effs1 a -> Eff effs2 a Source #
Lifts an Eff
computation into one that performs all the same effects, and
possibly more. For example, if you have a computation
m :: Eff
'[Foo, Bar] ()
then lift
will transform it into a polymorphic computation with the
following type:
lift
m :: (Foo:<
effs, Bar:<
effs) =>Eff
effs ()
This type is much more general, and effs
can now be instantiated at many
different types. Generally, lift
can manipulate the list of effects in any
of the following ways:
- Effects can be reordered.
- New effects can be inserted anywhere in the list.
- Duplicate effects can be collapsed.
More generally, the list of effects doesn’t need to be entirely concrete in
order for lift
to work. For example, if you have a computation
n :: Eff
(Foo ': Bar ': effs1) ()
then
will have the following type:lift
n
lift
n :: (Foo:<
effs2, Bar:<
effs2, effs1:<<
effs2) =>Eff
effs2 ()
This type is extremely general, and it allows lift
to manipulate the head
of the effects list even if the entire list is not completely known.
The Lift
typeclass provides some type-level programming machinery to
implement lift
, but it should be treated as an implementation detail. In
most situations, the machinery should “just work,” but if it doesn’t, the
type errors can be somewhat inscrutable. In those situations, adding some
explicit type annotations (or using TypeApplications
) can improve the type
errors significantly.
unsafeIOToEff :: IO a -> Eff effs a Source #
data State s :: Effect where Source #
The
effect provides access to a single cell of mutable state of
type State
ss
.
data NonDet :: Effect where Source #
The NonDet
effect provides so-called nondeterministic execution, which
runs all branches of a computation and collects some or all of their results.
Actual execution is not usually truly nondeterministic in the sense that it
is somehow random; rather, NonDet
models nondeterministic binary choice by
executing both possibilities rather than choosing just one.