#if __GLASGOW_HASKELL__ >= 706
#endif
module TextShow.Data.Typeable (
showbTyCon
, showbTypeRepPrec
#if MIN_VERSION_base(4,9,0)
, showbTrName
, showbModule
#endif
) where
import Data.Monoid.Compat ((<>))
import Data.Text.Lazy.Builder (Builder, fromString, singleton)
import Data.Typeable (TypeRep, typeRepArgs, typeRepTyCon)
#if MIN_VERSION_base(4,4,0)
import Data.Typeable.Internal (tyConName)
# if MIN_VERSION_base(4,8,0)
import Data.Typeable.Internal (typeRepKinds)
# endif
# if MIN_VERSION_base(4,9,0)
import Data.Typeable.Internal (Proxy(..), Typeable, TypeRep(TypeRep), typeRep)
import GHC.Exts (RuntimeRep(..), TYPE)
# elif MIN_VERSION_base(4,4,0)
import Data.Typeable.Internal (funTc, listTc)
# endif
#else
import Data.Typeable (mkTyCon, tyConString, typeOf)
#endif
#if MIN_VERSION_base(4,9,0)
import GHC.Exts (Char(..))
import GHC.Prim (Addr#, (+#), eqChar#, indexCharOffAddr#)
import GHC.Types (TyCon(..), TrName(..), Module(..), isTrue#)
#elif MIN_VERSION_base(4,4,0)
import Data.Typeable.Internal (TyCon)
#else
import Data.Typeable (TyCon)
#endif
import TextShow.Classes (TextShow(..), showbParen, showbSpace)
import TextShow.Data.List ()
import TextShow.Data.Typeable.Utils (showbArgs, showbTuple)
import TextShow.Utils (isTupleString)
#include "inline.h"
showbTypeRepPrec :: Int -> TypeRep -> Builder
showbTypeRepPrec p tyrep =
case tys of
[] -> showbTyCon tycon
#if MIN_VERSION_base(4,9,0)
[x@(TypeRep _ argCon _ _)]
#else
[x]
#endif
| tycon == tcList -> singleton '[' <> showb x <> singleton ']'
#if MIN_VERSION_base(4,9,0)
| tycon == tcTYPE && argCon == tc'Lifted -> singleton '*'
| tycon == tcTYPE && argCon == tc'Unlifted -> singleton '#'
#endif
[a,r] | tycon == tcFun -> showbParen (p > 8) $
showbPrec 9 a
<> " -> "
<> showbPrec 8 r
xs | isTupleTyCon tycon -> showbTuple xs
| otherwise -> showbParen (p > 9) $
showbPrec p tycon
<> showbSpace
<> showbArgs showbSpace
#if MIN_VERSION_base(4,8,0)
(kinds ++ tys)
#else
tys
#endif
where
tycon = typeRepTyCon tyrep
tys = typeRepArgs tyrep
#if MIN_VERSION_base(4,8,0)
kinds = typeRepKinds tyrep
#endif
#if MIN_VERSION_base(4,9,0)
tyConOf :: Typeable a => Proxy a -> TyCon
tyConOf = typeRepTyCon . typeRep
tcFun :: TyCon
tcFun = tyConOf (Proxy :: Proxy (Int -> Int))
tcList :: TyCon
tcList = tyConOf (Proxy :: Proxy [])
tcTYPE :: TyCon
tcTYPE = tyConOf (Proxy :: Proxy TYPE)
tc'Lifted :: TyCon
tc'Lifted = tyConOf (Proxy :: Proxy 'PtrRepLifted)
tc'Unlifted :: TyCon
tc'Unlifted = tyConOf (Proxy :: Proxy 'PtrRepUnlifted)
#elif MIN_VERSION_base(4,4,0)
tcList :: TyCon
tcList = listTc
tcFun :: TyCon
tcFun = funTc
#else
tcList :: TyCon
tcList = typeRepTyCon $ typeOf [()]
tcFun :: TyCon
tcFun = mkTyCon "->"
#endif
isTupleTyCon :: TyCon -> Bool
isTupleTyCon = isTupleString . tyConString
showbTyCon :: TyCon -> Builder
#if MIN_VERSION_base(4,9,0)
showbTyCon (TyCon _ _ _ tc_name) = showb tc_name
#else
showbTyCon = fromString . tyConString
#endif
#if MIN_VERSION_base(4,9,0)
showbTrName :: TrName -> Builder
showbTrName (TrNameS s) = unpackCStringToBuilder# s
showbTrName (TrNameD s) = fromString s
showbModule :: Module -> Builder
showbModule (Module p m) = showb p <> singleton ':' <> showb m
unpackCStringToBuilder# :: Addr# -> Builder
unpackCStringToBuilder# addr
= unpack 0#
where
unpack nh
| isTrue# (ch `eqChar#` '\0'#) = mempty
| True = singleton (C# ch) <> unpack (nh +# 1#)
where
!ch = indexCharOffAddr# addr nh
#endif
#if MIN_VERSION_base(4,4,0)
tyConString :: TyCon -> String
tyConString = tyConName
#endif
instance TextShow TypeRep where
showbPrec = showbTypeRepPrec
INLINE_INST_FUN(showbPrec)
instance TextShow TyCon where
showb = showbTyCon
INLINE_INST_FUN(showb)
#if MIN_VERSION_base(4,9,0)
instance TextShow TrName where
showb = showbTrName
INLINE_INST_FUN(showb)
instance TextShow Module where
showb = showbModule
INLINE_INST_FUN(showb)
#endif