text-show-3.2.1: 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

Methods

gShowbPrec :: Proxy arity -> (Int -> a -> Builder) -> ([a] -> Builder) -> 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 
GTextShow * Zero V1 Source 
(Constructor c, GTextShowCon k arity f, IsNullary * f) => GTextShow k arity (C1 c f) Source 
(GTextShow k arity f, GTextShow k arity g) => GTextShow k arity ((:+:) f g) Source 
GTextShow k arity f => GTextShow k arity (D1 d f) 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.

Methods

gShowbPrecCon :: Proxy arity -> ConType -> (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder Source

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

Instances

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

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 

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