text-show-3.8.5: Efficient conversion of values into Text

Copyright(C) 2014-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

TextShow.TH

Contents

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

Synopsis

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 TextShowClass clause to the end of a data declaration.

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 to deriveTextShow must not be a type synonym.
  • deriveTextShow makes the assumption that all type variables of kind * require a TextShowClass constraint when creating the type context. For example, if you have data Phantom a = Phantom, then (deriveTextShow ''Phantom) will generate instance TextShowClass a => TextShowClass (Phantom a) where ..., even though TextShowClass a is not required. If you want a proper TextShowClass instance for Phantom, you will need to use makeShowbPrec (see the documentation of the make 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 derive TextShowClass instances for these data types, you will need to use makeShowbPrec.
  • Some data constructors have arguments whose TextShowClass instance depends on a typeclass besides TextShowClass. For example, consider newtype MyFixed a = MyFixed (Fixed a). Fixed a is a TextShowClass instance only if a is an instance of both HasResolution and TextShowClass. Unfortunately, deriveTextShow cannot infer that a must be an instance of HasResolution, so it cannot create a TextShowClass instance for MyFixed. However, you can use makeShowbPrec 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 TextShowClass clause to the end of a data declaration. Examples:

{-# 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 a TextShowClass context, and type variables of kind * -> * are assumed to require a TextShowClass context. For more complicated scenarios, use makeLiftShowbPrec.
  • If using -XDatatypeContexts, a datatype constraint cannot mention the last type variable. For example, data Ord a => Illegal a = Illegal a cannot have a derived TextShowClass 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 derived TextShowClass instance, but data 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:

  1. v must be a type variable.
  2. v must not be mentioned in any of e1, ..., 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 TextShowClass clause to the end of a data declaration. Examples:

{-# 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 a TextShowClass constraint, type variables of kind * -> * are assumed to require a TextShowClass constraint, and type variables of kind * -> * -> * are assumed to require a TextShowClass constraint. For more complicated scenarios, use makeLiftShowbPrec2.
  • 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 derived TextShowClass 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 derived TextShowClass instance, but data 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:

  1. v1 and v2 must be distinct type variables.
  2. Neither v1 not v2 must be mentioned in any of e1, ..., 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

data Options Source #

Options that specify how to derive TextShow instances using Template Haskell.

Since: 3.4

Constructors

Options 

Fields

  • genTextMethods :: GenTextMethods

    When Template Haskell should generate definitions for methods which return Text?

    Since: 3.4

  • emptyCaseBehavior :: Bool

    If True, derived instances for empty data types (i.e., ones with no data constructors) will use the EmptyCase language extension. If False, derived instances will simply use seq instead. (This has no effect on GHCs before 7.8, since EmptyCase is only available in 7.8 or later.)

    Since: 3.7

Instances
Eq Options Source # 
Instance details

Defined in TextShow.Options

Methods

(==) :: Options -> Options -> Bool #

(/=) :: Options -> Options -> Bool #

Data Options Source # 
Instance details

Defined in TextShow.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Options -> c Options #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Options #

toConstr :: Options -> Constr #

dataTypeOf :: Options -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Options) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options) #

gmapT :: (forall b. Data b => b -> b) -> Options -> Options #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Options -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Options -> r #

gmapQ :: (forall d. Data d => d -> u) -> Options -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Options -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Options -> m Options #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Options -> m Options #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Options -> m Options #

Ord Options Source # 
Instance details

Defined in TextShow.Options

Read Options Source # 
Instance details

Defined in TextShow.Options

Show Options Source # 
Instance details

Defined in TextShow.Options

Generic Options Source # 
Instance details

Defined in TextShow.Options

Associated Types

type Rep Options :: Type -> Type #

Methods

from :: Options -> Rep Options x #

to :: Rep Options x -> Options #

Lift Options Source # 
Instance details

Defined in TextShow.Options

Methods

lift :: Options -> Q Exp #

TextShow Options Source # 
Instance details

Defined in TextShow.TH

type Rep Options Source # 
Instance details

Defined in TextShow.Options

type Rep Options = D1 (MetaData "Options" "TextShow.Options" "text-show-3.8.5-BF8Qe0doGepEICuml3c7hp" False) (C1 (MetaCons "Options" PrefixI True) (S1 (MetaSel (Just "genTextMethods") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GenTextMethods) :*: S1 (MetaSel (Just "emptyCaseBehavior") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

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

Constructors

AlwaysTextMethods

Always generate them.

SometimesTextMethods

Only generate when text-show feels it's appropriate.

NeverTextMethods

Never generate them under any circumstances.

Instances
Bounded GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Enum GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Eq GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Data GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenTextMethods -> c GenTextMethods #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenTextMethods #

toConstr :: GenTextMethods -> Constr #

dataTypeOf :: GenTextMethods -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenTextMethods) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenTextMethods) #

gmapT :: (forall b. Data b => b -> b) -> GenTextMethods -> GenTextMethods #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenTextMethods -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenTextMethods -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenTextMethods -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenTextMethods -> m GenTextMethods #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTextMethods -> m GenTextMethods #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTextMethods -> m GenTextMethods #

Ord GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Read GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Show GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Ix GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Generic GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Associated Types

type Rep GenTextMethods :: Type -> Type #

Lift GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Methods

lift :: GenTextMethods -> Q Exp #

TextShow GenTextMethods Source # 
Instance details

Defined in TextShow.TH

type Rep GenTextMethods Source # 
Instance details

Defined in TextShow.Options

type Rep GenTextMethods = D1 (MetaData "GenTextMethods" "TextShow.Options" "text-show-3.8.5-BF8Qe0doGepEICuml3c7hp" False) (C1 (MetaCons "AlwaysTextMethods" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SometimesTextMethods" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NeverTextMethods" PrefixI False) (U1 :: Type -> Type)))

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