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

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

Text.Show.Text.Generic

Contents

Description

Generic versions of Show class functions, as an alternative to Text.Show.Text.TH, which uses Template Haskell. This module is only available if the compiler supports generics (on GHC, 7.2 or above).

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

data D a = Nullary
         | Unary Int
         | Product String Char a
         | Record { testOne   :: Double
                  , testTwo   :: Bool
                  , testThree :: D a
                  }

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

D now has a Show instance analogous to what would be generated by a deriving Show clause.

Understanding a compiler error

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

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

instance Show Oops 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 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.

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

The GShow class

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

isNullary :: f a -> Bool Source

Instances

GShow U1 
Show c => GShow (K1 i c) 
(GShow a, GShow b) => GShow ((:+:) a b) 
(GShow a, GShow b) => GShow ((:*:) a b) 
Typeable ((* -> *) -> Constraint) GShow 
GShow a => GShow (M1 D d a) 
(Constructor c, GShow a) => GShow (M1 C c a) 
(Selector s, GShow a) => GShow (M1 S s a) 

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 Builder