| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Polysemy.Internal.TH.Effect
Description
This module provides Template Haskell functions for automatically generating
 effect operation functions (that is, functions that use send) from a given
 effect algebra. For example, using the FileSystem effect from the example in
 the module documentation for Polysemy, we can write the following:
data FileSystem m a where ReadFile ::FilePath-> FileSystemStringWriteFile ::FilePath->String-> FileSystem ()makeSem''FileSystem
This will automatically generate (approximately) the following functions:
readFile ::MemberFileSystem r =>FilePath->SemrStringreadFile a =send(ReadFile a) writeFile ::MemberFileSystem r =>FilePath->String->Semr () writeFile a b =send(WriteFile a b)
Documentation
makeSem :: Name -> Q [Dec] Source #
If T is a GADT representing an effect algebra, as described in the
 module documentation for Polysemy, $( automatically
 generates a smart constructor for every data constructor of makeSem ''T)T. This also
 works for data family instances. Names of smart constructors are created by
 changing first letter to lowercase or removing prefix : in case of
 operators. Fixity declaration is preserved for both normal names and
 operators.
Since: 0.1.2.0
makeSem_ :: Name -> Q [Dec] Source #
Like makeSem, but does not provide type signatures and fixities. This
 can be used to attach Haddock comments to individual arguments for each
 generated function.
data Output o m a where
  Output :: o -> Output o m ()
makeSem_ ''Output
-- | Output the value @o@.
output :: forall o r
       .  Member (Output o) r
       => o         -- ^ Value to output.
       -> Sem r ()  -- ^ No result.
Because of limitations in Template Haskell, signatures have to follow some rules to work properly:
- makeSem_must be used before the explicit type signatures
- signatures have to specify argument of Semrepresenting union of effects asr(e.g.Semr ()
- all arguments in effect's type constructor have to follow naming scheme from data constructor's declaration:
data Foo e m a where FooC1 :: Foo x m () FooC2 :: Foo (Maybe x) m ()
should have x in type signature of fooC1:
fooC1 :: forall x r. Member (Foo x) r => Sem r ()
and Maybe x in signature of fooC2:
fooC2 :: forall x r. Member (Foo (Maybe x)) r => Sem r ()
- all effect's type variables and rhave to be explicitly quantified usingforall(order is not important)
These restrictions may be removed in the future, depending on changes to the compiler.
Change in (TODO(Sandy): version): in case of GADTs, signatures now only use names from data constructor's type and not from type constructor declaration.
Since: 0.1.2.0