{-# LANGUAGE CPP               #-}
{-# LANGUAGE MagicHash         #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-|
Module:      TextShow.Data.Integral
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

'TextShow' instances and monomorphic functions for integral types.

/Since: 2/
-}
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)

-- | Convert an 'Integral' type to a 'Builder' with the given precedence.
--
-- /Since: 2/
showbIntegralPrec :: Integral a => Int -> a -> Builder
showbIntegralPrec :: Int -> a -> Builder
showbIntegralPrec Int
p = Int -> Integer -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (Integer -> Builder) -> (a -> Integer) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a. Integral a => a -> Integer
toInteger
{-# INLINE showbIntegralPrec #-}

-- | Shows a /non-negative/ 'Integral' number using the base specified by the
-- first argument, and the character representation specified by the second.
--
-- /Since: 2/
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 :: a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
base Int -> Char
toChr a
n0
    | a
base a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
1 = [Char] -> Builder
forall a. HasCallStack => [Char] -> a
error ([Char] -> Builder) -> (Builder -> [Char]) -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Char]
toString (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ Builder
"TextShow.Int.showbIntAtBase: applied to unsupported base" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. TextShow a => a -> Builder
showb a
base
    | a
n0 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0    = [Char] -> Builder
forall a. HasCallStack => [Char] -> a
error ([Char] -> Builder) -> (Builder -> [Char]) -> Builder -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> [Char]
toString (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ Builder
"TextShow.Int.showbIntAtBase: applied to negative number " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
forall a. TextShow a => a -> Builder
showb a
n0
    | Bool
otherwise = (a, a) -> Builder -> Builder
showbIt (a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem a
n0 a
base) Builder
forall a. Monoid a => a
mempty
  where
    showbIt :: (a, a) -> Builder -> Builder
showbIt (a
n, a
d) Builder
b = Char -> Builder -> Builder
seq Char
c (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ -- stricter than necessary
        case a
n of
             a
0 -> Builder
b'
             a
_ -> (a, a) -> Builder -> Builder
showbIt (a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem a
n a
base) Builder
b'
      where
        c :: Char
        c :: Char
c = Int -> Char
toChr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d

        b' :: Builder
        b' :: Builder
b' = Char -> Builder
singleton Char
c Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
b

-- | Show /non-negative/ 'Integral' numbers in base 2.
--
-- /Since: 2/
showbBin :: (Integral a, TextShow a) => a -> Builder
showbBin :: a -> Builder
showbBin = a -> (Int -> Char) -> a -> Builder
forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
2 Int -> Char
intToDigit
{-# INLINE showbBin #-}

-- | Show /non-negative/ 'Integral' numbers in base 16.
--
-- /Since: 2/
showbHex :: (Integral a, TextShow a) => a -> Builder
showbHex :: a -> Builder
showbHex = a -> (Int -> Char) -> a -> Builder
forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
16 Int -> Char
intToDigit
{-# INLINE showbHex #-}

-- | Show /non-negative/ 'Integral' numbers in base 8.
--
-- /Since: 2/
showbOct :: (Integral a, TextShow a) => a -> Builder
showbOct :: a -> Builder
showbOct = a -> (Int -> Char) -> a -> Builder
forall a.
(Integral a, TextShow a) =>
a -> (Int -> Char) -> a -> Builder
showbIntAtBase a
8 Int -> Char
intToDigit
{-# INLINE showbOct #-}

-- | /Since: 2/
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
'(' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a. Integral a => a -> Builder
decimal Int
n' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
')'
        | Bool
otherwise
        = Int -> Builder
forall a. Integral a => a -> Builder
decimal Int
n'

-- | /Since: 2/
instance TextShow Int8 where
    showbPrec :: Int -> Int8 -> Builder
showbPrec Int
p Int8
x = Int -> Int -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (Int8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
x :: Int)
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow Int16 where
    showbPrec :: Int -> Int16 -> Builder
showbPrec Int
p Int16
x = Int -> Int -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (Int16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int16
x :: Int)
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow Int32 where
    showbPrec :: Int -> Int32 -> Builder
showbPrec Int
p Int32
x = Int -> Int -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
x :: Int)
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow Int64 where
#if WORD_SIZE_IN_BITS < 64
    showbPrec :: Int -> Int64 -> Builder
showbPrec Int
p   = Int -> Integer -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p (Integer -> Builder) -> (Int64 -> Integer) -> Int64 -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger
#else
    showbPrec p x = showbPrec p (fromIntegral x :: Int)
#endif
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow Integer where
    showbPrec :: Int -> Integer -> Builder
showbPrec Int
p Integer
n
        | Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
6 Bool -> Bool -> Bool
&& Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Char -> Builder
singleton Char
'(' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Integer -> Builder
forall a. Integral a => a -> Builder
decimal Integer
n Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
')'
        | Bool
otherwise      = Integer -> Builder
forall a. Integral a => a -> Builder
decimal Integer
n
    {-# INLINE showbPrec #-}

-- | /Since: 2/
instance TextShow Word where
    showb :: Word -> Builder
showb = Word -> Builder
forall a. Integral a => a -> Builder
decimal
    {-# INLINE showb #-}

-- | /Since: 2/
instance TextShow Word8 where
    showb :: Word8 -> Builder
showb = Word8 -> Builder
forall a. Integral a => a -> Builder
decimal
    {-# INLINE showb #-}

-- | /Since: 2/
instance TextShow Word16 where
    showb :: Word16 -> Builder
showb = Word16 -> Builder
forall a. Integral a => a -> Builder
decimal
    {-# INLINE showb #-}

-- | /Since: 2/
instance TextShow Word32 where
    showb :: Word32 -> Builder
showb = Word32 -> Builder
forall a. Integral a => a -> Builder
decimal
    {-# INLINE showb #-}

-- | /Since: 2/
instance TextShow Word64 where
    showb :: Word64 -> Builder
showb = Word64 -> Builder
forall a. Integral a => a -> Builder
decimal
    {-# INLINE showb #-}