text-show-3.6: 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 #

A Generic implementation of showt.

Since: 2

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

A Generic implementation of showtl.

Since: 2

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

A Generic implementation of showPrect.

Since: 2

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

A Generic implementation of showtlPrec.

Since: 2

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

A Generic implementation of showtList.

Since: 2

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

A Generic implementation of showtlList.

Since: 2

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

A Generic implementation of showb.

Since: 2

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

A Generic implementation of showbPrec.

Since: 2

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

A Generic implementation of showbList.

Since: 2

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

A Generic implementation of printT.

Since: 2

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

A Generic implementation of printTL.

Since: 2

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

A Generic implementation of hPrintT.

Since: 2

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

A Generic implementation of hPrintTL.

Since: 2

genericLiftShowbPrec :: (Generic1 f, GTextShowB One (Rep1 f)) => (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder #

A Generic1 implementation of genericLiftShowbPrec.

Since: 2

genericShowbPrec1 :: (Generic a, Generic1 f, GTextShowB Zero (Rep a), GTextShowB One (Rep1 f)) => Int -> f a -> Builder #

A 'Generic'/'Generic1' implementation of showbPrec1.

Since: 2

Internals

Builder

class GTextShowB arity f where #

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 #

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 # 

Methods

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

GTextShowB Zero V1 # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class GTextShowConB arity f where #

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 #

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

Instances

GTextShowConB arity UWord # 

Methods

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

GTextShowConB arity UInt # 

Methods

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

GTextShowConB arity UFloat # 

Methods

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

GTextShowConB arity UDouble # 

Methods

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

GTextShowConB arity UChar # 

Methods

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

GTextShowConB arity U1 # 

Methods

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

GTextShowConB One Par1 # 

Methods

gShowbPrecCon :: ConType -> ShowFunsB One a -> Int -> Par1 a -> Builder #

TextShow1 f => GTextShowConB One (Rec1 f) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

data ShowFunsB arity a where #

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

Methods

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

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

Strict Text

class GTextShowT arity f where #

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 #

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 # 

Methods

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

GTextShowT Zero V1 # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class GTextShowConT arity f where #

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 #

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

Instances

GTextShowConT arity UWord # 

Methods

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

GTextShowConT arity UInt # 

Methods

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

GTextShowConT arity UFloat # 

Methods

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

GTextShowConT arity UDouble # 

Methods

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

GTextShowConT arity UChar # 

Methods

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

GTextShowConT arity U1 # 

Methods

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

GTextShowConT One Par1 # 

Methods

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

TextShow1 f => GTextShowConT One (Rec1 f) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

data ShowFunsT arity a where #

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

Methods

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

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

Lazy Text

class GTextShowTL arity f where #

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 #

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 # 

Methods

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

GTextShowTL Zero V1 # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class GTextShowConTL arity f where #

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 #

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

Instances

GTextShowConTL arity UWord # 

Methods

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

GTextShowConTL arity UInt # 

Methods

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

GTextShowConTL arity UFloat # 

Methods

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

GTextShowConTL arity UDouble # 

Methods

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

GTextShowConTL arity UChar # 

Methods

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

GTextShowConTL arity U1 # 

Methods

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

GTextShowConTL One Par1 # 

Methods

gShowtlPrecCon :: ConType -> ShowFunsTL One a -> Int -> Par1 a -> Text #

TextShow1 f => GTextShowConTL One (Rec1 f) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

data ShowFunsTL arity a where #

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

Methods

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

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

Other internals

class IsNullary f where #

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

Minimal complete definition

isNullary

Methods

isNullary :: f a -> Bool #

Instances

IsNullary * U1 # 

Methods

isNullary :: f a -> Bool #

IsNullary * UChar # 

Methods

isNullary :: f a -> Bool #

IsNullary * UDouble # 

Methods

isNullary :: f a -> Bool #

IsNullary * UFloat # 

Methods

isNullary :: f a -> Bool #

IsNullary * UInt # 

Methods

isNullary :: f a -> Bool #

IsNullary * UWord # 

Methods

isNullary :: f a -> Bool #

IsNullary * (Rec1 f) # 

Methods

isNullary :: f a -> Bool #

IsNullary * (K1 i c) # 

Methods

isNullary :: f a -> Bool #

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

Methods

isNullary :: f a -> Bool #

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

Methods

isNullary :: f a -> Bool #

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

Methods

isNullary :: f a -> Bool #

IsNullary * Par1 # 

Methods

isNullary :: f a -> Bool #

data ConType #

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 # 

Methods

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

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

Data ConType # 

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

Associated Types

type Rep ConType :: * -> * #

Methods

from :: ConType -> Rep ConType x #

to :: Rep ConType x -> ConType #

Lift ConType # 

Methods

lift :: ConType -> Q Exp #

TextShow ConType # 
type Rep ConType # 
type Rep ConType = D1 (MetaData "ConType" "TextShow.Generic" "text-show-3.6-Hq5mzOnCQFVF1NIlf4bCVT" 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 #

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

Since: 3.2

Instances

GTextShowTL Zero V1 # 

Methods

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

GTextShowT Zero V1 # 

Methods

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

GTextShowB Zero V1 # 

Methods

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

data One #

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

Since: 3.2

Instances