effectful-th-1.0.0.0: Template Haskell utilities for the effectful library.
Safe HaskellNone
LanguageHaskell2010

Effectful.TH

Description

Generate functions for performing operations of dynamically dispatched effects via Template Haskell.

Synopsis

Documentation

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

For an effect data type E, makeEffect E generates the appropriate instance of DispatchOf as well as functions for performing operations of E by sending them to the effect handler.

>>> :{
  data E :: Effect where
    Op1 :: Int -> m a -> E m a
    Op2 :: IOE :> es => Int -> E (Eff es) ()
    Op3 :: (forall r. m r -> m r) -> E m Int
  makeEffect ''E
:}
>>> :kind! DispatchOf E
DispatchOf E :: Dispatch
= 'Dynamic
>>> :i op1
op1 :: (HasCallStack, E :> es) => Int -> Eff es a -> Eff es a
...
>>> :i op2
op2 :: (HasCallStack, E :> es, IOE :> es) => Int -> Eff es ()
...
>>> :i op3
op3 ::
  (HasCallStack, E :> es) =>
  (forall r. Eff es r -> Eff es r) -> Eff es Int
...

The naming rule changes the first uppercase letter in the constructor name to lowercase or removes the : symbol in case of operators. Any fixity annotations defined for the constructors are preserved for the corresponding definitions.

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

Like makeEffect, but doesn't generate type signatures. This is useful when you want to attach Haddock documentation to function signatures:

>>> :{
  data Noop :: Effect where
    Noop :: Noop m ()
  makeEffect_ ''Noop
  -- | Perform nothing at all.
  noop :: Noop :> es => Eff es ()
:}

Note: function signatures must be added after the call to makeEffect_.