text-show-3.3: Efficient conversion of values into Text

Copyright(C) 2014-2016 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 (GTextShow 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 (GTextShow One (Rep1 Oops1)), add a "deriving Generic1" clause.

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

A Generic implementation of showt.

Since: 2

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

A Generic implementation of showtl.

Since: 2

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

A Generic implementation of showPrect.

Since: 2

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

A Generic implementation of showtlPrec.

Since: 2

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

A Generic implementation of showtList.

Since: 2

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

A Generic implementation of showtlList.

Since: 2

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

A Generic implementation of showb.

Since: 2

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

A Generic implementation of showbPrec.

Since: 2

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

A Generic implementation of showbList.

Since: 2

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

A Generic implementation of printT.

Since: 2

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

A Generic implementation of printTL.

Since: 2

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

A Generic implementation of hPrintT.

Since: 2

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

A Generic implementation of hPrintTL.

Since: 2

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

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

Since: 2

GTextShow and friends

class GTextShow 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. GTextShow Zero indicates TextShow behavior, and GTextShow One indicates TextShow1 behavior.

Since: 3.2

Minimal complete definition

gShowbPrec

Methods

gShowbPrec :: ShowFuns 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

GTextShow One V1 Source # 

Methods

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

GTextShow Zero V1 Source # 

Methods

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

(Constructor Meta c, GTextShowCon arity f, IsNullary * f) => GTextShow arity (C1 c f) Source # 

Methods

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

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

Methods

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

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

Methods

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

class GTextShowCon 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. GTextShow Zero indicates TextShow behavior, and GTextShow One indicates TextShow1 behavior.

Minimal complete definition

gShowbPrecCon

Methods

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

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

Instances

GTextShowCon arity UWord Source # 

Methods

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

GTextShowCon arity UInt Source # 

Methods

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

GTextShowCon arity UFloat Source # 

Methods

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

GTextShowCon arity UDouble Source # 

Methods

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

GTextShowCon arity UChar Source # 

Methods

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

GTextShowCon arity U1 Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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 #

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.3-bIZFsMsDGoDCqejfaz4KO" 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 ShowFuns arity a where Source #

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

Since: 3.3

Constructors

NoShowFuns :: ShowFuns Zero a 
Show1Funs :: (Int -> a -> Builder) -> ([a] -> Builder) -> ShowFuns One a 

Instances

Contravariant (ShowFuns arity) Source # 

Methods

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

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

data Zero Source #

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

Since: 3.2

Instances

data One Source #

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

Since: 3.2