module TextShow.Data.Integral (
showbIntPrec
, showbInt8Prec
, showbInt16Prec
, showbInt32Prec
, showbInt64Prec
, showbIntegerPrec
, showbIntegralPrec
, showbIntAtBase
, showbBin
, showbHex
, showbOct
, showbWord
, showbWord8
, showbWord16
, showbWord32
, showbWord64
) where
import Data.Char (intToDigit)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Monoid.Compat ((<>))
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 (isTrue#)
import GHC.Prim (Int#)
#endif
import GHC.Prim ((<#), (>#))
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Utils (toString)
#include "inline.h"
showbIntPrec :: Int -> Int -> Builder
showbIntPrec (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
showbInt8Prec :: Int -> Int8 -> Builder
showbInt8Prec p = showbIntPrec p . fromIntegral
showbInt16Prec :: Int -> Int16 -> Builder
showbInt16Prec p = showbIntPrec p . fromIntegral
showbInt32Prec :: Int -> Int32 -> Builder
showbInt32Prec p = showbIntPrec p . fromIntegral
showbInt64Prec :: Int -> Int64 -> Builder
#if WORD_SIZE_IN_BITS < 64
showbInt64Prec p = showbIntegerPrec p . toInteger
#else
showbInt64Prec p = showbIntPrec p . fromIntegral
#endif
showbIntegerPrec :: Int -> Integer -> Builder
showbIntegerPrec p n
| p > 6 && n < 0 = singleton '(' <> decimal n <> singleton ')'
| otherwise = decimal n
showbIntegralPrec :: Integral a => Int -> a -> Builder
showbIntegralPrec p = showbIntegerPrec p . toInteger
showbIntAtBase :: (Integral a, TextShow a) => a -> (Int -> Char) -> a -> 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
showbHex :: (Integral a, TextShow a) => a -> Builder
showbHex = showbIntAtBase 16 intToDigit
showbOct :: (Integral a, TextShow a) => a -> Builder
showbOct = showbIntAtBase 8 intToDigit
showbWord :: Word -> Builder
showbWord = decimal
showbWord8 :: Word8 -> Builder
showbWord8 = decimal
showbWord16 :: Word16 -> Builder
showbWord16 = decimal
showbWord32 :: Word32 -> Builder
showbWord32 = decimal
showbWord64 :: Word64 -> Builder
showbWord64 = decimal
instance TextShow Int where
showbPrec = showbIntPrec
INLINE_INST_FUN(showbPrec)
instance TextShow Int8 where
showbPrec = showbInt8Prec
INLINE_INST_FUN(showbPrec)
instance TextShow Int16 where
showbPrec = showbInt16Prec
INLINE_INST_FUN(showbPrec)
instance TextShow Int32 where
showbPrec = showbInt32Prec
INLINE_INST_FUN(showbPrec)
instance TextShow Int64 where
showbPrec = showbInt64Prec
INLINE_INST_FUN(showbPrec)
instance TextShow Integer where
showbPrec = showbIntegerPrec
INLINE_INST_FUN(showbPrec)
instance TextShow Word where
showb = showbWord
INLINE_INST_FUN(showb)
instance TextShow Word8 where
showb = showbWord8
INLINE_INST_FUN(showb)
instance TextShow Word16 where
showb = showbWord16
INLINE_INST_FUN(showb)
instance TextShow Word32 where
showb = showbWord32
INLINE_INST_FUN(showb)
instance TextShow Word64 where
showb = showbWord64
INLINE_INST_FUN(showb)