| Copyright | (C) 2014-2015 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
TextShow.TH
Description
Functions to mechanically derive TextShow, TextShow1, or TextShow2 instances,
or to splice show-related expressions into Haskell source code. You need to enable
the TemplateHaskell language extension in order to use this module.
Since: 2
- deriveTextShow :: Name -> Q [Dec]
- deriveTextShow1 :: Name -> Q [Dec]
- deriveTextShow2 :: Name -> Q [Dec]
- makeShowt :: Name -> Q Exp
- makeShowtl :: Name -> Q Exp
- makeShowtPrec :: Name -> Q Exp
- makeShowtlPrec :: Name -> Q Exp
- makeShowtList :: Name -> Q Exp
- makeShowtlList :: Name -> Q Exp
- makeShowb :: Name -> Q Exp
- makeShowbPrec :: Name -> Q Exp
- makeShowbList :: Name -> Q Exp
- makePrintT :: Name -> Q Exp
- makePrintTL :: Name -> Q Exp
- makeHPrintT :: Name -> Q Exp
- makeHPrintTL :: Name -> Q Exp
- makeShowbPrecWith :: Name -> Q Exp
- makeShowbPrec1 :: Name -> Q Exp
- makeShowbPrecWith2 :: Name -> Q Exp
- makeShowbPrec2 :: Name -> Q Exp
deriveTextShow
deriveTextShow automatically generates a TextShow instance declaration for a data
type, a newtype, or a data family instance. This emulates what would (hypothetically)
happen if you could attach a deriving clause to the end of a data
declaration.TextShow
Here are some examples of how to derive TextShow for simple data types:
{-# LANGUAGE TemplateHaskell #-}
import TextShow.TH (deriveTextShow)
data Letter = A | B | C
$(deriveTextShow ''Letter) -- instance TextShow Letter where ...
newtype Box a = Box a
$(deriveTextShow ''Box) -- instance TextShow a => TextShow (Box a) where ...
If you are using template-haskell-2.7.0.0 or later (i.e., GHC 7.4 or later),
deriveTextShow can also be used to derive TextShow instances for data family
instances (which requires the -XTypeFamilies extension). To do so, pass the name of
a data or newtype instance constructor to deriveTextShow. Note that the generated
code may require the -XFlexibleInstances extension. Some examples:
{-# LANGUAGE FlexibleInstances, TemplateHaskell, TypeFamilies #-}
import TextShow.TH (deriveTextShow)
class AssocClass a where
data AssocData a
instance AssocClass Int where
data AssocData Int = AssocDataInt1 Int | AssocDataInt2 Int Int
$(deriveTextShow 'AssocDataInt1) -- instance TextShow (AssocData Int) where ...
-- Alternatively, one could use $(deriveTextShow 'AssocDataInt2)
data family DataFam a b
newtype instance DataFam () b = DataFamB b
$(deriveTextShow 'DataFamB) -- instance TextShow b => TextShow (DataFam () b)
Note that at the moment, there are some limitations:
- The
Nameargument toderiveTextShowmust not be a type synonym. deriveTextShowmakes the assumption that all type variables of kind*require aTextShowconstraint when creating the type context. For example, if you havedata Phantom a = Phantom, then(will generatederiveTextShow''Phantom)instance, even thoughTextShowa =>TextShow(Phantom a) where ...is not required. If you want a properTextShowaTextShowinstance forPhantom, you will need to usemakeShowbPrec(see the documentation of themakefunctions for more information).deriveTextShowlacks the ability to properly detect data types with higher-kinded type parameters (e.g.,data HK f a = HK (f a)) or with kinds other than*(e.g.,data List a (empty :: Bool)). If you wish to deriveTextShowinstances for these data types, you will need to usemakeShowbPrec(see the documentation of themakefunctions for more information).- Some data constructors have arguments whose
TextShowinstance depends on a typeclass besidesTextShow. For example, considernewtype MyFixed a = MyFixed (Fixed a).is aFixedaTextShowinstance only ifais an instance of bothHasResolutionandTextShow. Unfortunately,deriveTextShowcannot infer thatamust be an instance ofHasResolution, so it cannot create aTextShowinstance forMyFixed. However, you can usemakeShowbPrecto get around this (see the documentation of themakefunctions for more information).
deriveTextShow :: Name -> Q [Dec] Source
Generates a TextShow instance declaration for the given data type or data
family instance.
Since: 2
deriveTextShow1
deriveTextShow1 automatically generates a Show1 instance declaration for a data
type, a newtype, or a data family instance that has at least one type variable.
This emulates what would (hypothetically) happen if you could attach a deriving
clause to the end of a data declaration. Examples:TextShow1
{-# LANGUAGE TemplateHaskell #-}
import TextShow.TH (deriveTextShow1)
data Stream a = Stream a (Stream a)
$(deriveTextShow1 ''Stream) -- instance Show1 TextStream where ...
newtype WrappedFunctor f a = WrapFunctor (f a)
$(deriveTextShow1 ''WrappedFunctor) -- instance TextShow1 f => TextShow1 (WrappedFunctor f) where ...
The same restrictions that apply to deriveTextShow also apply to deriveTextShow1,
with some caveats:
- With
deriveTextShow1, the last type variable must be of kind*. For other ones, type variables of kind*are assumed to require aTextShowcontext, and type variables of kind* -> *are assumed to require aTextShow1context. For more complicated scenarios, usemakeShowbPrecWith. - If using
-XDatatypeContexts, a datatype constraint cannot mention the last type variable. For example,data Ord a => Illegal a = Illegal acannot have a derivedTextShow1instance. - If the last type variable is used within a data field of a constructor, it must only
be used in the last argument of the data type constructor. For example,
data Legal a = Legal (Either Int a)can have a derivedTextShow1instance, butdata Illegal a = Illegal (Either a a)cannot. - Data family instances must be able to eta-reduce the last type variable. In other words, if you have a instance of the form:
data family Family a1 ... an t data instance Family e1 ... e2 v = ...
Then the following conditions must hold:
vmust be a type variable.vmust not be mentioned in any ofe1, ...,e2.
- In GHC 7.8, a bug exists that can cause problems when a data family declaration and one of its data instances use different type variables, e.g.,
data family Foo a b c data instance Foo Int y z = Foo Int y z $(deriveTextShow1 'Foo)
To avoid this issue, it is recommened that you use the same type variables in the same positions in which they appeared in the data family declaration:
data family Foo a b c data instance Foo Int b c = Foo Int b c $(deriveTextShow1 'Foo)
deriveTextShow1 :: Name -> Q [Dec] Source
Generates a TextShow1 instance declaration for the given data type or data
family instance.
Since: 2
deriveTextShow2
deriveTextShow2 automatically generates a TextShow2 instance declaration for a data
type, a newtype, or a data family instance that has at least two type variables.
This emulates what would (hypothetically) happen if you could attach a deriving
clause to the end of a data declaration. Examples:TextShow2
{-# LANGUAGE TemplateHaskell #-}
import TextShow.TH (deriveShow2)
data OneOrNone a b = OneL a | OneR b | None
$(deriveTextShow2 ''OneOrNone) -- instance TextShow2 OneOrNone where ...
newtype WrappedBifunctor f a b = WrapBifunctor (f a b)
$(deriveTextShow2 ''WrappedBifunctor) -- instance TextShow2 f => TextShow2 (WrappedBifunctor f) where ...
The same restrictions that apply to deriveTextShow and deriveTextShow1 also apply
to deriveTextShow2, with some caveats:
- With
deriveTextShow2, the last type variables must both be of kind*. For other ones, type variables of kind*are assumed to require aTextShowconstraint, type variables of kind* -> *are assumed to require aTextShow1constraint, and type variables of kind* -> * -> *are assumed to require aTextShow2constraint. For more complicated scenarios, usemakeShowbPrecWith2. - If using
-XDatatypeContexts, a datatype constraint cannot mention either of the last two type variables. For example,data Ord a => Illegal a b = Illegal a bcannot have a derivedTextShow2instance. - If either of the last two type variables is used within a data field of a constructor,
it must only be used in the last two arguments of the data type constructor. For
example,
data Legal a b = Legal (Int, Int, a, b)can have a derivedTextShow2instance, butdata Illegal a b = Illegal (a, b, a, b)cannot. - Data family instances must be able to eta-reduce the last two type variables. In other words, if you have a instance of the form:
data family Family a1 ... an t1 t2 data instance Family e1 ... e2 v1 v2 = ...
Then the following conditions must hold:
v1andv2must be distinct type variables.- Neither
v1notv2must be mentioned in any ofe1, ...,e2.
deriveTextShow2 :: Name -> Q [Dec] Source
Generates a TextShow2 instance declaration for the given data type or data
family instance.
Since: 2
make- functions
There may be scenarios in which you want to show an arbitrary data type or data
family instance without having to make the type an instance of TextShow. For these
cases, TextShow.TH provide several functions (all prefixed with make) that
splice the appropriate lambda expression into your source code. Example:
{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
import TextShow.TH (makeShowT)
data ADT = ADT
whichADT :: Bool
whichADT = $(makeShowT ''ADT) ADT == "ADT"
make functions are also useful for creating TextShow instances for data types with
sophisticated type parameters. For example, deriveTextShow cannot infer the correct
type context for newtype HigherKinded f a = HigherKinded (f a), since f is a
higher-kinded type parameter. However, it is still possible to derive a TextShow
instance for HigherKinded without too much trouble using makeShowbPrec:
{-# LANGUAGE FlexibleContexts, TemplateHaskell #-}
import TextShow
import TextShow.TH
instance TextShow (f a) => TextShow (HigherKinded f a) where
showbPrec = $(makeShowbPrec ''HigherKinded)
makeShowt :: Name -> Q Exp Source
Generates a lambda expression which behaves like showt (without requiring a
TextShow instance).
Since: 2
makeShowtl :: Name -> Q Exp Source
Generates a lambda expression which behaves like showtl (without requiring a
TextShow instance).
Since: 2
makeShowtPrec :: Name -> Q Exp Source
Generates a lambda expression which behaves like showtPrec (without requiring a
TextShow instance).
Since: 2
makeShowtlPrec :: Name -> Q Exp Source
Generates a lambda expression which behaves like showtlPrec (without
requiring a TextShow instance).
Since: 2
makeShowtList :: Name -> Q Exp Source
Generates a lambda expression which behaves like showtList (without requiring a
TextShow instance).
Since: 2
makeShowtlList :: Name -> Q Exp Source
Generates a lambda expression which behaves like showtlList (without
requiring a TextShow instance).
Since: 2
makeShowbPrec :: Name -> Q Exp Source
makeShowbList :: Name -> Q Exp Source
makePrintT :: Name -> Q Exp Source
Generates a lambda expression which behaves like printT (without requiring a
TextShow instance).
Since: 2
makePrintTL :: Name -> Q Exp Source
Generates a lambda expression which behaves like printTL (without requiring a
TextShow instance).
Since: 2
makeHPrintT :: Name -> Q Exp Source
Generates a lambda expression which behaves like hPrintT (without requiring a
TextShow instance).
Since: 2
makeHPrintTL :: Name -> Q Exp Source
Generates a lambda expression which behaves like hPrintTL (without
requiring a TextShow instance).
Since: 2
makeShowbPrecWith :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrecWith (without
requiring a TextShow1 instance).
Since: 2
makeShowbPrec1 :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrec1 (without
requiring a TextShow1 instance).
Since: 2
makeShowbPrecWith2 :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrecWith2 (without
requiring a TextShow2 instance).
Since: 2
makeShowbPrec2 :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrecWith2 (without
requiring a TextShow2 instance).
Since: 2