{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.Data.Integral (
showbIntegralPrec
, showbIntAtBase
, showbBin
, showbHex
, showbOct
) where
import Data.Char (intToDigit)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Text.Lazy.Builder (Builder, singleton)
import Data.Text.Lazy.Builder.Int (decimal)
import Data.Word (Word8, Word16, Word32, Word64)
import GHC.Exts (Int(I#), (<#), (>#))
#if __GLASGOW_HASKELL__ >= 708
import GHC.Exts (Int#, isTrue#)
#endif
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Utils (toString)
showbIntegralPrec :: Integral a => Int -> a -> Builder
showbIntegralPrec p = showbPrec p . toInteger
{-# INLINE showbIntegralPrec #-}
showbIntAtBase :: (Integral a, TextShow a) => a -> (Int -> Char) -> a -> Builder
{-# SPECIALIZE showbIntAtBase :: Int -> (Int -> Char) -> Int -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Int8 -> (Int -> Char) -> Int8 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Int16 -> (Int -> Char) -> Int16 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Int32 -> (Int -> Char) -> Int32 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Int64 -> (Int -> Char) -> Int64 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Integer -> (Int -> Char) -> Integer -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Word -> (Int -> Char) -> Word -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Word8 -> (Int -> Char) -> Word8 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Word16 -> (Int -> Char) -> Word16 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Word32 -> (Int -> Char) -> Word32 -> Builder #-}
{-# SPECIALIZE showbIntAtBase :: Word64 -> (Int -> Char) -> Word64 -> Builder #-}
showbIntAtBase base toChr n0
| base <= 1 = error . toString $ "TextShow.Int.showbIntAtBase: applied to unsupported base" <> showb base
| n0 < 0 = error . toString $ "TextShow.Int.showbIntAtBase: applied to negative number " <> showb n0
| otherwise = showbIt (quotRem n0 base) mempty
where
showbIt (n, d) b = seq c $
case n of
0 -> b'
_ -> showbIt (quotRem n base) b'
where
c :: Char
c = toChr $ fromIntegral d
b' :: Builder
b' = singleton c <> b
showbBin :: (Integral a, TextShow a) => a -> Builder
showbBin = showbIntAtBase 2 intToDigit
{-# INLINE showbBin #-}
showbHex :: (Integral a, TextShow a) => a -> Builder
showbHex = showbIntAtBase 16 intToDigit
{-# INLINE showbHex #-}
showbOct :: (Integral a, TextShow a) => a -> Builder
showbOct = showbIntAtBase 8 intToDigit
{-# INLINE showbOct #-}
instance TextShow Int where
showbPrec (I# p) n'@(I# n)
| isTrue (n <# 0#) && isTrue (p ># 6#)
= singleton '(' <> decimal n' <> singleton ')'
| otherwise
= decimal n'
where
#if __GLASGOW_HASKELL__ >= 708
isTrue :: Int# -> Bool
isTrue b = isTrue# b
#else
isTrue :: Bool -> Bool
isTrue = id
#endif
instance TextShow Int8 where
showbPrec p x = showbPrec p (fromIntegral x :: Int)
{-# INLINE showbPrec #-}
instance TextShow Int16 where
showbPrec p x = showbPrec p (fromIntegral x :: Int)
{-# INLINE showbPrec #-}
instance TextShow Int32 where
showbPrec p x = showbPrec p (fromIntegral x :: Int)
{-# INLINE showbPrec #-}
instance TextShow Int64 where
#if WORD_SIZE_IN_BITS < 64
showbPrec p = showbPrec p . toInteger
#else
showbPrec p x = showbPrec p (fromIntegral x :: Int)
#endif
{-# INLINE showbPrec #-}
instance TextShow Integer where
showbPrec p n
| p > 6 && n < 0 = singleton '(' <> decimal n <> singleton ')'
| otherwise = decimal n
{-# INLINE showbPrec #-}
instance TextShow Word where
showb = decimal
{-# INLINE showb #-}
instance TextShow Word8 where
showb = decimal
{-# INLINE showb #-}
instance TextShow Word16 where
showb = decimal
{-# INLINE showb #-}
instance TextShow Word32 where
showb = decimal
{-# INLINE showb #-}
instance TextShow Word64 where
showb = decimal
{-# INLINE showb #-}