| Copyright | (C) 2014-2016 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
TextShow.Generic
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
- genericShowt :: (Generic a, GTextShow Zero (Rep a)) => a -> Text
- genericShowtl :: (Generic a, GTextShow Zero (Rep a)) => a -> Text
- genericShowtPrec :: (Generic a, GTextShow Zero (Rep a)) => Int -> a -> Text
- genericShowtlPrec :: (Generic a, GTextShow Zero (Rep a)) => Int -> a -> Text
- genericShowtList :: (Generic a, GTextShow Zero (Rep a)) => [a] -> Text
- genericShowtlList :: (Generic a, GTextShow Zero (Rep a)) => [a] -> Text
- genericShowb :: (Generic a, GTextShow Zero (Rep a)) => a -> Builder
- genericShowbPrec :: (Generic a, GTextShow Zero (Rep a)) => Int -> a -> Builder
- genericShowbList :: (Generic a, GTextShow Zero (Rep a)) => [a] -> Builder
- genericPrintT :: (Generic a, GTextShow Zero (Rep a)) => a -> IO ()
- genericPrintTL :: (Generic a, GTextShow Zero (Rep a)) => a -> IO ()
- genericHPrintT :: (Generic a, GTextShow Zero (Rep a)) => Handle -> a -> IO ()
- genericHPrintTL :: (Generic a, GTextShow Zero (Rep a)) => Handle -> a -> IO ()
- genericLiftShowbPrec :: (Generic1 f, GTextShow One (Rep1 f)) => (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
- genericShowbPrec1 :: (Generic a, Generic1 f, GTextShow Zero (Rep a), GTextShow One (Rep1 f)) => Int -> f a -> Builder
- class GTextShow arity f where
- class GTextShowCon arity f where
- class IsNullary f where
- data ConType
- data ShowFuns arity a where
- data Zero
- data One
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 clause to your data type, at
compile-time, you might get an error message that begins roughly as follows:Generic
No instance for (GTextShowZero(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 "GTextShow
One (Rep1 Oops1))deriving " clause.Generic1
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
genericShowtlList :: (Generic a, GTextShow Zero (Rep a)) => [a] -> Text Source #
A Generic implementation of showtlList.
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. indicates GTextShow ZeroTextShow behavior, and
indicates GTextShow OneTextShow1 behavior.
Since: 3.2
Minimal complete definition
Methods
gShowbPrec :: ShowFuns arity a -> 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).
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. indicates GTextShow ZeroTextShow behavior, and
indicates GTextShow OneTextShow1 behavior.
Minimal complete definition
Instances
| GTextShowCon arity UWord Source # | |
| GTextShowCon arity UInt Source # | |
| GTextShowCon arity UFloat Source # | |
| GTextShowCon arity UDouble Source # | |
| GTextShowCon arity UChar Source # | |
| GTextShowCon arity U1 Source # | |
| GTextShowCon One Par1 Source # | |
| TextShow1 f => GTextShowCon One (Rec1 f) Source # | |
| (GTextShowCon arity f, GTextShowCon arity g) => GTextShowCon arity ((:*:) f g) Source # | |
| (Selector Meta s, GTextShowCon arity f) => GTextShowCon arity (S1 s f) Source # | |
| TextShow c => GTextShowCon arity (K1 i c) Source # | |
| (TextShow1 f, GTextShowCon One g) => GTextShowCon One ((:.:) f g) Source # | |
class IsNullary f where Source #
Class of generic representation types that represent a constructor with zero or more fields.
Minimal complete definition
Instances
| IsNullary * U1 Source # | |
| IsNullary * UChar Source # | |
| IsNullary * UDouble Source # | |
| IsNullary * UFloat Source # | |
| IsNullary * UInt Source # | |
| IsNullary * UWord Source # | |
| IsNullary * (Rec1 f) Source # | |
| IsNullary * (K1 i c) Source # | |
| IsNullary * ((:*:) f g) Source # | |
| IsNullary * ((:.:) f g) Source # | |
| IsNullary * f => IsNullary * (S1 s f) Source # | |
| IsNullary * Par1 Source # | |
data ShowFuns arity a where Source #
A ShowFuns value either stores nothing (for TextShow) or it stores
the two function arguments that show occurrences of the type parameter (for
TextShow1).
Since: 3.3
Constructors
| NoShowFuns :: ShowFuns Zero a | |
| Show1Funs :: (Int -> a -> Builder) -> ([a] -> Builder) -> ShowFuns One a |
Instances
| Contravariant (ShowFuns arity) Source # | |
A type-level indicator that TextShow is being derived generically.
Since: 3.2