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 |
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 based off of the Generics.Deriving.Show
module from the
generic-deriving
library.
Since: 2
- genericShowt :: (Generic a, GTextShow (Rep a)) => a -> Text
- genericShowtl :: (Generic a, GTextShow (Rep a)) => a -> Text
- genericShowtPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> Text
- genericShowtlPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> Text
- genericShowtList :: (Generic a, GTextShow (Rep a)) => [a] -> Text
- genericShowtlList :: (Generic a, GTextShow (Rep a)) => [a] -> Text
- genericShowb :: (Generic a, GTextShow (Rep a)) => a -> Builder
- genericShowbPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> Builder
- genericShowbList :: (Generic a, GTextShow (Rep a)) => [a] -> Builder
- genericPrintT :: (Generic a, GTextShow (Rep a)) => a -> IO ()
- genericPrintTL :: (Generic a, GTextShow (Rep a)) => a -> IO ()
- genericHPrintT :: (Generic a, GTextShow (Rep a)) => Handle -> a -> IO ()
- genericHPrintTL :: (Generic a, GTextShow (Rep a)) => Handle -> a -> IO ()
- genericShowbPrecWith :: (Generic1 f, GTextShow1 (Rep1 f)) => (Int -> a -> Builder) -> Int -> f a -> Builder
- genericShowbPrec1 :: (Generic a, Generic1 f, GTextShow (Rep a), GTextShow1 (Rep1 f)) => Int -> f a -> Builder
- class GTextShow f where
- class GTextShow1 f where
- gShowbPrecWith :: ConType -> (Int -> a -> Builder) -> Int -> f a -> Builder
- isNullary1 :: f a -> Bool
- data ConType
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 showbPrecWith =genericShowbPrecWith
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
clause to your data type, at
compile-time, you will get an error message that begins roughly as follows:Generic
No instance for (GTextShow
(Rep Oops))
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 "GTextShow1
(Rep1 Oops1))deriving
" clause.Generic1
genericShowt :: (Generic a, GTextShow (Rep a)) => a -> Text Source
A Generic
implementation of showt
.
Since: 2
genericShowtl :: (Generic a, GTextShow (Rep a)) => a -> Text Source
A Generic
implementation of showtl
.
Since: 2
genericShowtPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> Text Source
A Generic
implementation of showPrect
.
Since: 2
genericShowtlPrec :: (Generic a, GTextShow (Rep a)) => Int -> a -> Text Source
A Generic
implementation of showtlPrec
.
Since: 2
genericShowtList :: (Generic a, GTextShow (Rep a)) => [a] -> Text Source
A Generic
implementation of showtList
.
Since: 2
genericShowtlList :: (Generic a, GTextShow (Rep a)) => [a] -> Text Source
A Generic
implementation of showtlList
.
Since: 2
genericShowb :: (Generic a, GTextShow (Rep a)) => a -> Builder Source
A Generic
implementation of showb
.
Since: 2
genericShowbList :: (Generic a, GTextShow (Rep a)) => [a] -> Builder Source
A Generic
implementation of showbList
.
Since: 2
genericPrintT :: (Generic a, GTextShow (Rep a)) => a -> IO () Source
A Generic
implementation of printT
.
Since: 2
genericPrintTL :: (Generic a, GTextShow (Rep a)) => a -> IO () Source
A Generic
implementation of printTL
.
Since: 2
genericHPrintT :: (Generic a, GTextShow (Rep a)) => Handle -> a -> IO () Source
A Generic
implementation of hPrintT
.
Since: 2
genericHPrintTL :: (Generic a, GTextShow (Rep a)) => Handle -> a -> IO () Source
A Generic
implementation of hPrintTL
.
Since: 2
genericShowbPrecWith :: (Generic1 f, GTextShow1 (Rep1 f)) => (Int -> a -> Builder) -> Int -> f a -> Builder Source
A Generic1
implementation of showbPrecWith
.
Since: 2
genericShowbPrec1 :: (Generic a, Generic1 f, GTextShow (Rep a), GTextShow1 (Rep1 f)) => Int -> f a -> Builder Source
A 'Generic'/'Generic1' implementation of showbPrec1
.
Since: 2
The GTextShow
and GTextShow1
classes
class GTextShow f where Source
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.
GTextShow * U1 | |
TextShow c => GTextShow * (K1 i c) | |
(GTextShow * f, GTextShow * g) => GTextShow * ((:+:) f g) | |
(GTextShow * f, GTextShow * g) => GTextShow * ((:*:) f g) | |
GTextShow * f => GTextShow * (D1 d f) | |
(Constructor c, GTextShow * f) => GTextShow * (C1 c f) | |
(Selector s, GTextShow * f) => GTextShow * (S1 s f) | |
Typeable ((k -> *) -> Constraint) (GTextShow k) |
class GTextShow1 f where Source
Class of generic representation types (Rep1
) that can be converted to
a Builder
by lifting through a unary type constructor.
Since: 2
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.
GTextShow1 U1 | |
GTextShow1 Par1 | |
TextShow1 f => GTextShow1 (Rec1 f) | |
TextShow c => GTextShow1 (K1 i c) | |
(GTextShow1 f, GTextShow1 g) => GTextShow1 ((:+:) f g) | |
(GTextShow1 f, GTextShow1 g) => GTextShow1 ((:*:) f g) | |
(TextShow1 f, GTextShow1 g) => GTextShow1 ((:.:) f g) | |
GTextShow1 f => GTextShow1 (D1 d f) | |
(Constructor c, GTextShow1 f) => GTextShow1 (C1 c f) | |
(Selector s, GTextShow1 f) => GTextShow1 (S1 s f) | |
Typeable ((* -> *) -> Constraint) GTextShow1 |