module TextShow.GHC.Generics (
showbU1
, liftShowbPar1Prec
, showbRec1Prec
, liftShowbRec1Prec
, liftShowbK1Prec
, showbM1Prec
, liftShowbM1Prec
, showbSumTypePrec
, liftShowbSumTypePrec
, showbProductTypePrec
, liftShowbProductTypePrec
, showbCompFunctorsPrec
, liftShowbCompFunctorsPrec
, showbFixityPrec
, showbAssociativity
#if MIN_VERSION_base(4,9,0)
, showbSourceUnpackedness
, showbSourceStrictness
, showbDecidedStrictness
#else
, showbArityPrec
#endif
, showbUCharPrec
, showbUDoublePrec
, showbUFloatPrec
, showbUIntPrec
, showbUWordPrec
) where
import Data.Text.Lazy.Builder (Builder)
import Generics.Deriving.Base
import TextShow.Classes (TextShow(..), TextShow1(..), TextShow2(..))
import TextShow.Data.Char ()
import TextShow.Data.Floating ()
import TextShow.Data.Integral ()
import TextShow.TH.Internal (deriveTextShow, deriveTextShow1, makeShowbPrec,
makeLiftShowbPrec, makeLiftShowbPrec2)
#if !(MIN_VERSION_template_haskell(2,7,0))
import Data.Monoid.Compat ((<>))
import Data.Text.Lazy.Builder (fromString, singleton)
import GHC.Exts (Char(C#), Double(D#), Float(F#), Int(I#), Word(W#))
import GHC.Show (appPrec)
import TextShow.Classes (showbParen)
#endif
showbU1 :: U1 p -> Builder
showbU1 = showb
liftShowbPar1Prec :: (Int -> p -> Builder) -> Int -> Par1 p -> Builder
liftShowbPar1Prec sp = liftShowbPrec sp undefined
showbRec1Prec :: TextShow (f p) => Int -> Rec1 f p -> Builder
showbRec1Prec = showbPrec
liftShowbRec1Prec :: TextShow1 f => (Int -> p -> Builder) -> ([p] -> Builder)
-> Int -> Rec1 f p -> Builder
liftShowbRec1Prec = liftShowbPrec
liftShowbK1Prec :: (Int -> c -> Builder) -> Int -> K1 i c p -> Builder
liftShowbK1Prec sp = liftShowbPrec2 sp undefined undefined undefined
showbM1Prec :: TextShow (f p) => Int -> M1 i c f p -> Builder
showbM1Prec = showbPrec
liftShowbM1Prec :: TextShow1 f => (Int -> p -> Builder) -> ([p] -> Builder)
-> Int -> M1 i c f p -> Builder
liftShowbM1Prec = liftShowbPrec
showbSumTypePrec :: (TextShow (f p), TextShow (g p)) => Int -> (f :+: g) p -> Builder
showbSumTypePrec = showbPrec
liftShowbSumTypePrec :: (TextShow1 f, TextShow1 g)
=> (Int -> p -> Builder) -> ([p] -> Builder)
-> Int -> (f :+: g) p -> Builder
liftShowbSumTypePrec = liftShowbPrec
showbProductTypePrec :: (TextShow (f p), TextShow (g p)) => Int -> (f :*: g) p -> Builder
showbProductTypePrec = showbPrec
liftShowbProductTypePrec :: (TextShow1 f, TextShow1 g)
=> (Int -> p -> Builder) -> ([p] -> Builder)
-> Int -> (f :*: g) p -> Builder
liftShowbProductTypePrec = liftShowbPrec
showbCompFunctorsPrec :: TextShow (f (g p)) => Int -> (f :.: g) p -> Builder
showbCompFunctorsPrec = showbPrec
liftShowbCompFunctorsPrec :: (TextShow1 f, TextShow1 g)
=> (Int -> p -> Builder) -> ([p] -> Builder)
-> Int -> (f :.: g) p -> Builder
liftShowbCompFunctorsPrec = liftShowbPrec
showbFixityPrec :: Int -> Fixity -> Builder
showbFixityPrec = showbPrec
showbAssociativity :: Associativity -> Builder
showbAssociativity = showb
#if MIN_VERSION_base(4,9,0)
showbSourceUnpackedness :: SourceUnpackedness -> Builder
showbSourceUnpackedness = showb
showbSourceStrictness :: SourceStrictness -> Builder
showbSourceStrictness = showb
showbDecidedStrictness :: DecidedStrictness -> Builder
showbDecidedStrictness = showb
#else
showbArityPrec :: Int -> Arity -> Builder
showbArityPrec = showbPrec
#endif
showbUCharPrec :: Int -> UChar p -> Builder
showbUCharPrec = showbPrec
showbUDoublePrec :: Int -> UDouble p -> Builder
showbUDoublePrec = showbPrec
showbUFloatPrec :: Int -> UFloat p -> Builder
showbUFloatPrec = showbPrec
showbUIntPrec :: Int -> UInt p -> Builder
showbUIntPrec = showbPrec
showbUWordPrec :: Int -> UWord p -> Builder
showbUWordPrec = showbPrec
instance TextShow (U1 p) where
showbPrec = liftShowbPrec undefined undefined
$(deriveTextShow1 ''U1)
$(deriveTextShow ''Par1)
$(deriveTextShow1 ''Par1)
instance TextShow (f p) => TextShow (Rec1 f p) where
showbPrec = $(makeShowbPrec ''Rec1)
$(deriveTextShow1 ''Rec1)
instance TextShow c => TextShow (K1 i c p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow c => TextShow1 (K1 i c) where
liftShowbPrec = liftShowbPrec2 showbPrec showbList
instance TextShow2 (K1 i) where
liftShowbPrec2 = $(makeLiftShowbPrec2 ''K1)
instance TextShow (f p) => TextShow (M1 i c f p) where
showbPrec = $(makeShowbPrec ''M1)
instance TextShow1 f => TextShow1 (M1 i c f) where
liftShowbPrec = $(makeLiftShowbPrec ''M1)
instance (TextShow (f p), TextShow (g p)) => TextShow ((f :+: g) p) where
showbPrec = $(makeShowbPrec ''(:+:))
$(deriveTextShow1 ''(:+:))
instance (TextShow (f p), TextShow (g p)) => TextShow ((f :*: g) p) where
showbPrec = $(makeShowbPrec ''(:*:))
$(deriveTextShow1 ''(:*:))
instance TextShow (f (g p)) => TextShow ((f :.: g) p) where
showbPrec = $(makeShowbPrec ''(:.:))
$(deriveTextShow1 ''(:.:))
#if MIN_VERSION_template_haskell(2,7,0)
instance TextShow (UChar p) where
showbPrec = $(makeShowbPrec 'UChar)
$(deriveTextShow1 'UChar)
instance TextShow (UDouble p) where
showbPrec = $(makeShowbPrec 'UDouble)
$(deriveTextShow1 'UDouble)
instance TextShow (UFloat p) where
showbPrec = $(makeShowbPrec 'UFloat)
$(deriveTextShow1 'UFloat)
instance TextShow (UInt p) where
showbPrec = $(makeShowbPrec 'UInt)
$(deriveTextShow1 'UInt)
instance TextShow (UWord p) where
showbPrec = $(makeShowbPrec 'UWord)
$(deriveTextShow1 'UWord)
#else
instance TextShow (UChar p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow1 UChar where
liftShowbPrec _ _ p (UChar c) = showbParen (p > appPrec) $
fromString "UChar " <> singleton '{'
<> fromString "uChar# = " <> showb (C# c)
<> singleton '}'
instance TextShow (UDouble p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow1 UDouble where
liftShowbPrec _ _ p (UDouble d) = showbParen (p > appPrec) $
fromString "UDouble " <> singleton '{'
<> fromString "uDouble# = " <> showb (D# d)
<> singleton '}'
instance TextShow (UFloat p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow1 UFloat where
liftShowbPrec _ _ p (UFloat f) = showbParen (p > appPrec) $
fromString "UFloat " <> singleton '{'
<> fromString "uFloat# = " <> showb (F# f)
<> singleton '}'
instance TextShow (UInt p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow1 UInt where
liftShowbPrec _ _ p (UInt i) = showbParen (p > appPrec) $
fromString "UInt " <> singleton '{'
<> fromString "uInt# = " <> showb (I# i)
<> singleton '}'
instance TextShow (UWord p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow1 UWord where
liftShowbPrec _ _ p (UWord w) = showbParen (p > appPrec) $
fromString "UWord " <> singleton '{'
<> fromString "uWord# = " <> showb (W# w)
<> singleton '}'
#endif
$(deriveTextShow ''Fixity)
$(deriveTextShow ''Associativity)
#if MIN_VERSION_base(4,9,0)
$(deriveTextShow ''SourceUnpackedness)
$(deriveTextShow ''SourceStrictness)
$(deriveTextShow ''DecidedStrictness)
#else
$(deriveTextShow ''Arity)
#endif