text-show-3.10: 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.Generic

Description

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

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

Constructors

FromGeneric 

Fields

Instances

Instances details
Foldable FromGeneric Source # 
Instance details

Defined in TextShow.Generic

Methods

fold :: Monoid m => FromGeneric m -> m #

foldMap :: Monoid m => (a -> m) -> FromGeneric a -> m #

foldMap' :: Monoid m => (a -> m) -> FromGeneric a -> m #

foldr :: (a -> b -> b) -> b -> FromGeneric a -> b #

foldr' :: (a -> b -> b) -> b -> FromGeneric a -> b #

foldl :: (b -> a -> b) -> b -> FromGeneric a -> b #

foldl' :: (b -> a -> b) -> b -> FromGeneric a -> b #

foldr1 :: (a -> a -> a) -> FromGeneric a -> a #

foldl1 :: (a -> a -> a) -> FromGeneric a -> a #

toList :: FromGeneric a -> [a] #

null :: FromGeneric a -> Bool #

length :: FromGeneric a -> Int #

elem :: Eq a => a -> FromGeneric a -> Bool #

maximum :: Ord a => FromGeneric a -> a #

minimum :: Ord a => FromGeneric a -> a #

sum :: Num a => FromGeneric a -> a #

product :: Num a => FromGeneric a -> a #

Traversable FromGeneric Source # 
Instance details

Defined in TextShow.Generic

Methods

traverse :: Applicative f => (a -> f b) -> FromGeneric a -> f (FromGeneric b) #

sequenceA :: Applicative f => FromGeneric (f a) -> f (FromGeneric a) #

mapM :: Monad m => (a -> m b) -> FromGeneric a -> m (FromGeneric b) #

sequence :: Monad m => FromGeneric (m a) -> m (FromGeneric a) #

Functor FromGeneric Source # 
Instance details

Defined in TextShow.Generic

Methods

fmap :: (a -> b) -> FromGeneric a -> FromGeneric b #

(<$) :: a -> FromGeneric b -> FromGeneric a #

