| 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 |
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
- data Options = Options {}
- defaultOptions :: Options
- deriveTextShow :: Name -> Q [Dec]
- deriveTextShow1 :: Name -> Q [Dec]
- makeShowbPrec :: Name -> Q Exp
- deriveTextShow2 :: Name -> Q [Dec]
- makeShowt :: Name -> Q Exp
- makeShowtPrec :: Name -> Q Exp
- makeShowtlPrec :: Name -> Q Exp
- makeLiftShowbPrec :: Name -> Q Exp
- makeLiftShowbPrec2 :: Name -> Q Exp
- data GenTextMethods
- makeShowtl :: Name -> Q Exp
- makeShowtList :: Name -> Q Exp
- makeShowtlList :: Name -> Q Exp
- makeShowb :: Name -> Q Exp
- makeShowbList :: Name -> Q Exp
- makePrintT :: Name -> Q Exp
- makePrintTL :: Name -> Q Exp
- makeHPrintT :: Name -> Q Exp
- makeHPrintTL :: Name -> Q Exp
- makeShowbPrec1 :: Name -> Q Exp
- makeShowbPrec2 :: Name -> Q Exp
- deriveTextShowOptions :: Options -> Name -> Q [Dec]
- deriveTextShow1Options :: Options -> Name -> Q [Dec]
- deriveTextShow2Options :: Options -> Name -> Q [Dec]
Documentation
Options that specify how to derive TextShow instances using Template Haskell.
Since: 3.4
Constructors
| Options | |
Fields
| |
Instances
| Data Options Source # | |||||
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 # | |||||
Defined in TextShow.Options Associated Types
| |||||
| Read Options Source # | |||||
| Show Options Source # | |||||
| Eq Options Source # | |||||
| Ord Options Source # | |||||
| TextShow Options Source # | |||||
Defined in TextShow.TH Methods 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 # | |||||
| Lift Options Source # | |||||
| type Rep Options Source # | |||||
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
deriveTextShow2 :: Name -> Q [Dec] Source #
Generates a TextShow2 instance declaration for the given data type or data
family 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 |
| NeverTextMethods | Never generate them under any circumstances. |
Instances
makeShowtlList :: Name -> Q Exp Source #
Generates a lambda expression which behaves like showtlList (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
| TextShow GenTextMethods Source # | |
Methods 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 # | |
Methods 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 # | |