| Copyright | (C) 2014-2015 Ryan Scott | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Ryan Scott | 
| Stability | Experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Text.Show.Text.Generic
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
- 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 ()
- class GShow f where
- 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 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  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 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
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
The GShow class
Minimal complete definition