Data a => Data (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

Methods

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

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

toConstr :: FromGeneric a -> Constr #

dataTypeOf :: FromGeneric a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

Associated Types

type Rep (FromGeneric a) :: Type -> Type #

Methods

from :: FromGeneric a -> Rep (FromGeneric a) x #

to :: Rep (FromGeneric a) x -> FromGeneric a #

Read a => Read (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

Show a => Show (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

Eq a => Eq (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

Ord a => Ord (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

(Generic a, GTextShowB (Rep a ())) => TextShow (FromGeneric a) Source #

Since: 3.7.4

Instance details

Defined in TextShow.Generic

Generic1 FromGeneric Source # 
Instance details

Defined in TextShow.Generic

Associated Types

type Rep1 FromGeneric :: k -> Type #

Methods

from1 :: forall (a :: k). FromGeneric a -> Rep1 FromGeneric a #

to1 :: forall (a :: k). Rep1 FromGeneric a -> FromGeneric a #

Lift a => Lift (FromGeneric a :: Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

lift :: Quote m => FromGeneric a -> m Exp #

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

type Rep (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

type Rep (FromGeneric a) = D1 ('MetaData "FromGeneric" "TextShow.Generic" "text-show-3.10-4oaWXJVD4dqWldBonHjwo" 'True) (C1 ('MetaCons "FromGeneric" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromGeneric") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep1 FromGeneric Source # 
Instance details

Defined in TextShow.Generic

type Rep1 FromGeneric = D1 ('MetaData "FromGeneric" "TextShow.Generic" "text-show-3.10-4oaWXJVD4dqWldBonHjwo" 'True) (C1 ('MetaCons "FromGeneric" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromGeneric") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

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

Constructors

FromGeneric1 

Fields

Instances

Instances details
Generic1 (FromGeneric1 f :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Associated Types

type Rep1 (FromGeneric1 f) :: k -> Type #

Methods

from1 :: forall (a :: k0). FromGeneric1 f a -> Rep1 (FromGeneric1 f) a #

to1 :: forall (a :: k0). Rep1 (FromGeneric1 f) a -> FromGeneric1 f a #

Lift (f a) => Lift (FromGeneric1 f a :: Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

lift :: Quote m => FromGeneric1 f a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FromGeneric1 f a -> Code m (FromGeneric1 f a) #

Foldable f => Foldable (FromGeneric1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

fold :: Monoid m => FromGeneric1 f m -> m #

foldMap :: Monoid m => (a -> m) -> FromGeneric1 f a -> m #

foldMap' :: Monoid m => (a -> m) -> FromGeneric1 f a -> m #

foldr :: (a -> b -> b) -> b -> FromGeneric1 f a -> b #

foldr' :: (a -> b -> b) -> b -> FromGeneric1 f a -> b #

foldl :: (b -> a -> b) -> b -> FromGeneric1 f a -> b #

foldl' :: (b -> a -> b) -> b -> FromGeneric1 f a -> b #

foldr1 :: (a -> a -> a) -> FromGeneric1 f a -> a #

foldl1 :: (a -> a -> a) -> FromGeneric1 f a -> a #

toList :: FromGeneric1 f a -> [a] #

null :: FromGeneric1 f a -> Bool #

length :: FromGeneric1 f a -> Int #

elem :: Eq a => a -> FromGeneric1 f a -> Bool #

maximum :: Ord a => FromGeneric1 f a -> a #

minimum :: Ord a => FromGeneric1 f a -> a #

sum :: Num a => FromGeneric1 f a -> a #

product :: Num a => FromGeneric1 f a -> a #

Traversable f => Traversable (FromGeneric1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

traverse :: Applicative f0 => (a -> f0 b) -> FromGeneric1 f a -> f0 (FromGeneric1 f b) #

sequenceA :: Applicative f0 => FromGeneric1 f (f0 a) -> f0 (FromGeneric1 f a) #

mapM :: Monad m => (a -> m b) -> FromGeneric1 f a -> m (FromGeneric1 f b) #

sequence :: Monad m => FromGeneric1 f (m a) -> m (FromGeneric1 f a) #

Functor f => Functor (FromGeneric1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

fmap :: (a -> b) -> FromGeneric1 f a -> FromGeneric1 f b #

(<$) :: a -> FromGeneric1 f b -> FromGeneric1 f a #

(Generic1 f, GTextShowB1 (Rep1 f)) => TextShow1 (FromGeneric1 f) Source #

Since: 3.7.4

Instance details

Defined in TextShow.Generic

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromGeneric1 f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromGeneric1 f a] -> Builder Source #

(Data (f a), Typeable f, Typeable a) => Data (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromGeneric1 f a -> c (FromGeneric1 f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromGeneric1 f a) #

toConstr :: FromGeneric1 f a -> Constr #

dataTypeOf :: FromGeneric1 f a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> FromGeneric1 f a -> FromGeneric1 f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromGeneric1 f a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromGeneric1 f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromGeneric1 f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromGeneric1 f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromGeneric1 f a -> m (FromGeneric1 f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromGeneric1 f a -> m (FromGeneric1 f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromGeneric1 f a -> m (FromGeneric1 f a) #

Generic (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

Associated Types

type Rep (FromGeneric1 f a) :: Type -> Type #

Methods

from :: FromGeneric1 f a -> Rep (FromGeneric1 f a) x #

to :: Rep (FromGeneric1 f a) x -> FromGeneric1 f a #

Read (f a) => Read (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

Show (f a) => Show (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

Eq (f a) => Eq (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

Methods

(==) :: FromGeneric1 f a -> FromGeneric1 f a -> Bool #

(/=) :: FromGeneric1 f a -> FromGeneric1 f a -> Bool #

Ord (f a) => Ord (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

(Generic1 f, GTextShowB (Rep1 f a)) => TextShow (FromGeneric1 f a) Source #

Since: 3.10

Instance details

Defined in TextShow.Generic

type Rep1 (FromGeneric1 f :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

type Rep1 (FromGeneric1 f :: k -> Type) = D1 ('MetaData "FromGeneric1" "TextShow.Generic" "text-show-3.10-4oaWXJVD4dqWldBonHjwo" 'True) (C1 ('MetaCons "FromGeneric1" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromGeneric1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
type Rep (FromGeneric1 f a) Source # 
Instance details

Defined in TextShow.Generic

type Rep (FromGeneric1 f a) = D1 ('MetaData "FromGeneric1" "TextShow.Generic" "text-show-3.10-4oaWXJVD4dqWldBonHjwo" 'True) (C1 ('MetaCons "FromGeneric1" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromGeneric1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

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)
  deriving TextShow  via FromGeneric  (D a)
  deriving TextShow1 via FromGeneric1 D

Or, if you are using a version of GHC older than 8.6, one can alternatively define these instances like so:

instance TextShow a => TextShow (D a) where
    showbPrec = genericShowbPrec

instance TextShow1 D where
    liftShowbPrec = genericLiftShowbPrec

genericShowt :: (Generic a, GTextShowT (Rep a ())) => a -> Text Source #

A Generic implementation of showt.

Since: 2

genericShowtl :: (Generic a, GTextShowTL (Rep a ())) => a -> Text Source #

A Generic implementation of showtl.

Since: 2

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 #

A Generic implementation of showtList.

Since: 2

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 #

A Generic implementation of showb.

Since: 2

genericShowbPrec :: (Generic a, GTextShowB (Rep a ())) => Int -> a -> Builder Source #

A Generic implementation of showbPrec.

Since: 2

genericShowbList :: (Generic a, GTextShowB (Rep a ())) => [a] -> Builder Source #

A Generic implementation of showbList.

Since: 2

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 #

A Generic/Generic1 implementation of showbPrec1.

Since: 2

Internals

Builder

class GTextShowB a where Source #

Class of generic representation types that can be converted to a Builder. Since: 3.10

Methods

gShowbPrec :: Int -> a -> Builder Source #

Instances

Instances details
GTextShowB (V1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrec :: Int -> V1 p -> Builder Source #

(GTextShowB (f p), GTextShowB (g p)) => GTextShowB ((f :+: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrec :: Int -> (f :+: g) p -> Builder Source #

(Constructor c, GTextShowConB (f p), IsNullary f) => GTextShowB (C1 c f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrec :: Int -> C1 c f p -> Builder Source #

GTextShowB (f p) => GTextShowB (D1 d f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrec :: Int -> D1 d f p -> Builder Source #

class GTextShowConB a where Source #

Methods

gShowbPrecCon :: ConType -> Int -> a -> Builder Source #

Instances

Instances details
TextShow p => GTextShowConB (Par1 p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConB (U1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> Int -> U1 p -> Builder Source #

GTextShowConB (UChar p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConB (UDouble p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConB (UFloat p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConB (UInt p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConB (UWord p) Source # 
Instance details

Defined in TextShow.Generic

(TextShow1 f, TextShow p) => GTextShowConB (Rec1 f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> Int -> Rec1 f p -> Builder Source #

(GTextShowConB (f p), GTextShowConB (g p)) => GTextShowConB ((f :*: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> Int -> (f :*: g) p -> Builder Source #

TextShow c => GTextShowConB (K1 i c p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> Int -> K1 i c p -> Builder Source #

(Selector s, GTextShowConB (f p)) => GTextShowConB (S1 s f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> Int -> S1 s f p -> Builder Source #

(TextShow1 f, GTextShowConB (g p)) => GTextShowConB ((f :.: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> Int -> (f :.: g) p -> Builder Source #

class (forall a. TextShow a => GTextShowB (f a)) => GTextShowB1 f where Source #

Methods

gLiftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder Source #

Instances

Instances details
GTextShowB1 (V1 :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> V1 a -> Builder Source #

(GTextShowB1 f, GTextShowB1 g) => GTextShowB1 (f :+: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> (f :+: g) a -> Builder Source #

(Constructor c, GTextShowConB1 f, IsNullary f) => GTextShowB1 (C1 c f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> C1 c f a -> Builder Source #

GTextShowB1 f => GTextShowB1 (D1 d f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> D1 d f a -> Builder Source #

class (forall a. TextShow a => GTextShowConB (f a)) => GTextShowConB1 f where Source #

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> f a -> Builder Source #

Instances

Instances details
GTextShowConB1 Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> Par1 a -> Builder Source #

GTextShowConB1 (U1 :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> U1 a -> Builder Source #

GTextShowConB1 (UChar :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> UChar a -> Builder Source #

GTextShowConB1 (UDouble :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> UDouble a -> Builder Source #

GTextShowConB1 (UFloat :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> UFloat a -> Builder Source #

GTextShowConB1 (UInt :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> UInt a -> Builder Source #

GTextShowConB1 (UWord :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> UWord a -> Builder Source #

TextShow1 f => GTextShowConB1 (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> Rec1 f a -> Builder Source #

(GTextShowConB1 f, GTextShowConB1 g) => GTextShowConB1 (f :*: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> (f :*: g) a -> Builder Source #

TextShow c => GTextShowConB1 (K1 i c :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> K1 i c a -> Builder Source #

(Selector s, GTextShowConB1 f) => GTextShowConB1 (S1 s f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> S1 s f a -> Builder Source #

(TextShow1 f, GTextShowConB1 g) => GTextShowConB1 (f :.: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowbPrecCon :: (Int -> a -> Builder) -> ([a] -> Builder) -> ConType -> Int -> (f :.: g) a -> Builder Source #

Strict Text

class GTextShowT a where Source #

Class of generic representation types that can be converted to a Text. Since: 3.10

Methods

gShowtPrec :: Int -> a -> Text Source #

Instances

Instances details
GTextShowT (V1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrec :: Int -> V1 p -> Text Source #

(GTextShowT (f p), GTextShowT (g p)) => GTextShowT ((f :+: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrec :: Int -> (f :+: g) p -> Text Source #

(Constructor c, GTextShowConT (f p), IsNullary f) => GTextShowT (C1 c f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrec :: Int -> C1 c f p -> Text Source #

GTextShowT (f p) => GTextShowT (D1 d f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrec :: Int -> D1 d f p -> Text Source #

class GTextShowConT a where Source #

Methods

gShowtPrecCon :: ConType -> Int -> a -> Text Source #

Instances

Instances details
TextShow p => GTextShowConT (Par1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> Par1 p -> Text Source #

GTextShowConT (U1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> U1 p -> Text Source #

GTextShowConT (UChar p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> UChar p -> Text Source #

GTextShowConT (UDouble p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConT (UFloat p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> UFloat p -> Text Source #

GTextShowConT (UInt p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> UInt p -> Text Source #

GTextShowConT (UWord p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> UWord p -> Text Source #

(TextShow1 f, TextShow p) => GTextShowConT (Rec1 f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> Rec1 f p -> Text Source #

(GTextShowConT (f p), GTextShowConT (g p)) => GTextShowConT ((f :*: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> (f :*: g) p -> Text Source #

TextShow c => GTextShowConT (K1 i c p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> K1 i c p -> Text Source #

(Selector s, GTextShowConT (f p)) => GTextShowConT (S1 s f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> S1 s f p -> Text Source #

(TextShow1 f, GTextShowConT (g p)) => GTextShowConT ((f :.: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> Int -> (f :.: g) p -> Text Source #

class (forall a. TextShow a => GTextShowT (f a)) => GTextShowT1 f where Source #

Methods

gLiftShowtPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text Source #

Instances

Instances details
GTextShowT1 (V1 :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> V1 a -> Text Source #

(GTextShowT1 f, GTextShowT1 g) => GTextShowT1 (f :+: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> (f :+: g) a -> Text Source #

(Constructor c, GTextShowConT1 f, IsNullary f) => GTextShowT1 (C1 c f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> C1 c f a -> Text Source #

GTextShowT1 f => GTextShowT1 (D1 d f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> D1 d f a -> Text Source #

class (forall a. TextShow a => GTextShowConT (f a)) => GTextShowConT1 f where Source #

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> f a -> Text Source #

Instances

Instances details
GTextShowConT1 Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> Par1 a -> Text Source #

GTextShowConT1 (U1 :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> U1 a -> Text Source #

GTextShowConT1 (UChar :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UChar a -> Text Source #

GTextShowConT1 (UDouble :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UDouble a -> Text Source #

GTextShowConT1 (UFloat :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UFloat a -> Text Source #

GTextShowConT1 (UInt :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UInt a -> Text Source #

GTextShowConT1 (UWord :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UWord a -> Text Source #

TextShow1 f => GTextShowConT1 (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> Rec1 f a -> Text Source #

(GTextShowConT1 f, GTextShowConT1 g) => GTextShowConT1 (f :*: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> (f :*: g) a -> Text Source #

TextShow c => GTextShowConT1 (K1 i c :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> K1 i c a -> Text Source #

(Selector s, GTextShowConT1 f) => GTextShowConT1 (S1 s f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> S1 s f a -> Text Source #

(TextShow1 f, GTextShowConT1 g) => GTextShowConT1 (f :.: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> (f :.: g) a -> Text Source #

Lazy Text

class GTextShowTL a where Source #

Class of generic representation types that can be converted to a Text. Since: 3.10

Methods

gShowtlPrec :: Int -> a -> Text Source #

Instances

Instances details
GTextShowTL (V1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrec :: Int -> V1 p -> Text Source #

(GTextShowTL (f p), GTextShowTL (g p)) => GTextShowTL ((f :+: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrec :: Int -> (f :+: g) p -> Text Source #

(Constructor c, GTextShowConTL (f p), IsNullary f) => GTextShowTL (C1 c f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrec :: Int -> C1 c f p -> Text Source #

GTextShowTL (f p) => GTextShowTL (D1 d f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrec :: Int -> D1 d f p -> Text Source #

class GTextShowConTL a where Source #

Methods

gShowtlPrecCon :: ConType -> Int -> a -> Text Source #

Instances

Instances details
TextShow p => GTextShowConTL (Par1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> Par1 p -> Text Source #

GTextShowConTL (U1 p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> U1 p -> Text Source #

GTextShowConTL (UChar p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> UChar p -> Text Source #

GTextShowConTL (UDouble p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConTL (UFloat p) Source # 
Instance details

Defined in TextShow.Generic

GTextShowConTL (UInt p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> UInt p -> Text Source #

GTextShowConTL (UWord p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> UWord p -> Text Source #

(TextShow1 f, TextShow p) => GTextShowConTL (Rec1 f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> Rec1 f p -> Text Source #

(GTextShowConTL (f p), GTextShowConTL (g p)) => GTextShowConTL ((f :*: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> (f :*: g) p -> Text Source #

TextShow c => GTextShowConTL (K1 i c p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> K1 i c p -> Text Source #

(Selector s, GTextShowConTL (f p)) => GTextShowConTL (S1 s f p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> S1 s f p -> Text Source #

(TextShow1 f, GTextShowConTL (g p)) => GTextShowConTL ((f :.: g) p) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> Int -> (f :.: g) p -> Text Source #

class (forall a. TextShow a => GTextShowTL (f a)) => GTextShowTL1 f where Source #

Methods

gLiftShowtlPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text Source #

Instances

Instances details
GTextShowTL1 (V1 :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> V1 a -> Text Source #

(GTextShowTL1 f, GTextShowTL1 g) => GTextShowTL1 (f :+: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> (f :+: g) a -> Text Source #

(Constructor c, GTextShowConTL1 f, IsNullary f) => GTextShowTL1 (C1 c f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> C1 c f a -> Text Source #

GTextShowTL1 f => GTextShowTL1 (D1 d f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> D1 d f a -> Text Source #

class (forall a. TextShow a => GTextShowConTL (f a)) => GTextShowConTL1 f where Source #

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> f a -> Text Source #

Instances

Instances details
GTextShowConTL1 Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> Par1 a -> Text Source #

GTextShowConTL1 (U1 :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> U1 a -> Text Source #

GTextShowConTL1 (UChar :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UChar a -> Text Source #

GTextShowConTL1 (UDouble :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UDouble a -> Text Source #

GTextShowConTL1 (UFloat :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UFloat a -> Text Source #

GTextShowConTL1 (UInt :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UInt a -> Text Source #

GTextShowConTL1 (UWord :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> UWord a -> Text Source #

TextShow1 f => GTextShowConTL1 (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> Rec1 f a -> Text Source #

(GTextShowConTL1 f, GTextShowConTL1 g) => GTextShowConTL1 (f :*: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> (f :*: g) a -> Text Source #

TextShow c => GTextShowConTL1 (K1 i c :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> K1 i c a -> Text Source #

(Selector s, GTextShowConTL1 f) => GTextShowConTL1 (S1 s f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> S1 s f a -> Text Source #

(TextShow1 f, GTextShowConTL1 g) => GTextShowConTL1 (f :.: g) Source # 
Instance details

Defined in TextShow.Generic

Methods

gLiftShowtlPrecCon :: (Int -> a -> Text) -> ([a] -> Text) -> ConType -> Int -> (f :.: g) a -> Text Source #

Other internals

class IsNullary f where Source #

Class of generic representation types that represent a constructor with zero or more fields.

Methods

isNullary :: f a -> Bool Source #

Instances

Instances details
IsNullary Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k). Par1 a -> Bool Source #

IsNullary (U1 :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). U1 a -> Bool Source #

IsNullary (UChar :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). UChar a -> Bool Source #

IsNullary (UDouble :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). UDouble a -> Bool Source #

IsNullary (UFloat :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). UFloat a -> Bool Source #

IsNullary (UInt :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). UInt a -> Bool Source #

IsNullary (UWord :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). UWord a -> Bool Source #

IsNullary (Rec1 f :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). Rec1 f a -> Bool Source #

IsNullary (f :*: g :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). (f :*: g) a -> Bool Source #

IsNullary (K1 i c :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). K1 i c a -> Bool Source #

IsNullary f => IsNullary (S1 s f :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). S1 s f a -> Bool Source #

IsNullary (f :.: g :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). (f :.: g) a -> Bool Source #

data ConType Source #

Whether a constructor is a record (Rec), a tuple (Tup), is prefix (Pref), or infix (Inf).

Since: 2

Constructors

Rec 
Tup 
Pref 
Inf String 

Instances

Instances details
Data ConType Source # 
Instance details

Defined in TextShow.Generic

Methods

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 # 
Instance details

Defined in TextShow.Generic

Associated Types

type Rep ConType :: Type -> Type #

Methods

from :: ConType -> Rep ConType x #

to :: Rep ConType x -> ConType #

Read ConType Source # 
Instance details

Defined in TextShow.Generic

Show ConType Source # 
Instance details

Defined in TextShow.Generic

Eq ConType Source # 
Instance details

Defined in TextShow.Generic

Methods

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

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

Ord ConType Source # 
Instance details

Defined in TextShow.Generic

TextShow ConType Source # 
Instance details

Defined in TextShow.Generic

Lift ConType Source # 
Instance details

Defined in TextShow.Generic

Methods

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

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

type Rep ConType Source # 
Instance details

Defined in TextShow.Generic

type Rep ConType = D1 ('MetaData "ConType" "TextShow.Generic" "text-show-3.10-4oaWXJVD4dqWldBonHjwo" '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))))