| Copyright | (C) 2017 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Experimental |
| Portability | GHC |
| Safe Haskell | Unsafe |
| Language | GHC2021 |
Data.Eliminator.TH
Description
Generate dependently typed elimination functions using Template Haskell.
Synopsis
- deriveElim :: Name -> Q [Dec]
- deriveElimNamed :: String -> Name -> Q [Dec]
- deriveTypeElim :: Name -> Q [Dec]
- deriveTypeElimNamed :: String -> Name -> Q [Dec]
Eliminator generation
Term-level eliminators
deriveElim and deriveElimNamed provide a way to automate the creation of
eliminator functions, which are mostly boilerplate. Here is a complete example
showing how one might use deriveElim:
$(singletons[d| data MyList a = MyNil | MyCons a (MyList a) |]) $(deriveElim''MyList)
This will produce an eliminator function that looks roughly like the following:
elimMyList :: forall (a ::Type) (p :: MyList a~>Type) (l :: MyList a).Singl ->Applyp MyNil -> (forall (x :: a).Singx -> forall (xs :: MyList a).Singxs ->Applyp xs ->Applyp (MyCons x xs)) ->Applyp l elimMyList SMyNil pMyNil _ = pMyNil elimMyList (SMyCons (x' ::Singx) (xs' ::Singxs)) pMyNil pMyCons = pMyCons x' xs' (elimMyList @a @p @xs pMyNil pMyCons)
There are some important things to note here:
- Because these eliminators use
Singunder the hood, in order forderiveElimto work, theSinginstance for the data type given as an argument must be in scope. Moreover,deriveElimassumes the naming conventions for singled constructors used by thesingletonslibrary. (This is why thesingletonsfunction is used in the example above). There is a convention for the order in which the arguments appear. The quantified type variables appear in this order:
- First, the type variables of the data type itself (
a, in the above example). - Second, a predicate type variable of kind
<Datatype>(~>Typep, in the above example). - Finally, a type variable of kind
<Datatype>(l, in the above example).
- First, the type variables of the data type itself (
The function arguments appear in this order:
- First, a
Singargument (, in the above example).Singl - Next, there are arguments that correspond to each constructor. More on this in a second.
The return type is the predicate type variable applied to the data type
(, the above example).Apply p (MyCons x xs)
The type of each constructor argument also follows certain conventions:
- For each field, there will be a rank-2 type variable whose kind matches
the type of the field, followed by a matching
Singtype. For instance, in the above example,forall (x :: a).corresponds to the first field ofSingxMyCons. - In addition, if the field is a recursive occurrence of the data type,
an additional argument will follow the
Singtype. This is best explained using the above example. In theMyConsconstructor, the second field (of typeMyCons a) is a recursive occurrence ofMyCons, so that corresponds to the typeforall (xs :: MyList a)., whereSingxs ->Applyp xsis only present due to the recursion.Applyp xs - Finally, the return type will be the predicate type variable applied
to a saturated occurrence of the data constructor
(
, in the above example).Applyp (MyCons x xs)
You'll need to enable lots of GHC extensions in order for the code generated by
deriveElimto typecheck. You'll need at least the following:AllowAmbiguousTypes
DataKinds
GADTs
PolyKinds
RankNTypes
ScopedTypeVariables
TemplateHaskell
TypeApplications
deriveElimdoesn't support every possible data type at the moment. It is known not to work for the following:- Data types defined using
GADTsorExistentialQuantification - Data family instances
- Data types which use polymorphic recursion
(e.g.,
data Foo a = Foo (Foo a))
- Data types defined using
deriveElim :: Name -> Q [Dec] Source #
generates a top-level elimination function for the
datatype deriveElim dataNamedataName. The eliminator will follow these naming conventions:
- If the datatype has an alphanumeric name, its eliminator will have that name
with
elimprepended. - If the datatype has a symbolic name, its eliminator will have that name
with
~>prepended.
deriveElimNamed :: String -> Name -> Q [Dec] Source #
generates a top-level elimination
function named deriveElimNamed funName dataNamefunName for the datatype dataName.
Type-level eliminators
deriveTypeElim and deriveTypeElimNamed are like deriveElim and
deriveElimNamed except that they create type-level eliminators instead of
term-level ones. Here is an example showing how one might use
deriveTypeElim:
data MyList a = MyNil | MyCons a (MyList a)
$(deriveTypeElim ''MyList)
This will produce an eliminator function that looks roughly like the following:
type ElimMyList :: forall (a ::Type). forall (p :: MyList a~>Type) (l :: MyList a) ->Applyp MyNil -> (forall (x :: a) (xs :: MyList a) ->Applyp xs~>Applyp (MyCons x xs)) ->Applyp l type family ElimMyList p l pMyNil pMyCons where forall (a ::Type) (p :: MyList a ~>Type) (pMyNil ::Applyp MyNil) (pMyCons :: forall (x :: a) (xs :: MyList a) ->Applyp xs~>Applyp (MyCons x xs)). ElimMyLista p MyNil pMyNil pMyCons = pMyNil forall (a ::a p (MyCons x' xs') pMyNil pMyCons =Type) (p :: MyList a ~>Type) (_pMyNil ::Applyp MyNil) (pMyCons :: forall (x :: a) (xs :: MyList a) ->Applyp xs~>Applyp (MyCons x xs)) x' xs'. ElimMyListApply(pMyCons x' xs') (ElimMyList @a p xs' pMyNil pMyCons)
Note the following differences from a term-level eliminator that deriveElim
would generate:
- Type-level eliminators do not use
Sing. Instead, they use visible dependent quantification. That is, instead of generatingforall (x :: a). Sing x -> ...(as a term-level eliminator would do), a type-level eliminator would useforall (x :: a) -> .... - Term-level eliminators quantify
pwith an invisibleforall, whereas type-level eliminators quantifypwith a visibleforall. (Really,pought to be quantified visibly in both forms of eliminator, but GHC does not yet support visible dependent quantification at the term level.) - Type-level eliminators use (
~>) in certain places where (->) would appear in term-level eliminators. For instance, note the use ofinApplyp xs~>Applyp (MyCons x xs)ElimMyListabove. This is done to make it easier to use type-level eliminators with defunctionalization symbols (which aren't necessary for term-level eliminators).
This comes with a notable drawback: type-level eliminators cannot support
data constructors where recursive occurrences of the data type appear in a
position other than the last field of a constructor. In other words,
deriveTypeElim works on the MyList example above, but not this variant:
data SnocList a = SnocNil | SnocCons (SnocList a) a
This is because $( would generate an eliminator
with the following kind:deriveTypeElim ''SnocList)
type ElimSnocList :: forall (a ::Type). forall (p :: SnocList a~>Type) (l :: SnocList a) ->Applyp SnocNil -> (forall (xs :: SnocList a) ->Applyp xs~>(forall (x :: a) ->Applyp (SnocCons x xs))) ->Applyp l
Unfortunately, the kind
is
impredicative.Apply p xs ~> (forall (x :: a) -> Apply p (SnocCons x xs))
In addition to the language extensions that
deriveElimrequires, you'll need to enable these extensions in order to usederiveTypeElim:StandaloneKindSignatures
UndecidableInstances
deriveTypeElim :: Name -> Q [Dec] Source #
generates a type-level eliminator for the
datatype deriveTypeElim dataNamedataName. The eliminator will follow these naming conventions:
- If the datatype has an alphanumeric name, its eliminator will have that name
with
Elimprepended. - If the datatype has a symbolic name, its eliminator will have that name
with
~>prepended.
deriveTypeElimNamed :: String -> Name -> Q [Dec] Source #
generates a type-level eliminator
named deriveTypeElimNamed funName dataNamefunName for the datatype dataName.