module Text.Show.Text.GHC.Generics (
showbU1
, showbPar1PrecWith
, showbRec1Prec
, showbRec1PrecWith
, showbK1PrecWith
, showbM1Prec
, showbM1PrecWith
, showbSumTypePrec
, showbSumTypePrecWith
, showbProductTypePrec
, showbProductTypePrecWith
, showbCompFunctorsPrec
, showbCompFunctorsPrecWith
, showbFixityPrec
, showbAssociativity
, showbArityPrec
) where
import Data.Text.Lazy.Builder (Builder)
import Generics.Deriving.Base (U1(..), Par1, Rec1(..), K1(..),
M1(..), (:+:)(..), (:*:)(..), (:.:)(..),
Fixity, Associativity, Arity)
import Prelude hiding (Show)
import Text.Show.Text.Classes (Show(showb, showbPrec), Show1(..), Show2(..))
import Text.Show.Text.Data.Integral ()
import Text.Show.Text.TH.Internal (deriveShow, deriveShow1, mkShowbPrec,
mkShowbPrecWith, mkShowbPrecWith2)
showbU1 :: U1 p -> Builder
showbU1 = showb
showbPar1PrecWith :: (Int -> p -> Builder) -> Int -> Par1 p -> Builder
showbPar1PrecWith = showbPrecWith
showbRec1Prec :: Show (f p) => Int -> Rec1 f p -> Builder
showbRec1Prec = showbPrec
showbRec1PrecWith :: Show1 f => (Int -> p -> Builder) -> Int -> Rec1 f p -> Builder
showbRec1PrecWith = showbPrecWith
showbK1PrecWith :: (Int -> c -> Builder) -> Int -> K1 i c p -> Builder
showbK1PrecWith sp = showbPrecWith2 sp undefined
showbM1Prec :: Show (f p) => Int -> M1 i c f p -> Builder
showbM1Prec = showbPrec
showbM1PrecWith :: Show1 f => (Int -> p -> Builder) -> Int -> M1 i c f p -> Builder
showbM1PrecWith = showbPrecWith
showbSumTypePrec :: (Show (f p), Show (g p)) => Int -> (f :+: g) p -> Builder
showbSumTypePrec = showbPrec
showbSumTypePrecWith :: (Show1 f, Show1 g) => (Int -> p -> Builder) -> Int -> (f :+: g) p -> Builder
showbSumTypePrecWith = showbPrecWith
showbProductTypePrec :: (Show (f p), Show (g p)) => Int -> (f :*: g) p -> Builder
showbProductTypePrec = showbPrec
showbProductTypePrecWith :: (Show1 f, Show1 g) => (Int -> p -> Builder) -> Int -> (f :*: g) p -> Builder
showbProductTypePrecWith = showbPrecWith
showbCompFunctorsPrec :: Show (f (g p)) => Int -> (f :.: g) p -> Builder
showbCompFunctorsPrec = showbPrec
showbCompFunctorsPrecWith :: (Show1 f, Show1 g) => (Int -> p -> Builder) -> Int -> (f :.: g) p -> Builder
showbCompFunctorsPrecWith = showbPrecWith
showbFixityPrec :: Int -> Fixity -> Builder
showbFixityPrec = showbPrec
showbAssociativity :: Associativity -> Builder
showbAssociativity = showb
showbArityPrec :: Int -> Arity -> Builder
showbArityPrec = showbPrec
instance Show (U1 p) where
showbPrec = showbPrecWith undefined
$(deriveShow1 ''U1)
$(deriveShow ''Par1)
$(deriveShow1 ''Par1)
instance Show (f p) => Show (Rec1 f p) where
showbPrec = $(mkShowbPrec ''Rec1)
$(deriveShow1 ''Rec1)
instance Show c => Show (K1 i c p) where
showbPrec = showbPrecWith undefined
instance Show c => Show1 (K1 i c) where
showbPrecWith = showbPrecWith2 showbPrec
instance Show2 (K1 i) where
showbPrecWith2 = $(mkShowbPrecWith2 ''K1)
instance Show (f p) => Show (M1 i c f p) where
showbPrec = $(mkShowbPrec ''M1)
instance Show1 f => Show1 (M1 i c f) where
showbPrecWith = $(mkShowbPrecWith ''M1)
instance (Show (f p), Show (g p)) => Show ((f :+: g) p) where
showbPrec = $(mkShowbPrec ''(:+:))
$(deriveShow1 ''(:+:))
instance (Show (f p), Show (g p)) => Show ((f :*: g) p) where
showbPrec = $(mkShowbPrec ''(:*:))
$(deriveShow1 ''(:*:))
instance Show (f (g p)) => Show ((f :.: g) p) where
showbPrec = $(mkShowbPrec ''(:.:))
$(deriveShow1 ''(:.:))
$(deriveShow ''Fixity)
$(deriveShow ''Associativity)
$(deriveShow ''Arity)