#if !(MIN_VERSION_base(4,7,0))
#endif
module Text.Show.Text.GHC.TypeLits (
#if MIN_VERSION_base(4,7,0)
showbSomeNatPrec
, showbSomeSymbol
#else
showbIsEven
, showbIsZero
#endif
) where
import Data.Text.Lazy.Builder (Builder)
import Prelude hiding (Show)
import Text.Show.Text.Classes (Show(showb, showbPrec))
#if MIN_VERSION_base(4,7,0)
import GHC.TypeLits (SomeNat(..), SomeSymbol(..), natVal, symbolVal)
import Text.Show.Text.Data.Char (showbString)
import Text.Show.Text.Data.Integral (showbIntegerPrec)
#else
import GHC.TypeLits (IsEven(..), IsZero(..), Kind, Sing, SingE(fromSing))
import Text.Show.Text.Data.Integral ()
import Text.Show.Text.Utils ((<>), s)
#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 = s '0'
showbIsEven (IsEven x) = "(2 * " <> showb x <> s ')'
showbIsEven (IsOdd x) = "(2 * " <> showb x <> " + 1)"
showbIsZero :: IsZero n -> Builder
showbIsZero IsZero = s '0'
showbIsZero (IsSucc n) = s '(' <> showb n <> " + 1)"
#endif
#if MIN_VERSION_base(4,7,0)
instance Show SomeNat where
showbPrec = showbSomeNatPrec
instance Show SomeSymbol where
showb = showbSomeSymbol
#else
instance Show (IsEven n) where
showb = showbIsEven
instance Show (IsZero n) where
showb = showbIsZero
instance (SingE (Kind :: k) rep, Show rep) => Show (Sing (a :: k)) where
showbPrec p = showbPrec p . fromSing
#endif