{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.GHC.TypeLits () where
import GHC.TypeLits (SomeNat(..), SomeSymbol(..), natVal, symbolVal)
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Data.Char ()
import TextShow.Data.Integral ()
instance TextShow SomeNat where
showbPrec :: Int -> SomeNat -> Builder
showbPrec Int
p (SomeNat Proxy n
x) = forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p forall a b. (a -> b) -> a -> b
$ forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal Proxy n
x
{-# INLINE showbPrec #-}
instance TextShow SomeSymbol where
showb :: SomeSymbol -> Builder
showb (SomeSymbol Proxy n
x) = forall a. TextShow a => [a] -> Builder
showbList forall a b. (a -> b) -> a -> b
$ forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal Proxy n
x
{-# INLINE showb #-}