#if MIN_VERSION_base(4,6,0)
# if !(MIN_VERSION_base(4,7,0))
# endif
#endif
module TextShow.GHC.TypeLits (
#if MIN_VERSION_base(4,7,0)
showbSomeNatPrec
, showbSomeSymbol
) where
#elif MIN_VERSION_base(4,6,0)
showbIsEven
, showbIsZero
, showbSingPrec
) where
#else
) where
#endif
#if MIN_VERSION_base(4,6,0)
import Data.Text.Lazy.Builder (Builder)
import TextShow.Classes (TextShow(..))
# if MIN_VERSION_base(4,7,0)
import GHC.TypeLits (SomeNat(..), SomeSymbol(..), natVal, symbolVal)
import TextShow.Data.Char (showbString)
import TextShow.Data.Integral (showbIntegerPrec)
# else
import Data.Monoid.Compat ((<>))
import Data.Text.Lazy.Builder (singleton)
import GHC.TypeLits (IsEven(..), IsZero(..), Kind, Sing, SingE(fromSing))
import TextShow.Data.Integral ()
# endif
# if MIN_VERSION_base(4,7,0)
showbSomeNatPrec :: Int -> SomeNat -> Builder
showbSomeNatPrec p (SomeNat x) = showbIntegerPrec p $ natVal x
showbSomeSymbol :: SomeSymbol -> Builder
showbSomeSymbol (SomeSymbol x) = showbString $ symbolVal x
# else
showbIsEven :: IsEven n -> Builder
showbIsEven IsEvenZero = singleton '0'
showbIsEven (IsEven x) = "(2 * " <> showb x <> singleton ')'
showbIsEven (IsOdd x) = "(2 * " <> showb x <> " + 1)"
showbIsZero :: IsZero n -> Builder
showbIsZero IsZero = singleton '0'
showbIsZero (IsSucc n) = singleton '(' <> showb n <> " + 1)"
showbSingPrec :: (SingE (Kind :: k) rep, TextShow rep) => Int -> Sing (a :: k) -> Builder
showbSingPrec p = showbPrec p . fromSing
# endif
# if MIN_VERSION_base(4,7,0)
instance TextShow SomeNat where
showbPrec = showbSomeNatPrec
instance TextShow SomeSymbol where
showb = showbSomeSymbol
# else
instance TextShow (IsEven n) where
showb = showbIsEven
instance TextShow (IsZero n) where
showb = showbIsZero
instance (SingE (Kind :: k) rep, TextShow rep) => TextShow (Sing (a :: k)) where
showbPrec = showbSingPrec
# endif
#endif