module Text.Show.Text.Data.Data (
showbConstr
, showbConstrRepPrec
, showbDataRepPrec
, showbDataTypePrec
, showbFixity
) where
import Data.Data (Constr, ConstrRep, DataRep, DataType, Fixity, showConstr)
import Data.Text.Lazy.Builder (Builder, fromString)
import Prelude hiding (Show)
import Text.Show.Text.Classes (Show(showb, showbPrec))
import Text.Show.Text.Data.List ()
import Text.Show.Text.Data.Ratio ()
import Text.Show.Text.TH.Internal (deriveShow, deriveShowPragmas,
defaultInlineShowbPrec, defaultInlineShowb)
#include "inline.h"
showbDataTypePrec :: Int -> DataType -> Builder
showbDataTypePrec = showbPrec
showbDataRepPrec :: Int -> DataRep -> Builder
showbDataRepPrec = showbPrec
showbConstr :: Constr -> Builder
showbConstr = fromString . showConstr
showbFixity :: Fixity -> Builder
showbFixity = showb
showbConstrRepPrec :: Int -> ConstrRep -> Builder
showbConstrRepPrec = showbPrec
$(deriveShowPragmas defaultInlineShowbPrec ''DataType)
$(deriveShow ''DataRep)
$(deriveShow ''ConstrRep)
$(deriveShowPragmas defaultInlineShowb ''Fixity)
instance Show Constr where
showb = showbConstr
INLINE_INST_FUN(showb)