text-show-3.11.3: 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

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

Documentation

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.

    Since: 3.7

Instances

Instances details
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 :: forall r r'. (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 #

Generic Options Source # 
Instance details

Defined in TextShow.Options

Associated Types

type Rep Options 
Instance details

Defined in TextShow.Options

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

Methods

from :: Options -> Rep Options x #

to :: Rep Options x -> Options #

Read Options Source # 
Instance details

Defined in TextShow.Options

Show Options Source # 
Instance details

Defined in TextShow.Options

Eq Options Source # 
Instance details

Defined in TextShow.Options

Methods

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

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

Ord Options Source # 
Instance details

Defined in TextShow.Options

TextShow Options Source # 
Instance details

Defined in TextShow.TH

Lift Options Source # 
Instance details

Defined in TextShow.Options

Methods

lift :: Quote m => Options -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Options -> Code m Options #

type Rep Options Source # 
Instance details

Defined in TextShow.Options

type Rep Options = D1 ('MetaData "Options" "TextShow.Options" "text-show-3.11.3-9AwtPAQNGMv1t3CES9CRJ8" '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

deriveTextShow :: Name -> Q [Dec] Source #

Generates a TextShow instance declaration for the given data type or data family instance.

Since: 2

deriveTextShow1 :: Name -> Q [Dec] Source #

Generates a TextShow1 instance declaration for the given data type or data family instance.

Since: 2

makeShowbPrec :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showbPrec (without requiring a TextShow instance).

Since: 2

deriveTextShow2 :: Name -> Q [Dec] Source #

Generates a TextShow2 instance declaration for the given data type or data family instance.

Since: 2

makeShowt :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showt (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

makeLiftShowbPrec :: Name -> Q Exp Source #

Generates a lambda expression which behaves like liftShowbPrec (without requiring a TextShow1 instance).

Since: 3

makeLiftShowbPrec2 :: Name -> Q Exp Source #

Generates a lambda expression which behaves like liftShowbPrec2 (without requiring a TextShow2 instance).

Since: 3

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

Instances details
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 :: forall r r'. (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 #

Bounded GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Enum GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Generic GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Associated Types

type Rep GenTextMethods 
Instance details

Defined in TextShow.Options

type Rep GenTextMethods = D1 ('MetaData "GenTextMethods" "TextShow.Options" "text-show-3.11.3-9AwtPAQNGMv1t3CES9CRJ8" '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)))
Ix 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

Eq GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Ord GenTextMethods Source # 
Instance details

Defined in TextShow.Options

TextShow GenTextMethods Source # 
Instance details

Defined in TextShow.TH

Lift GenTextMethods Source # 
Instance details

Defined in TextShow.Options

Methods

lift :: Quote m => GenTextMethods -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => GenTextMethods -> Code m GenTextMethods #

type Rep GenTextMethods Source # 
Instance details

Defined in TextShow.Options

type Rep GenTextMethods = D1 ('MetaData "GenTextMethods" "TextShow.Options" "text-show-3.11.3-9AwtPAQNGMv1t3CES9CRJ8" '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)))

makeShowtl :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showtl (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

makeShowb :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showb (without requiring a TextShow instance).

Since: 2

makeShowbList :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showbList (without requiring a TextShow instance).

Since: 2

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

makeShowbPrec1 :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showbPrec1 (without requiring a TextShow1 instance).

Since: 2

makeShowbPrec2 :: Name -> Q Exp Source #

Generates a lambda expression which behaves like showbPrec2 (without requiring a TextShow2 instance).

Since: 2

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