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

Copyright(C) 2014-2015 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Text.Show.Text.Generic

Contents

Description

Generic versions of Show and Show1 class functions, as an alternative to Text.Show.Text.TH, which uses Template Haskell. Because there is no Generic2 class, Show2 cannot be implemented generically.

This implementation is based off of the Generics.Deriving.Show module from the generic-deriving library.

Since: 0.6

Synopsis

Generic show functions

Show 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 Text.Show.Text
import Text.Show.Generic

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

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

instance Show1 D where
    showbPrecWith = genericShowbPrecWith

Understanding a compiler error

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

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

instance Show Oops1 where
    showbPrec = genericShowbPrec

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

No instance for (GShow (Rep Oops1))

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 (GShow1 (Rep1 Oops2)), add a "deriving Generic1" clause.

genericShow :: (Generic a, GShow (Rep a)) => a -> Text Source

A Generic implementation of show.

Since: 0.6

genericShowLazy :: (Generic a, GShow (Rep a)) => a -> Text Source

A Generic implementation of showLazy.

Since: 0.6

genericShowPrec :: (Generic a, GShow (Rep a)) => Int -> a -> Text Source

A Generic implementation of showPrec.

Since: 0.6

genericShowPrecLazy :: (Generic a, GShow (Rep a)) => Int -> a -> Text Source

A Generic implementation of showPrecLazy.

Since: 0.6

genericShowList :: (Generic a, GShow (Rep a)) => [a] -> Text Source

A Generic implementation of showList.

Since: 0.6

genericShowListLazy :: (Generic a, GShow (Rep a)) => [a] -> Text Source

A Generic implementation of showListLazy.

Since: 0.6

genericShowb :: (Generic a, GShow (Rep a)) => a -> Builder Source

A Generic implementation of showb.

Since: 0.6

genericShowbPrec :: (Generic a, GShow (Rep a)) => Int -> a -> Builder Source

A Generic implementation of showbPrec.

Since: 0.6

genericShowbList :: (Generic a, GShow (Rep a)) => [a] -> Builder Source

A Generic implementation of showbList.

Since: 0.6

genericPrint :: (Generic a, GShow (Rep a)) => a -> IO () Source

A Generic implementation of print.

Since: 0.6

genericPrintLazy :: (Generic a, GShow (Rep a)) => a -> IO () Source

A Generic implementation of printLazy.

Since: 0.6

genericHPrint :: (Generic a, GShow (Rep a)) => Handle -> a -> IO () Source

A Generic implementation of hPrint.

Since: 0.6

genericHPrintLazy :: (Generic a, GShow (Rep a)) => Handle -> a -> IO () Source

A Generic implementation of hPrintLazy.

Since: 0.6

genericShowbPrecWith :: (Generic1 f, GShow1 (Rep1 f)) => (Int -> a -> Builder) -> Int -> f a -> Builder Source

A Generic1 implementation of showbPrecWith.

Since: 1

genericShowbPrec1 :: (Generic a, Generic1 f, GShow (Rep a), GShow1 (Rep1 f)) => Int -> f a -> Builder Source

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

Since: 1

The GShow and GShow1 classes

class GShow f where Source

Class of generic representation types (Rep) that can be converted to a Builder.

Since: 0.6

Minimal complete definition

gShowbPrec

Methods

gShowbPrec :: ConType -> Int -> f a -> Builder Source

This is used as the default generic implementation of showbPrec.

isNullary :: f a -> Bool Source

Whether a representation type has any constructors.

Instances

GShow * U1 
Show c => GShow * (K1 i c) 
(GShow * f, GShow * g) => GShow * ((:+:) f g) 
(GShow * f, GShow * g) => GShow * ((:*:) f g) 
GShow * f => GShow * (D1 d f) 
(Constructor c, GShow * f) => GShow * (C1 c f) 
(Selector s, GShow * f) => GShow * (S1 s f) 
Typeable ((k -> *) -> Constraint) (GShow k) 

class GShow1 f where Source

Class of generic representation types (Rep1) that can be converted to a Builder by lifting through a unary type constructor.

Since: 1

Minimal complete definition

gShowbPrecWith

Methods

gShowbPrecWith :: ConType -> (Int -> a -> Builder) -> Int -> f a -> Builder Source

This is used as the default generic implementation of showbPrecWith.

isNullary1 :: f a -> Bool Source

Whether a representation type has any constructors.

Instances

GShow1 U1 
GShow1 Par1 
Show1 f => GShow1 (Rec1 f) 
Show c => GShow1 (K1 i c) 
(GShow1 f, GShow1 g) => GShow1 ((:+:) f g) 
(GShow1 f, GShow1 g) => GShow1 ((:*:) f g) 
(Show1 f, GShow1 g) => GShow1 ((:.:) f g) 
GShow1 f => GShow1 (D1 d f) 
(Constructor c, GShow1 f) => GShow1 (C1 c f) 
(Selector s, GShow1 f) => GShow1 (S1 s f) 
Typeable ((* -> *) -> Constraint) GShow1 

data ConType Source

Whether a constructor is a record (Rec), a tuple (Tup), is prefix (Pref), or infix (Inf).

Since: 0.6

Constructors

Rec 
Tup 
Pref 
Inf String