{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
module Z.Data.Builder.Numeric (
IFormat(..)
, defaultIFormat
, Padding(..)
, int
, intWith
, integer
, hex, heX
, FFormat(..)
, double
, doubleWith
, float
, floatWith
, scientific
, scientificWith
, grisu3
, grisu3_sp
, i2wDec, i2wHex, i2wHeX
, countDigits
, c_intWith, hs_intWith
) where
import Control.Monad
import Control.Monad.ST
import Control.Monad.ST.Unsafe
import Data.Bits
import Data.Char
import Data.Int
import qualified Data.List as List
import Data.Primitive.ByteArray
import Data.Primitive.PrimArray
import qualified Data.Scientific as Sci
import Data.Word
import GHC.Exts
import GHC.Float
import GHC.Integer
import Z.Data.Builder.Base
import Z.Data.Builder.Numeric.DigitTable
import Z.Foreign
import System.IO.Unsafe
#ifdef INTEGER_GMP
import GHC.Integer.GMP.Internals
#endif
import Test.QuickCheck.Arbitrary (Arbitrary(..), CoArbitrary(..))
foreign import ccall unsafe "dtoa.h" c_int_dec :: Word64 -> Int -> Int -> Word8 -> MBA# Word8 -> Int -> IO Int
data IFormat = IFormat
{ IFormat -> Int
width :: Int
, IFormat -> Padding
padding :: Padding
, IFormat -> Bool
posSign :: Bool
} deriving (Int -> IFormat -> ShowS
[IFormat] -> ShowS
IFormat -> String
(Int -> IFormat -> ShowS)
-> (IFormat -> String) -> ([IFormat] -> ShowS) -> Show IFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IFormat] -> ShowS
$cshowList :: [IFormat] -> ShowS
show :: IFormat -> String
$cshow :: IFormat -> String
showsPrec :: Int -> IFormat -> ShowS
$cshowsPrec :: Int -> IFormat -> ShowS
Show, IFormat -> IFormat -> Bool
(IFormat -> IFormat -> Bool)
-> (IFormat -> IFormat -> Bool) -> Eq IFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IFormat -> IFormat -> Bool
$c/= :: IFormat -> IFormat -> Bool
== :: IFormat -> IFormat -> Bool
$c== :: IFormat -> IFormat -> Bool
Eq, Eq IFormat
Eq IFormat
-> (IFormat -> IFormat -> Ordering)
-> (IFormat -> IFormat -> Bool)
-> (IFormat -> IFormat -> Bool)
-> (IFormat -> IFormat -> Bool)
-> (IFormat -> IFormat -> Bool)
-> (IFormat -> IFormat -> IFormat)
-> (IFormat -> IFormat -> IFormat)
-> Ord IFormat
IFormat -> IFormat -> Bool
IFormat -> IFormat -> Ordering
IFormat -> IFormat -> IFormat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IFormat -> IFormat -> IFormat
$cmin :: IFormat -> IFormat -> IFormat
max :: IFormat -> IFormat -> IFormat
$cmax :: IFormat -> IFormat -> IFormat
>= :: IFormat -> IFormat -> Bool
$c>= :: IFormat -> IFormat -> Bool
> :: IFormat -> IFormat -> Bool
$c> :: IFormat -> IFormat -> Bool
<= :: IFormat -> IFormat -> Bool
$c<= :: IFormat -> IFormat -> Bool
< :: IFormat -> IFormat -> Bool
$c< :: IFormat -> IFormat -> Bool
compare :: IFormat -> IFormat -> Ordering
$ccompare :: IFormat -> IFormat -> Ordering
$cp1Ord :: Eq IFormat
Ord)
instance Arbitrary IFormat where
arbitrary :: Gen IFormat
arbitrary = Int -> Padding -> Bool -> IFormat
IFormat (Int -> Padding -> Bool -> IFormat)
-> Gen Int -> Gen (Padding -> Bool -> IFormat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Padding -> Bool -> IFormat)
-> Gen Padding -> Gen (Bool -> IFormat)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Padding
forall a. Arbitrary a => Gen a
arbitrary Gen (Bool -> IFormat) -> Gen Bool -> Gen IFormat
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
instance CoArbitrary IFormat where
coarbitrary :: IFormat -> Gen b -> Gen b
coarbitrary (IFormat Int
w Padding
pad Bool
p) = (Int, Padding, Bool) -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Int
w, Padding
pad, Bool
p)
defaultIFormat :: IFormat
defaultIFormat :: IFormat
defaultIFormat = Int -> Padding -> Bool -> IFormat
IFormat Int
0 Padding
NoPadding Bool
False
data Padding = NoPadding | RightSpacePadding | LeftSpacePadding | ZeroPadding deriving (Int -> Padding -> ShowS
[Padding] -> ShowS
Padding -> String
(Int -> Padding -> ShowS)
-> (Padding -> String) -> ([Padding] -> ShowS) -> Show Padding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Padding] -> ShowS
$cshowList :: [Padding] -> ShowS
show :: Padding -> String
$cshow :: Padding -> String
showsPrec :: Int -> Padding -> ShowS
$cshowsPrec :: Int -> Padding -> ShowS
Show, Padding -> Padding -> Bool
(Padding -> Padding -> Bool)
-> (Padding -> Padding -> Bool) -> Eq Padding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Padding -> Padding -> Bool
$c/= :: Padding -> Padding -> Bool
== :: Padding -> Padding -> Bool
$c== :: Padding -> Padding -> Bool
Eq, Eq Padding
Eq Padding
-> (Padding -> Padding -> Ordering)
-> (Padding -> Padding -> Bool)
-> (Padding -> Padding -> Bool)
-> (Padding -> Padding -> Bool)
-> (Padding -> Padding -> Bool)
-> (Padding -> Padding -> Padding)
-> (Padding -> Padding -> Padding)
-> Ord Padding
Padding -> Padding -> Bool
Padding -> Padding -> Ordering
Padding -> Padding -> Padding
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Padding -> Padding -> Padding
$cmin :: Padding -> Padding -> Padding
max :: Padding -> Padding -> Padding
$cmax :: Padding -> Padding -> Padding
>= :: Padding -> Padding -> Bool
$c>= :: Padding -> Padding -> Bool
> :: Padding -> Padding -> Bool
$c> :: Padding -> Padding -> Bool
<= :: Padding -> Padding -> Bool
$c<= :: Padding -> Padding -> Bool
< :: Padding -> Padding -> Bool
$c< :: Padding -> Padding -> Bool
compare :: Padding -> Padding -> Ordering
$ccompare :: Padding -> Padding -> Ordering
$cp1Ord :: Eq Padding
Ord, Int -> Padding
Padding -> Int
Padding -> [Padding]
Padding -> Padding
Padding -> Padding -> [Padding]
Padding -> Padding -> Padding -> [Padding]
(Padding -> Padding)
-> (Padding -> Padding)
-> (Int -> Padding)
-> (Padding -> Int)
-> (Padding -> [Padding])
-> (Padding -> Padding -> [Padding])
-> (Padding -> Padding -> [Padding])
-> (Padding -> Padding -> Padding -> [Padding])
-> Enum Padding
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Padding -> Padding -> Padding -> [Padding]
$cenumFromThenTo :: Padding -> Padding -> Padding -> [Padding]
enumFromTo :: Padding -> Padding -> [Padding]
$cenumFromTo :: Padding -> Padding -> [Padding]
enumFromThen :: Padding -> Padding -> [Padding]
$cenumFromThen :: Padding -> Padding -> [Padding]
enumFrom :: Padding -> [Padding]
$cenumFrom :: Padding -> [Padding]
fromEnum :: Padding -> Int
$cfromEnum :: Padding -> Int
toEnum :: Int -> Padding
$ctoEnum :: Int -> Padding
pred :: Padding -> Padding
$cpred :: Padding -> Padding
succ :: Padding -> Padding
$csucc :: Padding -> Padding
Enum)
instance Arbitrary Padding where
arbitrary :: Gen Padding
arbitrary = Int -> Padding
forall a. Enum a => Int -> a
toEnum (Int -> Padding) -> (Int -> Int) -> Int -> Padding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
4) (Int -> Padding) -> Gen Int -> Gen Padding
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
instance CoArbitrary Padding where
coarbitrary :: Padding -> Gen b -> Gen b
coarbitrary = Int -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Int -> Gen b -> Gen b)
-> (Padding -> Int) -> Padding -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Int
forall a. Enum a => a -> Int
fromEnum
int :: (Integral a, Bounded a) => a -> Builder ()
{-# INLINE int #-}
int :: a -> Builder ()
int = IFormat -> a -> Builder ()
forall a. (Integral a, Bounded a) => IFormat -> a -> Builder ()
intWith IFormat
defaultIFormat
intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder ()
intWith :: IFormat -> a -> Builder ()
intWith = IFormat -> a -> Builder ()
forall a. (Integral a, Bounded a) => IFormat -> a -> Builder ()
hs_intWith
{-# INLINE[0] intWith #-}
{-# RULES "intWith'/Int8" intWith = c_intWith :: IFormat -> Int8 -> Builder () #-}
{-# RULES "intWith'/Int" intWith = c_intWith :: IFormat -> Int -> Builder () #-}
{-# RULES "intWith'/Int16" intWith = c_intWith :: IFormat -> Int16 -> Builder () #-}
{-# RULES "intWith'/Int32" intWith = c_intWith :: IFormat -> Int32 -> Builder () #-}
{-# RULES "intWith'/Int64" intWith = c_intWith :: IFormat -> Int64 -> Builder () #-}
{-# RULES "intWith'/Word" intWith = c_intWith :: IFormat -> Word -> Builder () #-}
{-# RULES "intWith'/Word8" intWith = c_intWith :: IFormat -> Word8 -> Builder () #-}
{-# RULES "intWith'/Word16" intWith = c_intWith :: IFormat -> Word16 -> Builder () #-}
{-# RULES "intWith'/Word32" intWith = c_intWith :: IFormat -> Word32 -> Builder () #-}
{-# RULES "intWith'/Word64" intWith = c_intWith :: IFormat -> Word64 -> Builder () #-}
c_intWith :: (Integral a, Bits a) => IFormat -> a -> Builder ()
{-# INLINE c_intWith #-}
c_intWith :: IFormat -> a -> Builder ()
c_intWith (IFormat{Bool
Int
Padding
posSign :: Bool
padding :: Padding
width :: Int
posSign :: IFormat -> Bool
padding :: IFormat -> Padding
width :: IFormat -> Int
..}) a
x
| a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 =
let !x' :: Word64
x' = (a -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> a
forall a. Bits a => a -> a
complement a
x) :: Word64) Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1
in Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int)
-> Builder ()
atMost Int
width' (\ (MutablePrimArray MutableByteArray# s
mba#) Int
i ->
IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (Word64 -> Int -> Int -> Word8 -> MBA# Word8 -> Int -> IO Int
c_int_dec Word64
x' (-Int
1) Int
width Word8
pad (MutableByteArray# s -> MBA# Word8
unsafeCoerce# MutableByteArray# s
mba#) Int
i))
| Bool
posSign =
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int)
-> Builder ()
atMost Int
width' (\ (MutablePrimArray MutableByteArray# s
mba#) Int
i ->
IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (Word64 -> Int -> Int -> Word8 -> MBA# Word8 -> Int -> IO Int
c_int_dec (a -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x) Int
1 Int
width Word8
pad (MutableByteArray# s -> MBA# Word8
unsafeCoerce# MutableByteArray# s
mba#) Int
i))
| Bool
otherwise =
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int)
-> Builder ()
atMost Int
width' (\ (MutablePrimArray MutableByteArray# s
mba#) Int
i ->
IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (Word64 -> Int -> Int -> Word8 -> MBA# Word8 -> Int -> IO Int
c_int_dec (a -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x) Int
0 Int
width Word8
pad (MutableByteArray# s -> MBA# Word8
unsafeCoerce# MutableByteArray# s
mba#) Int
i))
where
width' :: Int
width' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
21 Int
width
pad :: Word8
pad = case Padding
padding of Padding
NoPadding -> Word8
0
Padding
RightSpacePadding -> Word8
1
Padding
LeftSpacePadding -> Word8
2
Padding
ZeroPadding -> Word8
3
hs_intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder ()
{-# INLINABLE hs_intWith #-}
hs_intWith :: IFormat -> a -> Builder ()
hs_intWith format :: IFormat
format@IFormat{Bool
Int
Padding
posSign :: Bool
padding :: Padding
width :: Int
posSign :: IFormat -> Bool
padding :: IFormat -> Padding
width :: IFormat -> Int
..} a
i
| a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 =
if a
i a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
forall a. Bounded a => a
minBound
then do
let (a
q, a
r) = a
i a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
10
!qq :: a
qq = -a
q
!rr :: Word8
rr = a -> Word8
forall a. Integral a => a -> Word8
i2wDec (-a
r)
!n :: Int
n = a -> Int
forall a. Integral a => a -> Int
countDigits a
qq
!n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2
if Int
width Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n'
then case Padding
padding of
Padding
NoPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n' ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
qq
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off'' Word8
rr
Padding
ZeroPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Int
leadingN Word8
zero
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off'' Int
n a
qq
let off''' :: Int
off''' = Int
off'' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off''' Word8
rr
Padding
LeftSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Int
leadingN Word8
space
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Word8
minus
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off'' Int
n a
qq
let off''' :: Int
off''' = Int
off'' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off''' Word8
rr
Padding
RightSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !trailingN :: Int
trailingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
qq
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off'' Word8
rr
let off''' :: Int
off''' = Int
off'' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off''' Int
trailingN Word8
space
else
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n' ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
qq
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off'' Word8
rr
else do
let !qq :: a
qq = -a
i
!n :: Int
n = a -> Int
forall a. Integral a => a -> Int
countDigits a
qq
!n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
if Int
width Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n'
then case Padding
padding of
Padding
NoPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n' ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
qq
Padding
ZeroPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Int
leadingN Word8
zero
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off'' Int
n a
qq
Padding
LeftSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Int
leadingN Word8
space
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Word8
minus
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off'' Int
n a
qq
Padding
RightSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !trailingN :: Int
trailingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
qq
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off'' Int
trailingN Word8
space
else
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n' ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
minus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
qq
| Bool
otherwise = IFormat -> a -> Builder ()
forall a. Integral a => IFormat -> a -> Builder ()
positiveInt IFormat
format a
i
positiveInt :: (Integral a) => IFormat -> a -> Builder ()
{-# INLINABLE positiveInt #-}
positiveInt :: IFormat -> a -> Builder ()
positiveInt (IFormat Int
width Padding
padding Bool
ps) a
i =
let !n :: Int
n = a -> Int
forall a. Integral a => a -> Int
countDigits a
i
in if Bool
ps
then
let n' :: Int
n' = Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1
in if Int
width Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n'
then case Padding
padding of
Padding
NoPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n' ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
plus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
i
Padding
ZeroPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
plus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Int
leadingN Word8
zero
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off'' Int
n a
i
Padding
LeftSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Int
leadingN Word8
space
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Word8
plus
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off'' Int
n a
i
Padding
RightSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !trailingN :: Int
trailingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n'
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
plus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
i
let off'' :: Int
off'' = Int
off' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off'' Int
trailingN Word8
space
else
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n' ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Word8
plus
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
i
else if Int
width Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n
then case Padding
padding of
Padding
NoPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off Int
n a
i
Padding
ZeroPadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Int
leadingN Word8
zero
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
i
Padding
LeftSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !leadingN :: Int
leadingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off Int
leadingN Word8
space
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
leadingN
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off' Int
n a
i
Padding
RightSpacePadding ->
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
width ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
let !trailingN :: Int
trailingN = Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off Int
n a
i
let off' :: Int
off' = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
setPrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off' Int
trailingN Word8
space
else
Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
n ((forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ())
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
forall a b. (a -> b) -> a -> b
$ \MutablePrimArray s Word8
marr Int
off -> do
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
forall a s.
Integral a =>
MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off Int
n a
i
writePositiveDec :: (Integral a)
=> forall s. MutablePrimArray s Word8
-> Int
-> Int
-> a
-> ST s ()
{-# INLINE writePositiveDec #-}
writePositiveDec :: forall s. MutablePrimArray s Word8 -> Int -> Int -> a -> ST s ()
writePositiveDec MutablePrimArray s Word8
marr Int
off0 Int
ds = Int -> a -> ST s ()
go (Int
off0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ds Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
where
go :: Int -> a -> ST s ()
go Int
off a
v
| a
v a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
100 = do
let (a
q, a
r) = a
v a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` a
100
Int -> a -> ST s ()
write2 Int
off a
r
Int -> a -> ST s ()
go (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) a
q
| a
v a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
10 = MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off (a -> Word8
forall a. Integral a => a -> Word8
i2wDec a
v)
| Bool
otherwise = Int -> a -> ST s ()
write2 Int
off a
v
write2 :: Int -> a -> ST s ()
write2 Int
off a
i0 = do
let i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i0; j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr Int
off (Word8 -> ST s ()) -> Word8 -> ST s ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
decDigitTable (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
MutablePrimArray (PrimState (ST s)) Word8
-> Int -> Word8 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray s Word8
MutablePrimArray (PrimState (ST s)) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Word8 -> ST s ()) -> Word8 -> ST s ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
decDigitTable Int
j
#include "MachDeps.h"
#if SIZEOF_HSWORD == 4
#define DIGITS 9
#define BASE 1000000000
#elif SIZEOF_HSWORD == 8
#define DIGITS 18
#define BASE 1000000000000000000
#else
#error Please define DIGITS and BASE
#endif
integer :: Integer -> Builder ()
#ifdef INTEGER_GMP
integer :: Integer -> Builder ()
integer (S# Int#
i#) = Int -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
int (Int# -> Int
I# Int#
i#)
#endif
integer Integer
n0
| Integer
n0 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Word8 -> Builder ()
forall a. UnalignedAccess a => a -> Builder ()
encodePrim Word8
minus Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Integer -> Builder ()
integer' (-Integer
n0)
| Bool
otherwise = Integer -> Builder ()
integer' Integer
n0
where
integer' :: Integer -> Builder ()
integer' :: Integer -> Builder ()
integer' Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< BASE = jhead (fromInteger n)
| Bool
otherwise = [Integer] -> Builder ()
jprinth (Integer -> Integer -> [Integer]
jsplitf (BASE*BASE) n)
jprinth :: [Integer] -> Builder ()
jprinth :: [Integer] -> Builder ()
jprinth (Integer
n:[Integer]
ns) =
case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` BASE of
(# Integer
q', Integer
r' #) ->
let q :: Int
q = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
q'
r :: Int
r = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
r'
in if Int
q Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int -> Builder ()
jhead Int
q Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> Builder ()
jblock Int
r Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Integer] -> Builder ()
jprintb [Integer]
ns
else Int -> Builder ()
jhead Int
r Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Integer] -> Builder ()
jprintb [Integer]
ns
jprinth [] = String -> Builder ()
forall a. String -> a
errorWithoutStackTrace String
"jprinth []"
jprintb :: [Integer] -> Builder ()
jprintb :: [Integer] -> Builder ()
jprintb [] = () -> Builder ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
jprintb (Integer
n:[Integer]
ns) = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` BASE of
(# Integer
q', Integer
r' #) ->
let q :: Int
q = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
q'
r :: Int
r = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
r'
in Int -> Builder ()
jblock Int
q Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> Builder ()
jblock Int
r Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Integer] -> Builder ()
jprintb [Integer]
ns
jhead :: Int -> Builder ()
jhead :: Int -> Builder ()
jhead = Int -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
int
jblock :: Int -> Builder ()
jblock :: Int -> Builder ()
jblock = IFormat -> Int -> Builder ()
forall a. (Integral a, Bounded a) => IFormat -> a -> Builder ()
intWith IFormat
defaultIFormat{padding :: Padding
padding = Padding
ZeroPadding, width :: Int
width=DIGITS}
jsplitf :: Integer -> Integer -> [Integer]
jsplitf :: Integer -> Integer -> [Integer]
jsplitf Integer
p Integer
n
| Integer
p Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
n = [Integer
n]
| Bool
otherwise = Integer -> [Integer] -> [Integer]
jsplith Integer
p (Integer -> Integer -> [Integer]
jsplitf (Integer
pInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
p) Integer
n)
jsplith :: Integer -> [Integer] -> [Integer]
jsplith :: Integer -> [Integer] -> [Integer]
jsplith Integer
p (Integer
n:[Integer]
ns) =
case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
p of
(# Integer
q, Integer
r #) ->
if Integer
q Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 then Integer
q Integer -> [Integer] -> [Integer]
forall k1. k1 -> [k1] -> [k1]
: Integer
r Integer -> [Integer] -> [Integer]
forall k1. k1 -> [k1] -> [k1]
: Integer -> [Integer] -> [Integer]
jsplitb Integer
p [Integer]
ns
else Integer
r Integer -> [Integer] -> [Integer]
forall k1. k1 -> [k1] -> [k1]
: Integer -> [Integer] -> [Integer]
jsplitb Integer
p [Integer]
ns
jsplith Integer
_ [] = String -> [Integer]
forall a. String -> a
errorWithoutStackTrace String
"jsplith: []"
jsplitb :: Integer -> [Integer] -> [Integer]
jsplitb :: Integer -> [Integer] -> [Integer]
jsplitb Integer
_ [] = []
jsplitb Integer
p (Integer
n:[Integer]
ns) = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
p of
(# Integer
q, Integer
r #) ->
Integer
q Integer -> [Integer] -> [Integer]
forall k1. k1 -> [k1] -> [k1]
: Integer
r Integer -> [Integer] -> [Integer]
forall k1. k1 -> [k1] -> [k1]
: Integer -> [Integer] -> [Integer]
jsplitb Integer
p [Integer]
ns
countDigits :: (Integral a) => a -> Int
{-# INLINE countDigits #-}
countDigits :: a -> Int
countDigits a
v0
| Word64 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
v64 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v0 = Int -> Word64 -> Int
forall t. Num t => t -> Word64 -> t
go Int
1 Word64
v64
| Bool
otherwise = Int -> Integer -> Int
goBig Int
1 (a -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v0)
where v64 :: Word64
v64 = a -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v0
goBig :: Int -> Integer -> Int
goBig !Int
k (Integer
v :: Integer)
| Integer
v Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
big = Int -> Integer -> Int
goBig (Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
19) (Integer
v Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
big)
| Bool
otherwise = Int -> Word64 -> Int
forall t. Num t => t -> Word64 -> t
go Int
k (Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
v)
big :: Integer
big = Integer
10000000000000000000
go :: t -> Word64 -> t
go !t
k (Word64
v :: Word64)
| Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
10 = t
k
| Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
100 = t
k t -> t -> t
forall a. Num a => a -> a -> a
+ t
1
| Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
1000 = t
k t -> t -> t
forall a. Num a => a -> a -> a
+ t
2
| Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
1000000000000 =
t
k t -> t -> t
forall a. Num a => a -> a -> a
+ if Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
100000000
then if Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
1000000
then if Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
10000
then t
3
else t
4 t -> t -> t
forall a. Num a => a -> a -> a
+ Word64 -> Word64 -> t
forall a p. (Ord a, Num p) => a -> a -> p
fin Word64
v Word64
100000
else t
6 t -> t -> t
forall a. Num a => a -> a -> a
+ Word64 -> Word64 -> t
forall a p. (Ord a, Num p) => a -> a -> p
fin Word64
v Word64
10000000
else if Word64
v Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
< Word64
10000000000
then t
8 t -> t -> t
forall a. Num a => a -> a -> a
+ Word64 -> Word64 -> t
forall a p. (Ord a, Num p) => a -> a -> p
fin Word64
v Word64
1000000000
else t
10 t -> t -> t
forall a. Num a => a -> a -> a
+ Word64 -> Word64 -> t
forall a p. (Ord a, Num p) => a -> a -> p
fin Word64
v Word64
100000000000
| Bool
otherwise = t -> Word64 -> t
go (t
k t -> t -> t
forall a. Num a => a -> a -> a
+ t
12) (Word64
v Word64 -> Word64 -> Word64
forall a. Integral a => a -> a -> a
`quot` Word64
1000000000000)
fin :: a -> a -> p
fin a
v a
n = if a
v a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
n then p
1 else p
0
minus, plus, zero, space :: Word8
{-# INLINE plus #-}
{-# INLINE minus #-}
{-# INLINE zero #-}
{-# INLINE space #-}
plus :: Word8
plus = Word8
43
minus :: Word8
minus = Word8
45
zero :: Word8
zero = Word8
48
space :: Word8
space = Word8
32
i2wDec :: (Integral a) => a -> Word8
{-# INLINE i2wDec #-}
i2wDec :: a -> Word8
i2wDec a
v = Word8
zero Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v
i2cDec :: (Integral a) => a -> Char
{-# INLINE i2cDec #-}
i2cDec :: a -> Char
i2cDec a
v = Int -> Char
chr (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Char) -> Word8 -> Char
forall a b. (a -> b) -> a -> b
$ Word8
zero Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v
i2wHex :: (Integral a) => a -> Word8
{-# INLINE i2wHex #-}
i2wHex :: a -> Word8
i2wHex a
v
| a
v a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
9 = Word8
zero Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v
| Bool
otherwise = Word8
87 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v
i2wHeX :: (Integral a) => a -> Word8
{-# INLINE i2wHeX #-}
i2wHeX :: a -> Word8
i2wHeX a
v
| a
v a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
9 = Word8
zero Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v
| Bool
otherwise = Word8
55 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v
hex :: forall a. (FiniteBits a, Integral a) => a -> Builder ()
{-# SPECIALIZE INLINE hex :: Int -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Int8 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Int16 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Int32 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Int64 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Word -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Word8 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Word16 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Word32 -> Builder () #-}
{-# SPECIALIZE INLINE hex :: Word64 -> Builder () #-}
hex :: a -> Builder ()
hex a
w = Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
hexSiz (a
-> Int
-> MutablePrimArray (PrimState (ST s)) Word8
-> Int
-> ST s ()
forall a (m :: * -> *).
(Integral a, PrimMonad m, Bits a) =>
a -> Int -> MutablePrimArray (PrimState m) Word8 -> Int -> m ()
go a
w (Int
hexSizInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2))
where
bitSiz :: Int
bitSiz = a -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (a
forall a. HasCallStack => a
undefined :: a)
hexSiz :: Int
hexSiz = (Int
bitSizInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
3) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
2
go :: a -> Int -> MutablePrimArray (PrimState m) Word8 -> Int -> m ()
go !a
v !Int
d MutablePrimArray (PrimState m) Word8
marr Int
off
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = do
let !i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xFF; !j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d) (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTable Int
j
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTable (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
a -> Int -> MutablePrimArray (PrimState m) Word8 -> Int -> m ()
go (a
v a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
8) (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2) MutablePrimArray (PrimState m) Word8
marr Int
off
| Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = do
let !i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xFF; !j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr Int
off (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTable Int
j
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTable (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = do
let !i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x0F :: Int
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr Int
off (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Int -> Word8
forall a. Integral a => a -> Word8
i2wHex Int
i
heX :: forall a. (FiniteBits a, Integral a) => a -> Builder ()
{-# SPECIALIZE INLINE heX :: Int -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Int8 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Int16 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Int32 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Int64 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Word -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Word8 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Word16 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Word32 -> Builder () #-}
{-# SPECIALIZE INLINE heX :: Word64 -> Builder () #-}
heX :: a -> Builder ()
heX a
w = Int
-> (forall s. MutablePrimArray s Word8 -> Int -> ST s ())
-> Builder ()
writeN Int
hexSiz (a
-> Int
-> MutablePrimArray (PrimState (ST s)) Word8
-> Int
-> ST s ()
forall a (m :: * -> *).
(Integral a, PrimMonad m, Bits a) =>
a -> Int -> MutablePrimArray (PrimState m) Word8 -> Int -> m ()
go a
w (Int
hexSizInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2))
where
bitSiz :: Int
bitSiz = a -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (a
forall a. HasCallStack => a
undefined :: a)
hexSiz :: Int
hexSiz = (Int
bitSizInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
3) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
2
go :: a -> Int -> MutablePrimArray (PrimState m) Word8 -> Int -> m ()
go !a
v !Int
d MutablePrimArray (PrimState m) Word8
marr Int
off
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = do
let !i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xFF; !j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d) (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTableUpper Int
j
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTableUpper (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
a -> Int -> MutablePrimArray (PrimState m) Word8 -> Int -> m ()
go (a
v a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
8) (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2) MutablePrimArray (PrimState m) Word8
marr Int
off
| Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = do
let !i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xFF; !j :: Int
j = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr Int
off (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTableUpper Int
j
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr (Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8
forall a. Prim a => Ptr a -> Int -> a
indexOffPtr Ptr Word8
hexDigitTableUpper (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = do
let !i :: Int
i = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
v Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x0F :: Int
MutablePrimArray (PrimState m) Word8 -> Int -> Word8 -> m ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
writePrimArray MutablePrimArray (PrimState m) Word8
marr Int
off (Word8 -> m ()) -> Word8 -> m ()
forall a b. (a -> b) -> a -> b
$ Int -> Word8
forall a. Integral a => a -> Word8
i2wHeX Int
i
data FFormat = Exponent
| Fixed
| Generic
deriving (Int -> FFormat
FFormat -> Int
FFormat -> [FFormat]
FFormat -> FFormat
FFormat -> FFormat -> [FFormat]
FFormat -> FFormat -> FFormat -> [FFormat]
(FFormat -> FFormat)
-> (FFormat -> FFormat)
-> (Int -> FFormat)
-> (FFormat -> Int)
-> (FFormat -> [FFormat])
-> (FFormat -> FFormat -> [FFormat])
-> (FFormat -> FFormat -> [FFormat])
-> (FFormat -> FFormat -> FFormat -> [FFormat])
-> Enum FFormat
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: FFormat -> FFormat -> FFormat -> [FFormat]
$cenumFromThenTo :: FFormat -> FFormat -> FFormat -> [FFormat]
enumFromTo :: FFormat -> FFormat -> [FFormat]
$cenumFromTo :: FFormat -> FFormat -> [FFormat]
enumFromThen :: FFormat -> FFormat -> [FFormat]
$cenumFromThen :: FFormat -> FFormat -> [FFormat]
enumFrom :: FFormat -> [FFormat]
$cenumFrom :: FFormat -> [FFormat]
fromEnum :: FFormat -> Int
$cfromEnum :: FFormat -> Int
toEnum :: Int -> FFormat
$ctoEnum :: Int -> FFormat
pred :: FFormat -> FFormat
$cpred :: FFormat -> FFormat
succ :: FFormat -> FFormat
$csucc :: FFormat -> FFormat
Enum, ReadPrec [FFormat]
ReadPrec FFormat
Int -> ReadS FFormat
ReadS [FFormat]
(Int -> ReadS FFormat)
-> ReadS [FFormat]
-> ReadPrec FFormat
-> ReadPrec [FFormat]
-> Read FFormat
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FFormat]
$creadListPrec :: ReadPrec [FFormat]
readPrec :: ReadPrec FFormat
$creadPrec :: ReadPrec FFormat
readList :: ReadS [FFormat]
$creadList :: ReadS [FFormat]
readsPrec :: Int -> ReadS FFormat
$creadsPrec :: Int -> ReadS FFormat
Read, Int -> FFormat -> ShowS
[FFormat] -> ShowS
FFormat -> String
(Int -> FFormat -> ShowS)
-> (FFormat -> String) -> ([FFormat] -> ShowS) -> Show FFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FFormat] -> ShowS
$cshowList :: [FFormat] -> ShowS
show :: FFormat -> String
$cshow :: FFormat -> String
showsPrec :: Int -> FFormat -> ShowS
$cshowsPrec :: Int -> FFormat -> ShowS
Show)
float :: Float -> Builder ()
{-# INLINE float #-}
float :: Float -> Builder ()
float = FFormat -> Maybe Int -> Float -> Builder ()
floatWith FFormat
Generic Maybe Int
forall k1. Maybe k1
Nothing
double :: Double -> Builder ()
{-# INLINE double #-}
double :: Double -> Builder ()
double = FFormat -> Maybe Int -> Double -> Builder ()
doubleWith FFormat
Generic Maybe Int
forall k1. Maybe k1
Nothing
floatWith :: FFormat
-> Maybe Int
-> Float
-> Builder ()
{-# INLINE floatWith #-}
floatWith :: FFormat -> Maybe Int -> Float -> Builder ()
floatWith FFormat
fmt Maybe Int
decs Float
x
| Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
x = Builder ()
"NaN"
| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
x = if Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0 then Builder ()
"-Infinity" else Builder ()
"Infinity"
| Float
x Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0 = Char -> Builder ()
char8 Char
'-' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs (Float -> ([Int], Int)
grisu3_sp (-Float
x))
| Float -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero Float
x = Char -> Builder ()
char8 Char
'-' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs ([Int
0], Int
0)
| Float
x Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0 = FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs ([Int
0], Int
0)
| Bool
otherwise = FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs (Float -> ([Int], Int)
grisu3_sp Float
x)
doubleWith :: FFormat
-> Maybe Int
-> Double
-> Builder ()
{-# INLINE doubleWith #-}
doubleWith :: FFormat -> Maybe Int -> Double -> Builder ()
doubleWith FFormat
fmt Maybe Int
decs Double
x
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
x = Builder ()
"NaN"
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
x = if Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 then Builder ()
"-Infinity" else Builder ()
"Infinity"
| Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = Char -> Builder ()
char8 Char
'-' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs (Double -> ([Int], Int)
grisu3 (-Double
x))
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero Double
x = Char -> Builder ()
char8 Char
'-' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs ([Int
0], Int
0)
| Double
x Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs ([Int
0], Int
0)
| Bool
otherwise = FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs (Double -> ([Int], Int)
grisu3 Double
x)
doFmt :: FFormat
-> Maybe Int
-> ([Int], Int)
-> Builder ()
{-# INLINABLE doFmt #-}
doFmt :: FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
format Maybe Int
decs ([Int]
is, Int
e) =
let ds :: String
ds = (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
forall a. Integral a => a -> Char
i2cDec [Int]
is
in case FFormat
format of
FFormat
Generic ->
FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt (if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
7 then FFormat
Exponent else FFormat
Fixed) Maybe Int
decs ([Int]
is,Int
e)
FFormat
Exponent ->
case Maybe Int
decs of
Maybe Int
Nothing ->
let show_e' :: Builder ()
show_e' = Int -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
int (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
in case String
ds of
String
"0" -> Builder ()
"0.0e0"
[Char
d] -> Char -> Builder ()
char8 Char
d Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
".0e" Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
show_e'
(Char
d:String
ds') -> Char -> Builder ()
char8 Char
d Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
char8 Char
'.' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
String -> Builder ()
string8 String
ds' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
char8 Char
'e' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Builder ()
show_e'
[] -> String -> Builder ()
forall a. HasCallStack => String -> a
error String
"doFmt/Exponent: []"
Just Int
dec
| Int
dec Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 ->
case [Int]
is of
[Int
0] -> Builder ()
"0e0"
[Int]
_ -> do
let (Int
ei,[Int]
is') = Int -> Int -> [Int] -> (Int, [Int])
roundTo Int
10 Int
1 [Int]
is
Char
n:String
_ = (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
forall a. Integral a => a -> Char
i2cDec (if Int
ei Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then [Int] -> [Int]
forall a. [a] -> [a]
init [Int]
is' else [Int]
is')
Char -> Builder ()
char8 Char
n
Char -> Builder ()
char8 Char
'e'
Int -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
int (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ei)
Just Int
dec ->
let dec' :: Int
dec' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
dec Int
1 in
case [Int]
is of
[Int
0] -> do
Char -> Builder ()
char8 Char
'0'
Char -> Builder ()
char8 Char
'.'
Int -> Builder () -> Builder ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
dec' (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Char -> Builder ()
char8 Char
'0'
Char -> Builder ()
char8 Char
'e'
Char -> Builder ()
char8 Char
'0'
[Int]
_ -> do
let (Int
ei,[Int]
is') = Int -> Int -> [Int] -> (Int, [Int])
roundTo Int
10 (Int
dec'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [Int]
is
(Char
d:String
ds') = (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
forall a. Integral a => a -> Char
i2cDec (if Int
ei Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then [Int] -> [Int]
forall a. [a] -> [a]
init [Int]
is' else [Int]
is')
Char -> Builder ()
char8 Char
d
Char -> Builder ()
char8 Char
'.'
String -> Builder ()
string8 String
ds'
Char -> Builder ()
char8 Char
'e'
Int -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
int (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ei)
FFormat
Fixed ->
let mk0 :: String -> Builder ()
mk0 String
ls = case String
ls of { String
"" -> Char -> Builder ()
char8 Char
'0' ; String
_ -> String -> Builder ()
string8 String
ls}
in case Maybe Int
decs of
Maybe Int
Nothing
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> do
Char -> Builder ()
char8 Char
'0'
Char -> Builder ()
char8 Char
'.'
Int -> Builder () -> Builder ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ (-Int
e) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Char -> Builder ()
char8 Char
'0'
String -> Builder ()
string8 String
ds
| Bool
otherwise ->
let f :: a -> String -> String -> Builder ()
f a
0 String
s String
rs = String -> Builder ()
mk0 (ShowS
forall a. [a] -> [a]
reverse String
s) Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> Builder ()
char8 Char
'.' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Builder ()
mk0 String
rs
f a
n String
s String
"" = a -> String -> String -> Builder ()
f (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1) (Char
'0'Char -> ShowS
forall k1. k1 -> [k1] -> [k1]
:String
s) String
""
f a
n String
s (Char
r:String
rs) = a -> String -> String -> Builder ()
f (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1) (Char
rChar -> ShowS
forall k1. k1 -> [k1] -> [k1]
:String
s) String
rs
in Int -> String -> String -> Builder ()
forall a. (Eq a, Num a) => a -> String -> String -> Builder ()
f Int
e String
"" String
ds
Just Int
dec ->
let dec' :: Int
dec' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
dec Int
0
in if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
then
let (Int
ei,[Int]
is') = Int -> Int -> [Int] -> (Int, [Int])
roundTo Int
10 (Int
dec' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e) [Int]
is
(String
ls,String
rs) = Int -> String -> (String, String)
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ei) ((Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
forall a. Integral a => a -> Char
i2cDec [Int]
is')
in String -> Builder ()
mk0 String
ls Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(Bool -> Builder () -> Builder ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
List.null String
rs) (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Char -> Builder ()
char8 Char
'.' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Builder ()
string8 String
rs)
else
let (Int
ei,[Int]
is') = Int -> Int -> [Int] -> (Int, [Int])
roundTo Int
10 Int
dec' (Int -> Int -> [Int]
forall a. Int -> a -> [a]
List.replicate (-Int
e) Int
0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int]
is)
Char
d:String
ds' = (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
forall a. Integral a => a -> Char
i2cDec (if Int
ei Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then [Int]
is' else Int
0Int -> [Int] -> [Int]
forall k1. k1 -> [k1] -> [k1]
:[Int]
is')
in Char -> Builder ()
char8 Char
d Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(Bool -> Builder () -> Builder ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
List.null String
ds') (Builder () -> Builder ()) -> Builder () -> Builder ()
forall a b. (a -> b) -> a -> b
$ Char -> Builder ()
char8 Char
'.' Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Builder ()
string8 String
ds')
#define GRISU3_SINGLE_BUF_LEN 10
#define GRISU3_DOUBLE_BUF_LEN 18
foreign import ccall unsafe "static grisu3" c_grisu3
:: Double
-> MBA# Word8
-> MBA# Int
-> MBA# Int
-> IO Int
grisu3 :: Double -> ([Int], Int)
{-# INLINE grisu3 #-}
grisu3 :: Double -> ([Int], Int)
grisu3 Double
d = IO ([Int], Int) -> ([Int], Int)
forall a. IO a -> a
unsafePerformIO (IO ([Int], Int) -> ([Int], Int))
-> IO ([Int], Int) -> ([Int], Int)
forall a b. (a -> b) -> a -> b
$
Int -> (MBA# Word8 -> IO ([Int], Int)) -> IO ([Int], Int)
forall a b. Int -> (MBA# Word8 -> IO b) -> IO b
allocMutableByteArrayUnsafe GRISU3_DOUBLE_BUF_LEN $ \ pBuf -> do
(len, (e, success)) <- allocPrimUnsafe $ \ pLen ->
allocPrimUnsafe $ \ pE ->
c_grisu3 (realToFrac d) pBuf pLen pE
if success == 0
then pure (floatToDigits 10 d)
else do
buf <- forM [0..len-1] $ \ i -> do
w8 <- readByteArray (MutableByteArray pBuf) i :: IO Word8
pure $! fromIntegral w8
let !e' = e + len
pure (buf, e')
foreign import ccall unsafe "static grisu3_sp" c_grisu3_sp
:: Float
-> MBA# Word8
-> MBA# Int
-> MBA# Int
-> IO Int
grisu3_sp :: Float -> ([Int], Int)
{-# INLINE grisu3_sp #-}
grisu3_sp :: Float -> ([Int], Int)
grisu3_sp Float
d = IO ([Int], Int) -> ([Int], Int)
forall a. IO a -> a
unsafePerformIO (IO ([Int], Int) -> ([Int], Int))
-> IO ([Int], Int) -> ([Int], Int)
forall a b. (a -> b) -> a -> b
$
Int -> (MBA# Word8 -> IO ([Int], Int)) -> IO ([Int], Int)
forall a b. Int -> (MBA# Word8 -> IO b) -> IO b
allocMutableByteArrayUnsafe GRISU3_SINGLE_BUF_LEN $ \ pBuf -> do
(len, (e, success)) <- allocPrimUnsafe $ \ pLen ->
allocPrimUnsafe $ \ pE ->
c_grisu3_sp (realToFrac d) pBuf pLen pE
if success == 0
then pure (floatToDigits 10 d)
else do
buf <- forM [0..len-1] $ \ i -> do
w8 <- readByteArray (MutableByteArray pBuf) i :: IO Word8
pure $! fromIntegral w8
let !e' = e + len
pure (buf, e')
scientific :: Sci.Scientific -> Builder ()
{-# INLINE scientific #-}
scientific :: Scientific -> Builder ()
scientific = FFormat -> Maybe Int -> Scientific -> Builder ()
scientificWith FFormat
Generic Maybe Int
forall k1. Maybe k1
Nothing
scientificWith :: FFormat
-> Maybe Int
-> Sci.Scientific
-> Builder ()
{-# INLINE scientificWith #-}
scientificWith :: FFormat -> Maybe Int -> Scientific -> Builder ()
scientificWith FFormat
fmt Maybe Int
decs Scientific
scntfc
| Scientific
scntfc Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
< Scientific
0 = Char -> Builder ()
char8 Char
'-' Builder () -> Builder () -> Builder ()
forall a. Semigroup a => a -> a -> a
<> FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs (Scientific -> ([Int], Int)
Sci.toDecimalDigits (-Scientific
scntfc))
| Bool
otherwise = FFormat -> Maybe Int -> ([Int], Int) -> Builder ()
doFmt FFormat
fmt Maybe Int
decs (Scientific -> ([Int], Int)
Sci.toDecimalDigits Scientific
scntfc)