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 |
Generic versions of TextShow
and TextShow1
class functions, as an alternative to
TextShow.TH, which uses Template Haskell. Because there is no Generic2
class, TextShow2
cannot be implemented generically.
This implementation is loosely based off of the Generics.Deriving.Show
module
from the generic-deriving
library.
Since: 2
Synopsis
- newtype FromGeneric a = FromGeneric {
- fromGeneric :: a
- newtype FromGeneric1 f a = FromGeneric1 {
- fromGeneric1 :: f a
- genericShowt :: (Generic a, GTextShowT (Rep a ())) => a -> Text
- genericShowtl :: (Generic a, GTextShowTL (Rep a ())) => a -> Text
- genericShowtPrec :: (Generic a, GTextShowT (Rep a ())) => Int -> a -> Text
- genericShowtlPrec :: (Generic a, GTextShowTL (Rep a ())) => Int -> a -> Text
- genericShowtList :: (Generic a, GTextShowT (Rep a ())) => [a] -> Text
- genericShowtlList :: (Generic a, GTextShowTL (Rep a ())) => [a] -> Text
- genericShowb :: (Generic a, GTextShowB (Rep a ())) => a -> Builder
- genericShowbPrec :: (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder
- genericShowbList :: (Generic a, GTextShowB (Rep a ())) => [a] -> Builder
- genericPrintT :: (Generic a, GTextShowT (Rep a ())) => a -> IO ()
- genericPrintTL :: (Generic a, GTextShowTL (Rep a ())) => a -> IO ()
- genericHPrintT :: (Generic a, GTextShowT (Rep a ())) => Handle -> a -> IO ()
- genericHPrintTL :: (Generic a, GTextShowTL (Rep a ())) => Handle -> a -> IO ()
- genericLiftShowbPrec :: (Generic1 f, GTextShowB1 (Rep1 f)) => (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
- genericShowbPrec1 :: (Generic a, Generic1 f, GTextShowB (Rep a ()), GTextShowB1 (Rep1 f)) => Int -> f a -> Builder
- class GTextShowB a where
- gShowbPrec :: Int -> a -> Builder
- class GTextShowConB a where
- gShowbPrecCon :: ConType -> Int -> a -> Builder
- class (forall a. TextShow a => GTextShowB (f a)) => GTextShowB1 f where
- class (forall a. TextShow a => GTextShowConB (f a)) => GTextShowConB1 f where
- class GTextShowT a where
- gShowtPrec :: Int -> a -> Text
- class GTextShowConT a where
- gShowtPrecCon :: ConType -> Int -> a -> Text
- class (forall a. TextShow a => GTextShowT (f a)) => GTextShowT1 f where
- class (forall a. TextShow a => GTextShowConT (f a)) => GTextShowConT1 f where
- class GTextShowTL a where
- gShowtlPrec :: Int -> a -> Text
- class GTextShowConTL a where
- gShowtlPrecCon :: ConType -> Int -> a -> Text
- class (forall a. TextShow a => GTextShowTL (f a)) => GTextShowTL1 f where
- class (forall a. TextShow a => GTextShowConTL (f a)) => GTextShowConTL1 f where
- class IsNullary f where
- data ConType
Generic adapter newtypes
newtype FromGeneric a Source #
An adapter newtype, suitable for DerivingVia
.
The TextShow
instance for FromGeneric
leverages a Generic
-based
default. That is,
showbPrec
p (FromGeneric
x) =genericShowbPrec
p x
Since: 3.7.4
FromGeneric | |
|
Instances
newtype FromGeneric1 f a Source #
An adapter newtype, suitable for DerivingVia
.
The TextShow1
instance for FromGeneric1
leverages a Generic1
-based
default. That is,
liftShowbPrec
sp sl p (FromGeneric1
x) =genericLiftShowbPrec
sp sl p x
Since: 3.7.4
FromGeneric1 | |
|
Instances
Generic show
functions
TextShow
instances can be easily defined for data types that are Generic
instances.
If you are using GHC 8.6 or later, the easiest way to do this is to use the
DerivingVia
extension.
{-# LANGUAGE DeriveGeneric, DerivingVia #-} import GHC.Generics import TextShow import TextShow.Generic data D a = D a deriving (Generic
,Generic1
) derivingTextShow
viaFromGeneric
(D a) derivingTextShow1
viaFromGeneric1
D
Or, if you are using a version of GHC older than 8.6, one can alternatively define these instances like so:
instanceTextShow
a =>TextShow
(D a) whereshowbPrec
=genericShowbPrec
instanceTextShow1
D whereliftShowbPrec
=genericLiftShowbPrec
genericShowt :: (Generic a, GTextShowT (Rep a ())) => a -> Text Source #
genericShowtl :: (Generic a, GTextShowTL (Rep a ())) => a -> Text Source #
genericShowtPrec :: (Generic a, GTextShowT (Rep a ())) => Int -> a -> Text Source #
A Generic
implementation of showPrect
.
Since: 2
genericShowtlPrec :: (Generic a, GTextShowTL (Rep a ())) => Int -> a -> Text Source #
A Generic
implementation of showtlPrec
.
Since: 2
genericShowtList :: (Generic a, GTextShowT (Rep a ())) => [a] -> Text Source #
genericShowtlList :: (Generic a, GTextShowTL (Rep a ())) => [a] -> Text Source #
A Generic
implementation of showtlList
.
Since: 2
genericShowb :: (Generic a, GTextShowB (Rep a ())) => a -> Builder Source #
genericShowbPrec :: (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder Source #
genericShowbList :: (Generic a, GTextShowB (Rep a ())) => [a] -> Builder Source #
genericPrintT :: (Generic a, GTextShowT (Rep a ())) => a -> IO () Source #
A Generic
implementation of printT
.
Since: 2
genericPrintTL :: (Generic a, GTextShowTL (Rep a ())) => a -> IO () Source #
A Generic
implementation of printTL
.
Since: 2
genericHPrintT :: (Generic a, GTextShowT (Rep a ())) => Handle -> a -> IO () Source #
A Generic
implementation of hPrintT
.
Since: 2
genericHPrintTL :: (Generic a, GTextShowTL (Rep a ())) => Handle -> a -> IO () Source #
A Generic
implementation of hPrintTL
.
Since: 2
genericLiftShowbPrec :: (Generic1 f, GTextShowB1 (Rep1 f)) => (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder Source #
A Generic1
implementation of genericLiftShowbPrec
.
Since: 2
genericShowbPrec1 :: (Generic a, Generic1 f, GTextShowB (Rep a ()), GTextShowB1 (Rep1 f)) => Int -> f a -> Builder Source #
Internals
Builder
class GTextShowB a where Source #
Class of generic representation types that can be converted to a Builder
. Since: 3.10
gShowbPrec :: Int -> a -> Builder Source #
Instances
GTextShowB (V1 p) Source # | |
Defined in TextShow.Generic | |
(GTextShowB (f p), GTextShowB (g p)) => GTextShowB ((f :+: g) p) Source # | |
Defined in TextShow.Generic | |
(Constructor c, GTextShowConB (f p), IsNullary f) => GTextShowB (C1 c f p) Source # | |
Defined in TextShow.Generic | |
GTextShowB (f p) => GTextShowB (D1 d f p) Source # | |
Defined in TextShow.Generic |
class GTextShowConB a where Source #
Instances
TextShow p => GTextShowConB (Par1 p) Source # | |
Defined in TextShow.Generic | |
GTextShowConB (U1 p) Source # | |
Defined in TextShow.Generic | |
GTextShowConB (UChar p) Source # | |
Defined in TextShow.Generic | |
GTextShowConB (UDouble p) Source # | |
Defined in TextShow.Generic | |
GTextShowConB (UFloat p) Source # | |
Defined in TextShow.Generic | |
GTextShowConB (UInt p) Source # | |
Defined in TextShow.Generic | |
GTextShowConB (UWord p) Source # | |
Defined in TextShow.Generic | |
(TextShow1 f, TextShow p) => GTextShowConB (Rec1 f p) Source # | |
Defined in TextShow.Generic | |
(GTextShowConB (f p), GTextShowConB (g p)) => GTextShowConB ((f :*: g) p) Source # | |
Defined in TextShow.Generic | |
TextShow c => GTextShowConB (K1 i c p) Source # | |
Defined in TextShow.Generic | |
(Selector s, GTextShowConB (f p)) => GTextShowConB (S1 s f p) Source # | |
Defined in TextShow.Generic | |
(TextShow1 f, GTextShowConB (g p)) => GTextShowConB ((f :.: g) p) Source # | |
Defined in TextShow.Generic |
class (forall a. TextShow a => GTextShowB (f a)) => GTextShowB1 f where Source #
Instances
GTextShowB1 (V1 :: Type -> Type) Source # | |
Defined in TextShow.Generic | |
(GTextShowB1 f, GTextShowB1 g) => GTextShowB1 (f :+: g) Source # | |
Defined in TextShow.Generic | |
(Constructor c, GTextShowConB1 f, IsNullary f) => GTextShowB1 (C1 c f) Source # | |
Defined in TextShow.Generic | |
GTextShowB1 f => GTextShowB1 (D1 d f) Source # | |
Defined in TextShow.Generic |
class (forall a. TextShow a => GTextShowConB (f a)) => GTextShowConB1 f where Source #
gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> f a -> Builder Source #
Instances
GTextShowConB1 Par1 Source # | |
GTextShowConB1 (U1 :: Type -> Type) Source # | |
GTextShowConB1 (UChar :: Type -> Type) Source # | |
GTextShowConB1 (UDouble :: Type -> Type) Source # | |
GTextShowConB1 (UFloat :: Type -> Type) Source # | |
GTextShowConB1 (UInt :: Type -> Type) Source # | |
GTextShowConB1 (UWord :: Type -> Type) Source # | |
TextShow1 f => GTextShowConB1 (Rec1 f) Source # | |
(GTextShowConB1 f, GTextShowConB1 g) => GTextShowConB1 (f :*: g) Source # | |
TextShow c => GTextShowConB1 (K1 i c :: Type -> Type) Source # | |
(Selector s, GTextShowConB1 f) => GTextShowConB1 (S1 s f) Source # | |
(TextShow1 f, GTextShowConB1 g) => GTextShowConB1 (f :.: g) Source # | |
Strict Text
class GTextShowT a where Source #
Class of generic representation types that can be converted to a Text
. Since: 3.10
gShowtPrec :: Int -> a -> Text Source #
Instances
GTextShowT (V1 p) Source # | |
Defined in TextShow.Generic | |
(GTextShowT (f p), GTextShowT (g p)) => GTextShowT ((f :+: g) p) Source # | |
Defined in TextShow.Generic | |
(Constructor c, GTextShowConT (f p), IsNullary f) => GTextShowT (C1 c f p) Source # | |
Defined in TextShow.Generic | |
GTextShowT (f p) => GTextShowT (D1 d f p) Source # | |
Defined in TextShow.Generic |
class GTextShowConT a where Source #
Instances
TextShow p => GTextShowConT (Par1 p) Source # | |
Defined in TextShow.Generic | |
GTextShowConT (U1 p) Source # | |
Defined in TextShow.Generic | |
GTextShowConT (UChar p) Source # | |
Defined in TextShow.Generic | |
GTextShowConT (UDouble p) Source # | |
Defined in TextShow.Generic | |
GTextShowConT (UFloat p) Source # | |
Defined in TextShow.Generic | |
GTextShowConT (UInt p) Source # | |
Defined in TextShow.Generic | |
GTextShowConT (UWord p) Source # | |
Defined in TextShow.Generic | |
(TextShow1 f, TextShow p) => GTextShowConT (Rec1 f p) Source # | |
Defined in TextShow.Generic | |
(GTextShowConT (f p), GTextShowConT (g p)) => GTextShowConT ((f :*: g) p) Source # | |
Defined in TextShow.Generic | |
TextShow c => GTextShowConT (K1 i c p) Source # | |
Defined in TextShow.Generic | |
(Selector s, GTextShowConT (f p)) => GTextShowConT (S1 s f p) Source # | |
Defined in TextShow.Generic | |
(TextShow1 f, GTextShowConT (g p)) => GTextShowConT ((f :.: g) p) Source # | |
Defined in TextShow.Generic |
class (forall a. TextShow a => GTextShowT (f a)) => GTextShowT1 f where Source #
Instances
GTextShowT1 (V1 :: Type -> Type) Source # | |
Defined in TextShow.Generic | |
(GTextShowT1 f, GTextShowT1 g) => GTextShowT1 (f :+: g) Source # | |
Defined in TextShow.Generic | |
(Constructor c, GTextShowConT1 f, IsNullary f) => GTextShowT1 (C1 c f) Source # | |
Defined in TextShow.Generic | |
GTextShowT1 f => GTextShowT1 (D1 d f) Source # | |
Defined in TextShow.Generic |
class (forall a. TextShow a => GTextShowConT (f a)) => GTextShowConT1 f where Source #
Instances
GTextShowConT1 Par1 Source # | |
GTextShowConT1 (U1 :: Type -> Type) Source # | |
GTextShowConT1 (UChar :: Type -> Type) Source # | |
GTextShowConT1 (UDouble :: Type -> Type) Source # | |
GTextShowConT1 (UFloat :: Type -> Type) Source # | |
GTextShowConT1 (UInt :: Type -> Type) Source # | |
GTextShowConT1 (UWord :: Type -> Type) Source # | |
TextShow1 f => GTextShowConT1 (Rec1 f) Source # | |
(GTextShowConT1 f, GTextShowConT1 g) => GTextShowConT1 (f :*: g) Source # | |
TextShow c => GTextShowConT1 (K1 i c :: Type -> Type) Source # | |
(Selector s, GTextShowConT1 f) => GTextShowConT1 (S1 s f) Source # | |
(TextShow1 f, GTextShowConT1 g) => GTextShowConT1 (f :.: g) Source # | |
Lazy Text
class GTextShowTL a where Source #
Class of generic representation types that can be converted to a Text
. Since: 3.10
gShowtlPrec :: Int -> a -> Text Source #
Instances
GTextShowTL (V1 p) Source # | |
Defined in TextShow.Generic | |
(GTextShowTL (f p), GTextShowTL (g p)) => GTextShowTL ((f :+: g) p) Source # | |
Defined in TextShow.Generic | |
(Constructor c, GTextShowConTL (f p), IsNullary f) => GTextShowTL (C1 c f p) Source # | |
Defined in TextShow.Generic | |
GTextShowTL (f p) => GTextShowTL (D1 d f p) Source # | |
Defined in TextShow.Generic |
class GTextShowConTL a where Source #
Instances
TextShow p => GTextShowConTL (Par1 p) Source # | |
Defined in TextShow.Generic | |
GTextShowConTL (U1 p) Source # | |
Defined in TextShow.Generic | |
GTextShowConTL (UChar p) Source # | |
Defined in TextShow.Generic | |
GTextShowConTL (UDouble p) Source # | |
Defined in TextShow.Generic | |
GTextShowConTL (UFloat p) Source # | |
Defined in TextShow.Generic | |
GTextShowConTL (UInt p) Source # | |
Defined in TextShow.Generic | |
GTextShowConTL (UWord p) Source # | |
Defined in TextShow.Generic | |
(TextShow1 f, TextShow p) => GTextShowConTL (Rec1 f p) Source # | |
Defined in TextShow.Generic | |
(GTextShowConTL (f p), GTextShowConTL (g p)) => GTextShowConTL ((f :*: g) p) Source # | |
Defined in TextShow.Generic | |
TextShow c => GTextShowConTL (K1 i c p) Source # | |
Defined in TextShow.Generic | |
(Selector s, GTextShowConTL (f p)) => GTextShowConTL (S1 s f p) Source # | |
Defined in TextShow.Generic | |
(TextShow1 f, GTextShowConTL (g p)) => GTextShowConTL ((f :.: g) p) Source # | |
Defined in TextShow.Generic |
class (forall a. TextShow a => GTextShowTL (f a)) => GTextShowTL1 f where Source #
Instances
GTextShowTL1 (V1 :: Type -> Type) Source # | |
Defined in TextShow.Generic | |
(GTextShowTL1 f, GTextShowTL1 g) => GTextShowTL1 (f :+: g) Source # | |
Defined in TextShow.Generic | |
(Constructor c, GTextShowConTL1 f, IsNullary f) => GTextShowTL1 (C1 c f) Source # | |
Defined in TextShow.Generic | |
GTextShowTL1 f => GTextShowTL1 (D1 d f) Source # | |
Defined in TextShow.Generic |
class (forall a. TextShow a => GTextShowConTL (f a)) => GTextShowConTL1 f where Source #
Instances
GTextShowConTL1 Par1 Source # | |
GTextShowConTL1 (U1 :: Type -> Type) Source # | |
GTextShowConTL1 (UChar :: Type -> Type) Source # | |
GTextShowConTL1 (UDouble :: Type -> Type) Source # | |
GTextShowConTL1 (UFloat :: Type -> Type) Source # | |
GTextShowConTL1 (UInt :: Type -> Type) Source # | |
GTextShowConTL1 (UWord :: Type -> Type) Source # | |
TextShow1 f => GTextShowConTL1 (Rec1 f) Source # | |
(GTextShowConTL1 f, GTextShowConTL1 g) => GTextShowConTL1 (f :*: g) Source # | |
TextShow c => GTextShowConTL1 (K1 i c :: Type -> Type) Source # | |
(Selector s, GTextShowConTL1 f) => GTextShowConTL1 (S1 s f) Source # | |
(TextShow1 f, GTextShowConTL1 g) => GTextShowConTL1 (f :.: g) Source # | |
Other internals
class IsNullary f where Source #
Class of generic representation types that represent a constructor with zero or more fields.
Instances
IsNullary Par1 Source # | |
IsNullary (U1 :: k -> Type) Source # | |
IsNullary (UChar :: k -> Type) Source # | |
IsNullary (UDouble :: k -> Type) Source # | |
IsNullary (UFloat :: k -> Type) Source # | |
IsNullary (UInt :: k -> Type) Source # | |
IsNullary (UWord :: k -> Type) Source # | |
IsNullary (Rec1 f :: k -> Type) Source # | |
IsNullary (f :*: g :: k -> Type) Source # | |
IsNullary (K1 i c :: k -> Type) Source # | |
IsNullary f => IsNullary (S1 s f :: k -> Type) Source # | |
IsNullary (f :.: g :: k -> Type) Source # | |
Instances
Data ConType Source # | |
Defined in TextShow.Generic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConType -> c ConType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConType # toConstr :: ConType -> Constr # dataTypeOf :: ConType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConType) # gmapT :: (forall b. Data b => b -> b) -> ConType -> ConType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConType -> r # gmapQ :: (forall d. Data d => d -> u) -> ConType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConType -> m ConType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConType -> m ConType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConType -> m ConType # | |
Generic ConType Source # | |
Read ConType Source # | |
Show ConType Source # | |
Eq ConType Source # | |
Ord ConType Source # | |
TextShow ConType Source # | |
Defined in TextShow.Generic showbPrec :: Int -> ConType -> Builder Source # showb :: ConType -> Builder Source # showbList :: [ConType] -> Builder Source # showtPrec :: Int -> ConType -> Text Source # showt :: ConType -> Text Source # showtList :: [ConType] -> Text Source # showtlPrec :: Int -> ConType -> Text Source # showtl :: ConType -> Text Source # showtlList :: [ConType] -> Text Source # | |
Lift ConType Source # | |
type Rep ConType Source # | |
Defined in TextShow.Generic type Rep ConType = D1 ('MetaData "ConType" "TextShow.Generic" "text-show-3.10.5-9kIsI5kUu5RFXpCwih7TWK" 'False) ((C1 ('MetaCons "Rec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tup" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pref" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |