| Copyright | (C) 2014-2015 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Show.Text.Generic
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
- genericShow :: (Generic a, GShow (Rep a)) => a -> Text
- genericShowLazy :: (Generic a, GShow (Rep a)) => a -> Text
- genericShowPrec :: (Generic a, GShow (Rep a)) => Int -> a -> Text
- genericShowPrecLazy :: (Generic a, GShow (Rep a)) => Int -> a -> Text
- genericShowList :: (Generic a, GShow (Rep a)) => [a] -> Text
- genericShowListLazy :: (Generic a, GShow (Rep a)) => [a] -> Text
- genericShowb :: (Generic a, GShow (Rep a)) => a -> Builder
- genericShowbPrec :: (Generic a, GShow (Rep a)) => Int -> a -> Builder
- genericShowbList :: (Generic a, GShow (Rep a)) => [a] -> Builder
- genericPrint :: (Generic a, GShow (Rep a)) => a -> IO ()
- genericPrintLazy :: (Generic a, GShow (Rep a)) => a -> IO ()
- genericHPrint :: (Generic a, GShow (Rep a)) => Handle -> a -> IO ()
- genericHPrintLazy :: (Generic a, GShow (Rep a)) => Handle -> a -> IO ()
- genericShowbPrecWith :: (Generic1 f, GShow1 (Rep1 f)) => (Int -> a -> Builder) -> Int -> f a -> Builder
- genericShowbPrec1 :: (Generic a, Generic1 f, GShow (Rep a), GShow1 (Rep1 f)) => Int -> f a -> Builder
- class GShow f where
- class GShow1 f where
- gShowbPrecWith :: ConType -> (Int -> a -> Builder) -> Int -> f a -> Builder
- isNullary1 :: f a -> Bool
- data ConType
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 clause to your data type, at
compile-time, you will get an error message that begins roughly as follows:Generic
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 " clause.Generic
Similarly, if the compiler complains about not having an instance for (, add a "GShow1
(Rep1 Oops2))deriving " clause.Generic1
genericShowPrecLazy :: (Generic a, GShow (Rep a)) => Int -> a -> Text Source
A Generic implementation of showPrecLazy.
Since: 0.6
genericShowListLazy :: (Generic a, GShow (Rep a)) => [a] -> Text Source
A Generic implementation of showListLazy.
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
Minimal complete definition
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
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
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 |