free-4.8.0.1: Monads for free

PortabilityMPTCs, fundeps
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Monad.Free.TH

Contents

Description

Automatic generation of free monadic actions.

Synopsis

Free monadic actions

makeFree :: Name -> Q [Dec]Source

$(makeFree ''Type) provides free monadic actions for the constructors of the given type.

To generate free monadic actions from a Type, it must be a data declaration (maybe GADT) with at least one free variable. For each constructor of the type, a new function will be declared.

Consider the following generalized definitions:

 data Type a1 a2 … aN param = …
                            | FooBar t1 t2 t3 … tJ
                            | (:+) t1 t2 t3 … tJ
                            | t1 :* t2
                            | t1 `Bar` t2
                            | Baz { x :: t1, y :: t2, …, z :: tJ }
                            | forall b1 b2 … bN. cxt => Qux t1 t2 … tJ
                            | …

where each of the constructor arguments t1, …, tJ is either:

  1. A type, perhaps depending on some of the a1, …, aN.
  2. A type dependent on param, of the form s1 -> … -> sM -> param, M ≥ 0. At most 2 of the t1, …, tJ may be of this form. And, out of these two, at most 1 of them may have M == 0; that is, be of the form param.

For each constructor, a function will be generated. First, the name of the function is derived from the name of the constructor:

  • For prefix constructors, the name of the constructor with the first letter in lowercase (e.g. FooBar turns into fooBar).
  • For infix constructors, the name of the constructor with the first character (a colon :), removed (e.g. :+ turns into +).

Then, the type of the function is derived from the arguments to the constructor:

 …
 fooBar :: (MonadFree Type m) => t1' -> … -> tK' -> m ret
 (+)    :: (MonadFree Type m) => t1' -> … -> tK' -> m ret
 bar    :: (MonadFree Type m) => t1  -> … -> tK' -> m ret
 baz    :: (MonadFree Type m) => t1' -> … -> tK' -> m ret
 qux    :: (MonadFree Type m, cxt) => t1' -> … -> tK' -> m ret
 …

The t1', …, tK' are those t1tJ that only depend on the a1, …, aN.

The type ret depends on those constructor arguments that reference the param type variable:

  1. If no arguments to the constructor depend on param, ret ≡ a, where a is a fresh type variable.
  2. If only one argument in the constructor depends on param, then ret ≡ (s1, …, sM). In particular, f M == 0, then ret ≡ (); if M == 1, ret ≡ s1.
  3. If two arguments depend on param, (e.g. u1 -> … -> uL -> param and v1 -> … -> vM -> param, then ret ≡ Either (u1, …, uL) (v1, …, vM).

Note that Either a () and Either () a are both isomorphic to Maybe a. Because of this, when L == 0 or M == 0 in case 3., the type of ret is simplified:

  • ret ≡ Either (u1, …, uL) () is rewritten to ret ≡ Maybe (u1, …, uL).
  • ret ≡ Either () (v1, …, vM) is rewritten to ret ≡ Maybe (v1, …, vM).

Examples

Teletype (regular data type declaration)

Retry (GADT declaration)