polysemy-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Polysemy.Interpretation

Contents

Description

Everything you need in order to define new effects.

Synopsis

TH

makeSemantic :: Name -> Q [Dec] Source #

If T is a GADT representing an effect algebra, as described in the module documentation for Polysemy, $(makeEffect ''T) automatically generates a function that uses send with each operation. For more information, see the module documentation for Polysemy.TH.

makeSemantic_ :: Name -> Q [Dec] Source #

Like makeEffect, but does not provide type signatures. This can be used to attach Haddock comments to individual arguments for each generated function.

data Lang x where
  Output :: String -> Lang ()

makeSemantic_ ''Lang

-- | Output a string.
output :: Member Lang effs
       => String    -- ^ String to output.
       -> Semantic effs ()  -- ^ No result.

Note that makeEffect_ must be used before the explicit type signatures.

First order

interpret :: FirstOrder e "interpret" => (forall x m. e m x -> Semantic r x) -> Semantic (e ': r) a -> Semantic r a Source #

intercept :: forall e r a. (Member e r, FirstOrder e "intercept") => (forall x m. e m x -> Semantic r x) -> Semantic r a -> Semantic r a Source #

Like interpret, but instead of handling the effect, allows responding to the effect while leaving it unhandled.

reinterpret :: forall e2 e1 r a. FirstOrder e1 "reinterpret" => (forall m x. e1 m x -> Semantic (e2 ': r) x) -> Semantic (e1 ': r) a -> Semantic (e2 ': r) a Source #

Like interpret, but instead of removing the effect e, reencodes it in some new effect f. This function will fuse when followed by runState, meaning it's free to reinterpret in terms of the State effect and immediately run it.

TODO(sandy): Make this fuse in with stateful directly.

reinterpret2 :: forall e2 e3 e1 r a. FirstOrder e1 "reinterpret2" => (forall m x. e1 m x -> Semantic (e2 ': (e3 ': r)) x) -> Semantic (e1 ': r) a -> Semantic (e2 ': (e3 ': r)) a Source #

Higher order

interpretH :: forall e r a. (forall x m. e m x -> Tactical e m r x) -> Semantic (e ': r) a -> Semantic r a Source #

interceptH :: forall e r a. Member e r => (forall x m. e m x -> Tactical e m r x) -> Semantic r a -> Semantic r a Source #

Like interpret, but instead of handling the effect, allows responding to the effect while leaving it unhandled.

reinterpretH :: forall e2 e1 r a. (forall m x. e1 m x -> Tactical e1 m (e2 ': r) x) -> Semantic (e1 ': r) a -> Semantic (e2 ': r) a Source #

Like interpret, but instead of removing the effect e, reencodes it in some new effect f. This function will fuse when followed by runState, meaning it's free to reinterpret in terms of the State effect and immediately run it.

TODO(sandy): Make this fuse in with stateful directly.

reinterpret2H :: forall e2 e3 e1 r a. (forall m x. e1 m x -> Tactical e1 m (e2 ': (e3 ': r)) x) -> Semantic (e1 ': r) a -> Semantic (e2 ': (e3 ': r)) a Source #

Statefulness

stateful :: (forall x m. e m x -> s -> Semantic r (s, x)) -> s -> Semantic (e ': r) a -> Semantic r (s, a) Source #

Like interpret, but with access to an intermediate state s.

lazilyStateful :: (forall x m. e m x -> s -> Semantic r (s, x)) -> s -> Semantic (e ': r) a -> Semantic r (s, a) Source #

Like interpret, but with access to an intermediate state s.

Raising

raise :: forall e r a. Semantic r a -> Semantic (e ': r) a Source #

Performance

inlineRecursiveCalls :: Q [Dec] -> Q [Dec] Source #

GHC has a really hard time inlining recursive calls---such as those used in interpreters for higher-order effects. This can have disastrous repercussions for your performance.

Fortunately there's a solution, but it's ugly boilerplate. You can enable -XTemplateHaskell and use inlineRecursiveCalls to convince GHC to make these functions fast again.

inlineRecursiveCalls [d|
  factorial :: Int -> Int
  factorial 0 = 1
  factorial n = n * factorial (n - 1)
  |]

Tactics

type Tactical e m r x = forall f. Functor f => Semantic (Tactics f m (e ': r) ': r) (f x) Source #

pureT :: a -> Tactical e n r a Source #

runT :: n a -> Semantic (Tactics f n (e ': r) ': r) (Semantic (e ': r) (f a)) Source #

bindT :: (a -> n b) -> Semantic (Tactics f n (e ': r) ': r) (f a -> Semantic (e ': r) (f b)) Source #