module Text.Show.Text.Data.Typeable (showbTyCon, showbTypeRepPrec) where
import Data.Text.Lazy.Builder (Builder, fromString)
import Data.Typeable (TypeRep, typeRepArgs, typeRepTyCon)
#if MIN_VERSION_base(4,4,0)
import Data.Typeable.Internal (TyCon(..), funTc, listTc)
#else
import Data.Typeable (TyCon, mkTyCon, tyConString, typeOf)
#endif
import Prelude hiding (Show)
import Text.Show.Text.Classes (Show(showb, showbPrec), showbParen, showbSpace)
import Text.Show.Text.Data.List ()
import Text.Show.Text.Data.Typeable.Utils (showbArgs, showbTuple)
import Text.Show.Text.Utils ((<>), isTupleString, s)
#include "inline.h"
showbTypeRepPrec :: Int -> TypeRep -> Builder
showbTypeRepPrec p tyrep =
case tys of
[] -> showbTyCon tycon
[x] | tycon == listTc -> s '[' <> showb x <> s ']'
[a,r] | tycon == funTc -> showbParen (p > 8) $
showbPrec 9 a
<> " -> "
<> showbPrec 8 r
xs | isTupleTyCon tycon -> showbTuple xs
| otherwise -> showbParen (p > 9) $
showbPrec p tycon
<> showbSpace
<> showbArgs showbSpace tys
where
tycon = typeRepTyCon tyrep
tys = typeRepArgs tyrep
#if !(MIN_VERSION_base(4,4,0))
listTc :: TyCon
listTc = typeRepTyCon $ typeOf [()]
funTc :: TyCon
funTc = mkTyCon "->"
#endif
isTupleTyCon :: TyCon -> Bool
isTupleTyCon = isTupleString . tyConString
showbTyCon :: TyCon -> Builder
showbTyCon = fromString . tyConString
#if MIN_VERSION_base(4,4,0)
tyConString :: TyCon -> String
tyConString = tyConName
#endif
instance Show TypeRep where
showbPrec = showbTypeRepPrec
INLINE_INST_FUN(showbPrec)
instance Show TyCon where
showb = showbTyCon
INLINE_INST_FUN(showb)