Copyright | (C) 2014-2017 Ryan Scott |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Ryan Scott |
Stability | Provisional |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
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
Synopsis
- 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
- makeLiftShowbPrec :: Name -> Q Exp
- makeShowbPrec1 :: Name -> Q Exp
- makeLiftShowbPrec2 :: Name -> Q Exp
- makeShowbPrec2 :: Name -> Q Exp
- data Options = Options {}
- defaultOptions :: Options
- data GenTextMethods
- deriveTextShowOptions :: Options -> Name -> Q [Dec]
- deriveTextShow1Options :: Options -> Name -> Q [Dec]
- deriveTextShow2Options :: Options -> Name -> Q [Dec]
deriveTextShow
deriveTextShow
automatically generates a TextShowClass
instance declaration for a data
type, newtype, or data family instance. This emulates what would (hypothetically)
happen if you could attach a deriving
clause to the end of a data
declaration.TextShowClass
Here are some examples of how to derive TextShowClass
for simple data types:
{-# LANGUAGE TemplateHaskell #-} import TextShow.TH 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 ...
deriveTextShow
can also be used to derive TextShowClass
instances for data family
instances (which requires the -XTypeFamilies
extension). To do so, pass the name of
a data or newtype instance constructor (NOT a data family name!) 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
Name
argument toderiveTextShow
must not be a type synonym. deriveTextShow
makes the assumption that all type variables of kind*
require aTextShowClass
constraint when creating the type context. For example, if you havedata Phantom a = Phantom
, then(
will generatederiveTextShow
''Phantom)instance
, even thoughTextShowClass
a =>TextShowClass
(Phantom a) where ...
is not required. If you want a properTextShowClass
aTextShowClass
instance forPhantom
, you will need to usemakeShowbPrec
(see the documentation of themake
functions for more information).deriveTextShow
lacks 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 deriveTextShowClass
instances for these data types, you will need to usemakeShowbPrec
.- Some data constructors have arguments whose
TextShowClass
instance depends on a typeclass besidesTextShowClass
. For example, considernewtype MyFixed a = MyFixed (Fixed a)
.
is aFixed
aTextShowClass
instance only ifa
is an instance of bothHasResolution
andTextShowClass
. Unfortunately,deriveTextShow
cannot infer thata
must be an instance ofHasResolution
, so it cannot create aTextShowClass
instance forMyFixed
. However, you can usemakeShowbPrec
to get around this.
deriveTextShow :: Name -> Q [Dec] Source #
Generates a TextShowClass
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, newtype, or 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:TextShowClass
{-# LANGUAGE TemplateHaskell #-} import TextShow.TH data Stream a = Stream a (Stream a) $(deriveTextShow1
''Stream) -- instance TextShow1 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 aTextShowClass
context, and type variables of kind* -> *
are assumed to require aTextShowClass
context. For more complicated scenarios, usemakeLiftShowbPrec
. - If using
-XDatatypeContexts
, a datatype constraint cannot mention the last type variable. For example,data Ord a => Illegal a = Illegal a
cannot have a derivedTextShowClass
instance. - 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 derivedTextShowClass
instance, 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:
v
must be a type variable.v
must not be mentioned in any ofe1
, ...,e2
.
deriveTextShow1 :: Name -> Q [Dec] Source #
Generates a TextShowClass
instance declaration for the given data type or data
family instance.
Since: 2
deriveTextShow2
deriveTextShow2
automatically generates a TextShowClass
instance declaration for a data
type, newtype, or 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:TextShowClass
{-# LANGUAGE TemplateHaskell #-} import TextShow.TH 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 aTextShowClass
constraint, type variables of kind* -> *
are assumed to require aTextShowClass
constraint, and type variables of kind* -> * -> *
are assumed to require aTextShowClass
constraint. For more complicated scenarios, usemakeLiftShowbPrec2
. - 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 b
cannot have a derivedTextShowClass
instance. - 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 derivedTextShowClass
instance, 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:
v1
andv2
must be distinct type variables.- Neither
v1
notv2
must be mentioned in any ofe1
, ...,e2
.
deriveTextShow2 :: Name -> Q [Dec] Source #
Generates a TextShowClass
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 TextShowClass
. For these
cases, this modules provides several functions (all prefixed with make
-) that
splice the appropriate lambda expression into your source code. Example:
This is particularly useful for creating instances for sophisticated data types. For
example, deriveTextShow
cannot infer the correct type context for
newtype HigherKinded f a = HigherKinded (f a)
, since f
is of kind * -> *
.
However, it is still possible to derive a TextShowClass
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
TextShowClass
instance).
Since: 2
makeShowtl :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showtl
(without requiring a
TextShowClass
instance).
Since: 2
makeShowtPrec :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showtPrec
(without requiring a
TextShowClass
instance).
Since: 2
makeShowtlPrec :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showtlPrec
(without
requiring a TextShowClass
instance).
Since: 2
makeShowtList :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showtList
(without requiring a
TextShowClass
instance).
Since: 2
makeShowtlList :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showtlList
(without
requiring a TextShowClass
instance).
Since: 2
makeShowb :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showb
(without requiring a
TextShowClass
instance).
Since: 2
makeShowbPrec :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showbPrec
(without requiring a
TextShowClass
instance).
Since: 2
makeShowbList :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showbList
(without requiring a
TextShowClass
instance).
Since: 2
makePrintT :: Name -> Q Exp Source #
Generates a lambda expression which behaves like printT
(without requiring a
TextShowClass
instance).
Since: 2
makePrintTL :: Name -> Q Exp Source #
Generates a lambda expression which behaves like printTL
(without requiring a
TextShowClass
instance).
Since: 2
makeHPrintT :: Name -> Q Exp Source #
Generates a lambda expression which behaves like hPrintT
(without requiring a
TextShowClass
instance).
Since: 2
makeHPrintTL :: Name -> Q Exp Source #
Generates a lambda expression which behaves like hPrintTL
(without
requiring a TextShowClass
instance).
Since: 2
makeLiftShowbPrec :: Name -> Q Exp Source #
Generates a lambda expression which behaves like liftShowbPrec
(without
requiring a TextShowClass
instance).
Since: 3
makeShowbPrec1 :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showbPrec1
(without
requiring a TextShowClass
instance).
Since: 2
makeLiftShowbPrec2 :: Name -> Q Exp Source #
Generates a lambda expression which behaves like liftShowbPrec2
(without
requiring a TextShowClass
instance).
Since: 3
makeShowbPrec2 :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showbPrec2
(without
requiring a TextShowClass
instance).
Since: 2
Options
Options that specify how to derive TextShow
instances using Template Haskell.
Since: 3.4
Options | |
|
Instances
defaultOptions :: Options Source #
Sensible default Options
.
Since: 3.4
data GenTextMethods Source #
When should Template Haskell generate implementations for the methods of
TextShow
which return Text
?
Since: 3.4
AlwaysTextMethods | Always generate them. |
SometimesTextMethods | Only generate when |
NeverTextMethods | Never generate them under any circumstances. |
Instances
deriveTextShowOptions :: Options -> Name -> Q [Dec] Source #
Like deriveTextShow
, but takes an Options
argument.
Since: 3.4
deriveTextShow1Options :: Options -> Name -> Q [Dec] Source #
Like deriveTextShow1
, but takes an Options
argument.
Since: 3.4
deriveTextShow2Options :: Options -> Name -> Q [Dec] Source #
Like deriveTextShow2
, but takes an Options
argument.
Since: 3.4
Orphan instances
TextShow GenTextMethods Source # | |
showbPrec :: Int -> GenTextMethods -> Builder Source # showb :: GenTextMethods -> Builder Source # showbList :: [GenTextMethods] -> Builder Source # showtPrec :: Int -> GenTextMethods -> Text Source # showt :: GenTextMethods -> Text Source # showtList :: [GenTextMethods] -> Text Source # showtlPrec :: Int -> GenTextMethods -> Text Source # showtl :: GenTextMethods -> Text Source # showtlList :: [GenTextMethods] -> Text Source # | |
TextShow Options Source # | |
showbPrec :: Int -> Options -> Builder Source # showb :: Options -> Builder Source # showbList :: [Options] -> Builder Source # showtPrec :: Int -> Options -> Text Source # showt :: Options -> Text Source # showtList :: [Options] -> Text Source # showtlPrec :: Int -> Options -> Text Source # showtl :: Options -> Text Source # showtlList :: [Options] -> Text Source # |