| 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 |
Text.Show.Text.TH
Description
Functions to mechanically derive Show, Show1, or Show2 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: 0.3
- deriveShow :: Name -> Q [Dec]
- deriveShow1 :: Name -> Q [Dec]
- deriveShow2 :: Name -> Q [Dec]
- mkShow :: Name -> Q Exp
- mkShowLazy :: Name -> Q Exp
- mkShowPrec :: Name -> Q Exp
- mkShowPrecLazy :: Name -> Q Exp
- mkShowList :: Name -> Q Exp
- mkShowListLazy :: Name -> Q Exp
- mkShowb :: Name -> Q Exp
- mkShowbPrec :: Name -> Q Exp
- mkShowbList :: Name -> Q Exp
- mkPrint :: Name -> Q Exp
- mkPrintLazy :: Name -> Q Exp
- mkHPrint :: Name -> Q Exp
- mkHPrintLazy :: Name -> Q Exp
- mkShowbPrecWith :: Name -> Q Exp
- mkShowbPrec1 :: Name -> Q Exp
- mkShowbPrecWith2 :: Name -> Q Exp
- mkShowbPrec2 :: Name -> Q Exp
deriveShow
deriveShow automatically generates a Show 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.Show
Here are some examples of how to derive simple data types:
{-# LANGUAGE TemplateHaskell #-}
import Text.Show.Text.TH (deriveShow)
data Letter = A | B | C
$(deriveShow ''Letter) -- instance Show Letter where ...
newtype Box a = Box a
$(deriveShow ''Box) -- instance Show a => Show (Box a) where ...
If you are using template-haskell-2.7.0.0 or later, deriveShow can also be used
to derive Show instances for data family instances (which requires the
-XTypeFamilies extension). To do so, pass the name of a data instance or newtype
instance constructor to deriveShow. Note that the generated code may require the
-XFlexibleInstances extension. Some examples:
{-# LANGUAGE FlexibleInstances, TemplateHaskell, TypeFamilies #-}
import Text.Show.Text.TH (deriveShow)
class AssocClass a where
data AssocData a
instance AssocClass Int where
data AssocData Int = AssocDataInt1 Int | AssocDataInt2 Int Int
$(deriveShow 'AssocDataInt1) -- instance Show (AssocData Int) where ...
-- Alternatively, one could use $(deriveShow 'AssocDataInt2)
data family DataFam a b
newtype instance DataFam () b = DataFamB b
$(deriveShow 'DataFamB) -- instance Show b => Show (DataFam () b)
Note that at the moment, there are some limitations:
- The
Nameargument toderiveShowmust not be a type synonym. deriveShowmakes the assumption that all type variables of kind*require aShowconstraint when creating the type context. For example, if you havedata Phantom a = Phantom, then(will generatederiveShow''Phantom)instance, even thoughShowa =>Show(Phantom a) whereis not required. If you want a properShowaShowinstance forPhantom, you will need to usemkShowbPrec(see the documentation of themkfunctions for more information).deriveShowlacks 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 deriveShowinstances for these data types, you will need to usemkShowbPrec(see the documentation of themkfunctions for more information).- Some data constructors have arguments whose
Showinstance depends on a typeclass besidesShow. For example, considernewtype MyFixed a = MyFixed (Fixed a).is aFixedaShowinstance only ifais an instance of bothHasResolutionandShow. Unfortunately,deriveShowcannot infer thatamust be an instance ofHasResolution, so it cannot create aShowinstance forMyFixed. However, you can usemkShowbPrecto get around this (see the documentation of themkfunctions for more information).
deriveShow :: Name -> Q [Dec] Source
Generates a Show instance declaration for the given data type or data
family instance.
Since: 0.3
deriveShow1
deriveShow1 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:Show1
{-# LANGUAGE TemplateHaskell #-}
import Text.Show.Text.TH (deriveShow1)
data Stream a = Stream a (Stream a)
$(deriveShow1 ''Stream) -- instance Show1 Stream where ...
newtype WrappedFunctor f a = WrapFunctor (f a)
$(deriveShow1 ''WrappedFunctor) -- instance Show1 f => Show1 (WrappedFunctor f) where ...
The same restrictions that apply to deriveShow also apply to deriveShow1, with
some caveats:
- With
deriveShow1, the last type variable must be of kind*. For other ones, type variables of kind*are assumed to require aShowcontext, and type variables of kind* -> *are assumed to require aShow1context. For more complicated scenarios, usemkShowbPrecWith. - If using
DatatypeContexts, a datatype constraint cannot mention the last type variable. For example,data Show a => Illegal a = Illegal acannot have a derivedShow1instance. - 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 derivedShow1instance, 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 $(deriveShow1 '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 $(deriveShow 'Foo)
deriveShow1 :: Name -> Q [Dec] Source
Generates a Show1 instance declaration for the given data type or data
family instance.
Since: 1
deriveShow2
deriveShow2 automatically generates a Show2 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:Show2
{-# LANGUAGE TemplateHaskell #-}
import Text.Show.Text.TH (deriveShow2)
data OneOrNone a b = OneL a | OneR b | None
$(deriveShow2 ''OneOrNone) -- instance Show2 OneOrNone where ...
newtype WrappedBifunctor f a b = WrapBifunctor (f a b)
$(deriveShow2 ''WrappedBifunctor) -- instance Show2 f => Show2 (WrappedBifunctor f) where ...
The same restrictions that apply to deriveShow and deriveShow1 also apply to
deriveShow2, with some caveats:
- With
deriveShow2, the last type variables must both be of kind*. For other ones, type variables of kind*are assumed to require aShowconstraint, type variables of kind* -> *are assumed to require aShow1constraint, and type variables of kind* -> * -> *are assumed to require aShow2constraint. For more complicated scenarios, usemkShowbPrecWith2. - If using
DatatypeContexts, a datatype constraint cannot mention either of the last two type variables. For example,data Show a => Illegal a b = Illegal a bcannot have a derivedShow2instance. - 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 derivedShow2instance, 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.
deriveShow2 :: Name -> Q [Dec] Source
Generates a Show2 instance declaration for the given data type or data
family instance.
Since: 1
mk 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 Show. For these
cases, Text.Show.Text.TH provide several functions (all prefixed with mk) that
splice the appropriate lambda expression into your source code.
As an example, suppose you have data ADT = ADT, which is not an instance of Show.
With mkShow, you can still convert it to Text:
{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
import Text.Show.Text.TH (mkShow)
whichADT :: Bool
whichADT = $(mkShow ''ADT) ADT == "ADT"
mk functions are also useful for creating Show instances for data types with
sophisticated type parameters. For example, deriveShow 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 Show
instance for HigherKinded without too much trouble using mkShowbPrec:
{-# LANGUAGE FlexibleContexts, TemplateHaskell #-}
import Prelude hiding (Show)
import Text.Show.Text (Show(showbPrec))
import Text.Show.Text.TH (mkShowbPrec)
instance Show (f a) => Show (HigherKinded f a) where
showbPrec = $(mkShowbPrec ''HigherKinded)
mkShowLazy :: Name -> Q Exp Source
mkShowPrec :: Name -> Q Exp Source
mkShowPrecLazy :: Name -> Q Exp Source
Generates a lambda expression which behaves like showPrecLazy (without
requiring a Show instance).
Since: 0.3.1
mkShowList :: Name -> Q Exp Source
mkShowListLazy :: Name -> Q Exp Source
Generates a lambda expression which behaves like showListLazy (without
requiring a Show instance).
Since: 0.5
mkShowbPrec :: Name -> Q Exp Source
mkShowbList :: Name -> Q Exp Source
mkPrintLazy :: Name -> Q Exp Source
mkHPrintLazy :: Name -> Q Exp Source
Generates a lambda expression which behaves like hPrintLazy (without
requiring a Show instance).
Since: 0.3.1
mkShowbPrecWith :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrecWith (without
requiring a Show1 instance).
Since: 1
mkShowbPrec1 :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrec1 (without
requiring a Show1 instance).
Since: 1
mkShowbPrecWith2 :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrecWith2 (without
requiring a Show2 instance).
Since: 1
mkShowbPrec2 :: Name -> Q Exp Source
Generates a lambda expression which behaves like showbPrecWith2 (without
requiring a Show2 instance).
Since: 1