Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- data Instruction xs a where
- Instruction :: !(Membership xs kv) -> AssocValue kv a -> Instruction xs a
- type Eff xs = Skeleton (Instruction xs)
- liftEff :: forall proxy s t xs a. Associate s t xs => proxy s -> t a -> Eff xs a
- hoistEff :: forall proxy s t xs a. Associate s t xs => proxy s -> (forall x. t x -> t x) -> Eff xs a -> Eff xs a
- handleWith :: RecordOf (Handler m) xs -> Eff xs a -> MonadView m (Eff xs) a
- newtype Handler f g = Handler {
- runHandler :: forall a. g a -> f a
- data Action args a r where
- type family Function args r :: *
- receive :: Functor f => Function xs (f a) -> Handler f (Action xs a)
- (!-!!) :: Monad m => (forall x. t x -> m x) -> (forall x. Eff xs x -> m x) -> Eff ((s :> t) : xs) a -> m a
- squash :: (forall x. t x -> Eff xs x) -> Eff ((s :> t) : xs) a -> Eff xs a
- nihility :: Monad m => Eff `[]` a -> m a
Documentation
data Instruction xs a where Source
A unit of effects
Instruction :: !(Membership xs kv) -> AssocValue kv a -> Instruction xs a |
type Eff xs = Skeleton (Instruction xs) Source
The extensible operational monad
liftEff :: forall proxy s t xs a. Associate s t xs => proxy s -> t a -> Eff xs a Source
Lift some effect to Eff
hoistEff :: forall proxy s t xs a. Associate s t xs => proxy s -> (forall x. t x -> t x) -> Eff xs a -> Eff xs a Source