text-show-3.9.7: 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
Functor FromGeneric Source # 
Instance details

Defined in TextShow.Generic

Methods

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

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

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) #

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

Defined in TextShow.Generic

Methods

lift :: FromGeneric a -> Q Exp #

liftTyped :: FromGeneric a -> Q (TExp (FromGeneric a)) #

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

Defined in TextShow.Generic

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) #

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

Defined in TextShow.Generic

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

Defined in TextShow.Generic

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

Defined in TextShow.Generic

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 #

(Generic a, GTextShowB Zero (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 #

type Rep (FromGeneric a) Source # 
Instance details

Defined in TextShow.Generic

type Rep (FromGeneric a) = D1 ('MetaData "FromGeneric" "TextShow.Generic" "text-show-3.9.7-3HqfCZ2EhfQ6YY909KzVGe" '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.9.7-3HqfCZ2EhfQ6YY909KzVGe" '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 :: FromGeneric1 f a -> Q Exp #

liftTyped :: FromGeneric1 f a -> Q (TExp (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 #

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) #

(Generic1 f, GTextShowB One (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 #

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 #

(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) #

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

Defined in TextShow.Generic

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

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 #

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.9.7-3HqfCZ2EhfQ6YY909KzVGe" '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.9.7-3HqfCZ2EhfQ6YY909KzVGe" '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

Understanding a compiler error

Suppose you intend to define a TextShow instance via FromGeneric:

data Oops = Oops
  deriving TextShow via FromGeneric Oops
    -- forgot to add "deriving Generic" here!

If you forget to add a deriving Generic clause to your data type, at compile-time, you might get an error message that begins roughly as follows:

No instance for (GTextShowB Zero (Rep Oops))

This error can be confusing, but don't let it intimidate you. The correct fix is simply to add the missing "deriving Generic" clause.

Similarly, if the compiler complains about not having an instance for (GTextShowB One (Rep1 Oops1)), add a "deriving Generic1" clause.

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

A Generic implementation of showt.

Since: 2

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

A Generic implementation of showtl.

Since: 2

genericShowtPrec :: (Generic a, GTextShowT Zero (Rep a)) => Int -> a -> Text Source #

A Generic implementation of showPrect.

Since: 2

genericShowtlPrec :: (Generic a, GTextShowTL Zero (Rep a)) => Int -> a -> Text Source #

A Generic implementation of showtlPrec.

Since: 2

genericShowtList :: (Generic a, GTextShowT Zero (Rep a)) => [a] -> Text Source #

A Generic implementation of showtList.

Since: 2

genericShowtlList :: (Generic a, GTextShowTL Zero (Rep a)) => [a] -> Text Source #

A Generic implementation of showtlList.

Since: 2

genericShowb :: (Generic a, GTextShowB Zero (Rep a)) => a -> Builder Source #

A Generic implementation of showb.

Since: 2

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

A Generic implementation of showbPrec.

Since: 2

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

A Generic implementation of showbList.

Since: 2

genericPrintT :: (Generic a, GTextShowT Zero (Rep a)) => a -> IO () Source #

A Generic implementation of printT.

Since: 2

genericPrintTL :: (Generic a, GTextShowTL Zero (Rep a)) => a -> IO () Source #

A Generic implementation of printTL.

Since: 2

genericHPrintT :: (Generic a, GTextShowT Zero (Rep a)) => Handle -> a -> IO () Source #

A Generic implementation of hPrintT.

Since: 2

genericHPrintTL :: (Generic a, GTextShowTL Zero (Rep a)) => Handle -> a -> IO () Source #

A Generic implementation of hPrintTL.

Since: 2

genericLiftShowbPrec :: (Generic1 f, GTextShowB One (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 Zero (Rep a), GTextShowB One (Rep1 f)) => Int -> f a -> Builder Source #

A Generic/Generic1 implementation of showbPrec1.

Since: 2

Internals

Builder

class GTextShowB arity f where Source #

Class of generic representation types that can be converted to a Builder. The arity type variable indicates which type class is used. GTextShowB Zero indicates TextShow behavior, and GTextShowB One indicates TextShow1 behavior. Since: 3.4

Methods

gShowbPrec :: ShowFunsB arity a -> Int -> f a -> Builder Source #

This is used as the default generic implementation of showbPrec (if the arity is Zero) or liftShowbPrec (if the arity is One).

Instances

Instances details
GTextShowB arity (V1 :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrec :: ShowFunsB arity a -> Int -> V1 a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowbPrec :: ShowFunsB arity a -> Int -> C1 c f a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowbPrec :: ShowFunsB arity a -> Int -> (f :+: g) a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowbPrec :: ShowFunsB arity a -> Int -> D1 d f a -> Builder Source #

class GTextShowConB arity f where Source #

Class of generic representation types for which the ConType has been determined. The arity type variable indicates which type class is used. GTextShowConB Zero indicates TextShow behavior, and GTextShowConB One indicates TextShow1 behavior.

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> f a -> Builder Source #

Convert value of a specific ConType to a Builder with the given precedence.

Instances

Instances details
GTextShowConB One Par1 Source # 
Instance details

Defined in TextShow.Generic

GTextShowConB arity (UWord :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> UWord a -> Builder Source #

GTextShowConB arity (UInt :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> UInt a -> Builder Source #

GTextShowConB arity (UFloat :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> UFloat a -> Builder Source #

GTextShowConB arity (UDouble :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> UDouble a -> Builder Source #

GTextShowConB arity (UChar :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> UChar a -> Builder Source #

GTextShowConB arity (U1 :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> U1 a -> Builder Source #

TextShow1 f => GTextShowConB One (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB One a -> Int -> Rec1 f a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> (f :*: g) a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> S1 s f a -> Builder Source #

TextShow c => GTextShowConB arity (K1 i c :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB arity a -> Int -> K1 i c a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB One a -> Int -> (f :.: g) a -> Builder Source #

data ShowFunsB arity a where Source #

A ShowFunsB value either stores nothing (for TextShow) or it stores the two function arguments that show occurrences of the type parameter (for TextShow1). Since: 3.4

Constructors

NoShowFunsB :: ShowFunsB Zero a 
Show1FunsB :: (Int -> a -> Builder) -> ([a] -> Builder) -> ShowFunsB One a 

Instances

Instances details
Contravariant (ShowFunsB arity) Source # 
Instance details

Defined in TextShow.Generic

Methods

contramap :: (a -> b) -> ShowFunsB arity b -> ShowFunsB arity a #

(>$) :: b -> ShowFunsB arity b -> ShowFunsB arity a #

Strict Text

class GTextShowT arity f where Source #

Class of generic representation types that can be converted to a Text. The arity type variable indicates which type class is used. GTextShowT Zero indicates TextShow behavior, and GTextShowT One indicates TextShow1 behavior. Since: 3.4

Methods

gShowtPrec :: ShowFunsT arity a -> Int -> f a -> Text Source #

This is used as the default generic implementation of showtPrec (if the arity is Zero) or liftShowtPrec (if the arity is One).

Instances

Instances details
GTextShowT arity (V1 :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrec :: ShowFunsT arity a -> Int -> V1 a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrec :: ShowFunsT arity a -> Int -> C1 c f a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrec :: ShowFunsT arity a -> Int -> (f :+: g) a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrec :: ShowFunsT arity a -> Int -> D1 d f a -> Text Source #

class GTextShowConT arity f where Source #

Class of generic representation types for which the ConType has been determined. The arity type variable indicates which type class is used. GTextShowConT Zero indicates TextShow behavior, and GTextShowConT One indicates TextShow1 behavior.

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> f a -> Text Source #

Convert value of a specific ConType to a Text with the given precedence.

Instances

Instances details
GTextShowConT One Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT One a -> Int -> Par1 a -> Text Source #

GTextShowConT arity (UWord :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> UWord a -> Text Source #

GTextShowConT arity (UInt :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> UInt a -> Text Source #

GTextShowConT arity (UFloat :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> UFloat a -> Text Source #

GTextShowConT arity (UDouble :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> UDouble a -> Text Source #

GTextShowConT arity (UChar :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> UChar a -> Text Source #

GTextShowConT arity (U1 :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> U1 a -> Text Source #

TextShow1 f => GTextShowConT One (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT One a -> Int -> Rec1 f a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> (f :*: g) a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> S1 s f a -> Text Source #

TextShow c => GTextShowConT arity (K1 i c :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT arity a -> Int -> K1 i c a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT One a -> Int -> (f :.: g) a -> Text Source #

data ShowFunsT arity a where Source #

A ShowFunsT value either stores nothing (for TextShow) or it stores the two function arguments that show occurrences of the type parameter (for TextShow1). Since: 3.4

Constructors

NoShowFunsT :: ShowFunsT Zero a 
Show1FunsT :: (Int -> a -> Text) -> ([a] -> Text) -> ShowFunsT One a 

Instances

Instances details
Contravariant (ShowFunsT arity) Source # 
Instance details

Defined in TextShow.Generic

Methods

contramap :: (a -> b) -> ShowFunsT arity b -> ShowFunsT arity a #

(>$) :: b -> ShowFunsT arity b -> ShowFunsT arity a #

Lazy Text

class GTextShowTL arity f where Source #

Class of generic representation types that can be converted to a Text. The arity type variable indicates which type class is used. GTextShowTL Zero indicates TextShow behavior, and GTextShowTL One indicates TextShow1 behavior. Since: 3.4

Methods

gShowtlPrec :: ShowFunsTL arity a -> Int -> f a -> Text Source #

This is used as the default generic implementation of showtlPrec (if the arity is Zero) or liftShowtlPrec (if the arity is One).

Instances

Instances details
GTextShowTL arity (V1 :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrec :: ShowFunsTL arity a -> Int -> V1 a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrec :: ShowFunsTL arity a -> Int -> C1 c f a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrec :: ShowFunsTL arity a -> Int -> (f :+: g) a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrec :: ShowFunsTL arity a -> Int -> D1 d f a -> Text Source #

class GTextShowConTL arity f where Source #

Class of generic representation types for which the ConType has been determined. The arity type variable indicates which type class is used. GTextShowConTL Zero indicates TextShow behavior, and GTextShowConTL One indicates TextShow1 behavior.

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> f a -> Text Source #

Convert value of a specific ConType to a Text with the given precedence.

Instances

Instances details
GTextShowConTL One Par1 Source # 
Instance details

Defined in TextShow.Generic

GTextShowConTL arity (UWord :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> UWord a -> Text Source #

GTextShowConTL arity (UInt :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> UInt a -> Text Source #

GTextShowConTL arity (UFloat :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> UFloat a -> Text Source #

GTextShowConTL arity (UDouble :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> UDouble a -> Text Source #

GTextShowConTL arity (UChar :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> UChar a -> Text Source #

GTextShowConTL arity (U1 :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> U1 a -> Text Source #

TextShow1 f => GTextShowConTL One (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL One a -> Int -> Rec1 f a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> (f :*: g) a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> S1 s f a -> Text Source #

TextShow c => GTextShowConTL arity (K1 i c :: Type -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL arity a -> Int -> K1 i c a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL One a -> Int -> (f :.: g) a -> Text Source #

data ShowFunsTL arity a where Source #

A ShowFunsTL value either stores nothing (for TextShow) or it stores the two function arguments that show occurrences of the type parameter (for TextShow1). Since: 3.4

Constructors

NoShowFunsTL :: ShowFunsTL Zero a 
Show1FunsTL :: (Int -> a -> Text) -> ([a] -> Text) -> ShowFunsTL One a 

Instances

Instances details
Contravariant (ShowFunsTL arity) Source # 
Instance details

Defined in TextShow.Generic

Methods

contramap :: (a -> b) -> ShowFunsTL arity b -> ShowFunsTL arity a #

(>$) :: b -> ShowFunsTL arity b -> ShowFunsTL arity a #

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 (UWord :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

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

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

Defined in TextShow.Generic

Methods

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

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

Defined in TextShow.Generic

Methods

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

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

Defined in TextShow.Generic

Methods

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

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

Defined in TextShow.Generic

Methods

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

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

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k0). U1 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 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 (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 :.: g :: k -> Type) Source # 
Instance details

Defined in TextShow.Generic

Methods

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

IsNullary Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

isNullary :: forall (a :: k). Par1 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
Eq ConType Source # 
Instance details

Defined in TextShow.Generic

Methods

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

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

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 #

Ord ConType Source # 
Instance details

Defined in TextShow.Generic

Read ConType Source # 
Instance details

Defined in TextShow.Generic

Show ConType Source # 
Instance details

Defined in TextShow.Generic

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 #

TextShow ConType Source # 
Instance details

Defined in TextShow.Generic

Lift ConType Source # 
Instance details

Defined in TextShow.Generic

Methods

lift :: ConType -> Q Exp #

liftTyped :: ConType -> Q (TExp ConType) #

type Rep ConType Source # 
Instance details

Defined in TextShow.Generic

type Rep ConType = D1 ('MetaData "ConType" "TextShow.Generic" "text-show-3.9.7-3HqfCZ2EhfQ6YY909KzVGe" '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))))

data Zero Source #

A type-level indicator that TextShow is being derived generically.

Since: 3.2

data One Source #

A type-level indicator that TextShow1 is being derived generically.

Since: 3.2

Instances

Instances details
GTextShowConTL One Par1 Source # 
Instance details

Defined in TextShow.Generic

GTextShowConT One Par1 Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT One a -> Int -> Par1 a -> Text Source #

GTextShowConB One Par1 Source # 
Instance details

Defined in TextShow.Generic

TextShow1 f => GTextShowConTL One (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL One a -> Int -> Rec1 f a -> Text Source #

TextShow1 f => GTextShowConT One (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT One a -> Int -> Rec1 f a -> Text Source #

TextShow1 f => GTextShowConB One (Rec1 f) Source # 
Instance details

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB One a -> Int -> Rec1 f a -> Builder Source #

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

Defined in TextShow.Generic

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL One a -> Int -> (f :.: g) a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowtPrecCon :: ConType -> ShowFunsT One a -> Int -> (f :.: g) a -> Text Source #

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

Defined in TextShow.Generic

Methods

gShowbPrecCon :: ConType -> ShowFunsB One a -> Int -> (f :.: g) a -> Builder Source #