text-show-3.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

Contents

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 show functions

TextShow instances can be easily defined for data types that are Generic instances. The easiest way to do this is to use the DeriveGeneric extension.

{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
import TextShow
import TextShow.Generic

data D a = D a
  deriving (Generic, Generic1)

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

instance TextShow1 D where
    liftShowbPrec = genericLiftShowbPrec

Understanding a compiler error

Suppose you intend to use genericShowbPrec to define a TextShow instance.

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

instance TextShow Oops where
    showbPrec = genericShowbPrec

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

Minimal complete definition

gShowbPrec

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

GTextShowB One V1 Source # 

Methods

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

GTextShowB Zero V1 Source # 

Methods

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

(Constructor Meta c, GTextShowConB arity f, IsNullary * f) => GTextShowB arity (C1 c f) Source # 

Methods

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

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

Methods

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

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

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.

Minimal complete definition

gShowbPrecCon

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

GTextShowConB arity UWord Source # 

Methods

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

GTextShowConB arity UInt Source # 

Methods

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

GTextShowConB arity UFloat Source # 

Methods

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

GTextShowConB arity UDouble Source # 

Methods

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

GTextShowConB arity UChar Source # 

Methods

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

GTextShowConB arity U1 Source # 

Methods

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

GTextShowConB One Par1 Source # 
TextShow1 f => GTextShowConB One (Rec1 f) Source # 

Methods

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

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

Methods

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

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

Methods

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

TextShow c => GTextShowConB arity (K1 i c) Source # 

Methods

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

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

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

Contravariant (ShowFunsB arity) Source # 

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

Minimal complete definition

gShowtPrec

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

GTextShowT One V1 Source # 

Methods

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

GTextShowT Zero V1 Source # 

Methods

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

(Constructor Meta c, GTextShowConT arity f, IsNullary * f) => GTextShowT arity (C1 c f) Source # 

Methods

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

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

Methods

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

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

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.

Minimal complete definition

gShowtPrecCon

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

GTextShowConT arity UWord Source # 

Methods

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

GTextShowConT arity UInt Source # 

Methods

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

GTextShowConT arity UFloat Source # 

Methods

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

GTextShowConT arity UDouble Source # 

Methods

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

GTextShowConT arity UChar Source # 

Methods

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

GTextShowConT arity U1 Source # 

Methods

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

GTextShowConT One Par1 Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

TextShow c => GTextShowConT arity (K1 i c) Source # 

Methods

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

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

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

Contravariant (ShowFunsT arity) Source # 

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

Minimal complete definition

gShowtlPrec

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

GTextShowTL One V1 Source # 

Methods

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

GTextShowTL Zero V1 Source # 

Methods

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

(Constructor Meta c, GTextShowConTL arity f, IsNullary * f) => GTextShowTL arity (C1 c f) Source # 

Methods

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

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

Methods

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

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

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.

Minimal complete definition

gShowtlPrecCon

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

GTextShowConTL arity UWord Source # 

Methods

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

GTextShowConTL arity UInt Source # 

Methods

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

GTextShowConTL arity UFloat Source # 

Methods

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

GTextShowConTL arity UDouble Source # 

Methods

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

GTextShowConTL arity UChar Source # 

Methods

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

GTextShowConTL arity U1 Source # 

Methods

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

GTextShowConTL One Par1 Source # 
TextShow1 f => GTextShowConTL One (Rec1 f) Source # 

Methods

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

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

Methods

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

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

Methods

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

TextShow c => GTextShowConTL arity (K1 i c) Source # 

Methods

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

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

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

Contravariant (ShowFunsTL arity) Source # 

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.

Minimal complete definition

isNullary

Methods

isNullary :: f a -> Bool Source #

Instances

IsNullary * U1 Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * UChar Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * UDouble Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * UFloat Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * UInt Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * UWord Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * (Rec1 f) Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * (K1 i c) Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * ((:*:) f g) Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * ((:.:) f g) Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * f => IsNullary * (S1 s f) Source # 

Methods

isNullary :: f a -> Bool Source #

IsNullary * Par1 Source # 

Methods

isNullary :: f 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

Eq ConType Source # 

Methods

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

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

Data ConType Source # 

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 :: (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 # 
Read ConType Source # 
Show ConType Source # 
Generic ConType Source # 

Associated Types

type Rep ConType :: * -> * #

Methods

from :: ConType -> Rep ConType x #

to :: Rep ConType x -> ConType #

Lift ConType Source # 

Methods

lift :: ConType -> Q Exp #

TextShow ConType Source # 
type Rep ConType Source # 
type Rep ConType = D1 (MetaData "ConType" "TextShow.Generic" "text-show-3.7-6jZ65hp38R6KdTZv9c1P1P" False) ((:+:) ((:+:) (C1 (MetaCons "Rec" PrefixI False) U1) (C1 (MetaCons "Tup" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Pref" PrefixI False) U1) (C1 (MetaCons "Inf" PrefixI False) (S1 (MetaSel (Nothing 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

GTextShowConTL One Par1 Source # 
GTextShowTL One V1 Source # 

Methods

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

GTextShowConT One Par1 Source # 

Methods

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

GTextShowT One V1 Source # 

Methods

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

GTextShowConB One Par1 Source # 
GTextShowB One V1 Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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