{-# 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#), (<#), (>#), isTrue#)
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.Utils (toString)
showbIntegralPrec :: Integral a => Int -> a -> Builder
showbIntegralPrec :: forall a. Integral a => Int -> a -> Builder
showbIntegralPrec Int
p = forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
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 :: forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
base Int -> Char
toChr a
n0
| a
base forall a. Ord a => a -> a -> Bool
<= a
1 = forall a. HasCallStack => [Char] -> a
error forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Char]
toString forall a b. (a -> b) -> a -> b
$ Builder
"TextShow.Int.showbIntAtBase: applied to unsupported base" forall a. Semigroup a => a -> a -> a
<> forall a. TextShow a => a -> Builder
showb a
base
| a
n0 forall a. Ord a => a -> a -> Bool
< a
0 = forall a. HasCallStack => [Char] -> a
error forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Char]
toString forall a b. (a -> b) -> a -> b
$ Builder
"TextShow.Int.showbIntAtBase: applied to negative number " forall a. Semigroup a => a -> a -> a
<> forall a. TextShow a => a -> Builder
showb a
n0
| Bool
otherwise = (a, a) -> Builder -> Builder
showbIt (forall a. Integral a => a -> a -> (a, a)
quotRem a
n0 a
base) forall a. Monoid a => a
mempty
where
showbIt :: (a, a) -> Builder -> Builder
showbIt (a
n, a
d) Builder
b = seq :: forall a b. a -> b -> b
seq Char
c forall a b. (a -> b) -> a -> b
$
case a
n of
a
0 -> Builder
b'
a
_ -> (a, a) -> Builder -> Builder
showbIt (forall a. Integral a => a -> a -> (a, a)
quotRem a
n a
base) Builder
b'
where
c :: Char
c :: Char
c = Int -> Char
toChr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d
b' :: Builder
b' :: Builder
b' = Char -> Builder
singleton Char
c forall a. Semigroup a => a -> a -> a
<> Builder
b
showbBin :: (Integral a, TextShow a) => a -> Builder
showbBin :: forall a. (Integral a, TextShow a) => a -> Builder
showbBin = forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
2 Int -> Char
intToDigit
{-# INLINE showbBin #-}
showbHex :: (Integral a, TextShow a) => a -> Builder
showbHex :: forall a. (Integral a, TextShow a) => a -> Builder
showbHex = forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
16 Int -> Char
intToDigit
{-# INLINE showbHex #-}
showbOct :: (Integral a, TextShow a) => a -> Builder
showbOct :: forall a. (Integral a, TextShow a) => a -> Builder
showbOct = forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
8 Int -> Char
intToDigit
{-# INLINE showbOct #-}
instance TextShow Int where
showbPrec :: Int -> Int -> Builder
showbPrec (I# Int#
p) n' :: Int
n'@(I# Int#
n)
| Int# -> Bool
isTrue# (Int#
n Int# -> Int# -> Int#
<# Int#
0#) Bool -> Bool -> Bool
&& Int# -> Bool
isTrue# (Int#
p Int# -> Int# -> Int#
># Int#
6#)
= Char -> Builder
singleton Char
'(' forall a. Semigroup a => a -> a -> a
<> forall a. Integral a => a -> Builder
decimal Int
n' forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
')'
| Bool
otherwise
= forall a. Integral a => a -> Builder
decimal Int
n'
instance TextShow Int8 where
showbPrec :: Int -> Int8 -> Builder
showbPrec Int
p Int8
x = forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
x :: Int)
{-# INLINE showbPrec #-}
instance TextShow Int16 where
showbPrec :: Int -> Int16 -> Builder
showbPrec Int
p Int16
x = forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
x :: Int)
{-# INLINE showbPrec #-}
instance TextShow Int32 where
showbPrec :: Int -> Int32 -> Builder
showbPrec Int
p Int32
x = forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
x :: Int)
{-# INLINE showbPrec #-}
instance TextShow Int64 where
#if WORD_SIZE_IN_BITS < 64
showbPrec :: Int -> Int64 -> Builder
showbPrec Int
p = forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger
#else
showbPrec p x = showbPrec p (fromIntegral x :: Int)
#endif
{-# INLINE showbPrec #-}
instance TextShow Integer where
showbPrec :: Int -> Integer -> Builder
showbPrec Int
p Integer
n
| Int
p forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Integer
n forall a. Ord a => a -> a -> Bool
< Integer
0 = Char -> Builder
singleton Char
'(' forall a. Semigroup a => a -> a -> a
<> forall a. Integral a => a -> Builder
decimal Integer
n forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
')'
| Bool
otherwise = forall a. Integral a => a -> Builder
decimal Integer
n
{-# INLINE showbPrec #-}
instance TextShow Word where
showb :: Word -> Builder
showb = forall a. Integral a => a -> Builder
decimal
{-# INLINE showb #-}
instance TextShow Word8 where
showb :: Word8 -> Builder
showb = forall a. Integral a => a -> Builder
decimal
{-# INLINE showb #-}
instance TextShow Word16 where
showb :: Word16 -> Builder
showb = forall a. Integral a => a -> Builder
decimal
{-# INLINE showb #-}
instance TextShow Word32 where
showb :: Word32 -> Builder
showb = forall a. Integral a => a -> Builder
decimal
{-# INLINE showb #-}
instance TextShow Word64 where
showb :: Word64 -> Builder
showb = forall a. Integral a => a -> Builder
decimal
{-# INLINE showb #-}