{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE CPP #-}
module Z.Data.Parser.Numeric
(
uint, int
, hex
, rational
, float, double
, scientific
, scientifically
, rational'
, float', double'
, scientific'
, scientifically'
, hexLoop
, decLoop
, decLoopIntegerFast
, isHexDigit
, isDigit
, floatToScientific
, doubleToScientific
) where
import Control.Applicative
import Control.Monad
import Data.Bits
import Data.Int
import qualified Data.Scientific as Sci
import Data.Word
import Foreign.Ptr (IntPtr)
import qualified Z.Data.Builder.Numeric as B
import Z.Data.Parser.Base (Parser, (<?>))
import qualified Z.Data.Parser.Base as P
import qualified Z.Data.Vector.Base as V
import qualified Z.Data.Vector.Extra as V
#define WORD64_MAX_DIGITS_LEN 18
#define PLUS 43
#define MINUS 45
#define DOT 46
#define LITTLE_E 101
#define BIG_E 69
#define C_0 48
hex :: (Integral a, Bits a) => Parser a
{-# INLINE hex #-}
{-# SPECIALIZE INLINE hex :: Parser Int #-}
{-# SPECIALIZE INLINE hex :: Parser Int64 #-}
{-# SPECIALIZE INLINE hex :: Parser Int32 #-}
{-# SPECIALIZE INLINE hex :: Parser Int16 #-}
{-# SPECIALIZE INLINE hex :: Parser Int8 #-}
{-# SPECIALIZE INLINE hex :: Parser Word #-}
{-# SPECIALIZE INLINE hex :: Parser Word64 #-}
{-# SPECIALIZE INLINE hex :: Parser Word32 #-}
{-# SPECIALIZE INLINE hex :: Parser Word16 #-}
{-# SPECIALIZE INLINE hex :: Parser Word8 #-}
{-# SPECIALIZE INLINE hex :: Parser Integer #-}
{-# SPECIALIZE INLINE hex :: Parser IntPtr #-}
hex :: Parser a
hex = Text
"Z.Data.Parser.Numeric.hex" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> a -> Bytes -> a
forall a. (Integral a, Bits a) => a -> Bytes -> a
hexLoop a
0 (Bytes -> a) -> Parser Bytes -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Bool) -> Parser Bytes
P.takeWhile1 Word8 -> Bool
isHexDigit
hexLoop :: (Integral a, Bits a)
=> a
-> V.Bytes
-> a
{-# INLINE hexLoop #-}
hexLoop :: a -> Bytes -> a
hexLoop = (a -> Word8 -> a) -> a -> Bytes -> a
forall (v :: * -> *) a b. Vec v a => (b -> a -> b) -> b -> v a -> b
V.foldl' a -> Word8 -> a
forall a a. (Bits a, Integral a, Num a) => a -> a -> a
step
where
step :: a -> a -> a
step a
a a
w = a
a a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
4 a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> a
forall a. (Ord a, Num a) => a -> a
w2iHex a
w)
w2iHex :: a -> a
w2iHex a
w
| a
w a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
57 = a
w a -> a -> a
forall a. Num a => a -> a -> a
- a
48
| a
w a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
70 = a
w a -> a -> a
forall a. Num a => a -> a -> a
- a
55
| a
w a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
102 = a
w a -> a -> a
forall a. Num a => a -> a -> a
- a
87
isHexDigit :: Word8 -> Bool
{-# INLINE isHexDigit #-}
isHexDigit :: Word8 -> Bool
isHexDigit Word8
w = Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
48 Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
9 Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
65 Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
5 Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
97 Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
5
uint :: (Integral a) => Parser a
{-# INLINE uint #-}
{-# SPECIALIZE INLINE uint :: Parser Int #-}
{-# SPECIALIZE INLINE uint :: Parser Int64 #-}
{-# SPECIALIZE INLINE uint :: Parser Int32 #-}
{-# SPECIALIZE INLINE uint :: Parser Int16 #-}
{-# SPECIALIZE INLINE uint :: Parser Int8 #-}
{-# SPECIALIZE INLINE uint :: Parser Word #-}
{-# SPECIALIZE INLINE uint :: Parser Word64 #-}
{-# SPECIALIZE INLINE uint :: Parser Word32 #-}
{-# SPECIALIZE INLINE uint :: Parser Word16 #-}
{-# SPECIALIZE INLINE uint :: Parser Word8 #-}
{-# SPECIALIZE INLINE uint :: Parser Integer #-}
uint :: Parser a
uint = Text
"Z.Data.Parser.Numeric.uint" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> a -> Bytes -> a
forall a. Integral a => a -> Bytes -> a
decLoop a
0 (Bytes -> a) -> Parser Bytes -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Bool) -> Parser Bytes
P.takeWhile1 Word8 -> Bool
isDigit
decLoop :: Integral a
=> a
-> V.Bytes
-> a
{-# INLINE decLoop #-}
decLoop :: a -> Bytes -> a
decLoop = (a -> Word8 -> a) -> a -> Bytes -> a
forall (v :: * -> *) a b. Vec v a => (b -> a -> b) -> b -> v a -> b
V.foldl' a -> Word8 -> a
forall a a. (Integral a, Num a) => a -> a -> a
step
where step :: a -> a -> a
step a
a a
w = a
a a -> a -> a
forall a. Num a => a -> a -> a
* a
10 a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a
w a -> a -> a
forall a. Num a => a -> a -> a
- a
48)
decLoopIntegerFast :: V.Bytes -> Integer
{-# INLINE decLoopIntegerFast #-}
decLoopIntegerFast :: Bytes -> Integer
decLoopIntegerFast Bytes
bs
| Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
bs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= WORD64_MAX_DIGITS_LEN = fromIntegral (decLoop @Word64 0 bs)
| Bool
otherwise = Integer -> Bytes -> Integer
forall a. Integral a => a -> Bytes -> a
decLoop @Integer Integer
0 Bytes
bs
isDigit :: Word8 -> Bool
isDigit :: Word8 -> Bool
isDigit Word8
w = Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
48 Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
9
{-# INLINE isDigit #-}
int :: (Integral a) => Parser a
{-# INLINE int #-}
{-# SPECIALIZE INLINE int :: Parser Int #-}
{-# SPECIALIZE INLINE int :: Parser Int64 #-}
{-# SPECIALIZE INLINE int :: Parser Int32 #-}
{-# SPECIALIZE INLINE int :: Parser Int16 #-}
{-# SPECIALIZE INLINE int :: Parser Int8 #-}
{-# SPECIALIZE INLINE int :: Parser Word #-}
{-# SPECIALIZE INLINE int :: Parser Word64 #-}
{-# SPECIALIZE INLINE int :: Parser Word32 #-}
{-# SPECIALIZE INLINE int :: Parser Word16 #-}
{-# SPECIALIZE INLINE int :: Parser Word8 #-}
{-# SPECIALIZE INLINE int :: Parser Integer #-}
int :: Parser a
int = Text
"Z.Data.Parser.Numeric.int" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> do
Word8
w <- Parser Word8
P.peek
if Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== MINUS
then Parser ()
P.skipWord8 Parser () -> Parser a -> Parser a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (a -> a
forall a. Num a => a -> a
negate (a -> a) -> Parser a -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser a
uint')
else if Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== PLUS then P.skipWord8 *> uint' else uint'
where
uint' :: Parser a
uint' = a -> Bytes -> a
forall a. Integral a => a -> Bytes -> a
decLoop a
0 (Bytes -> a) -> Parser Bytes -> Parser a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Bool) -> Parser Bytes
P.takeWhile1 Word8 -> Bool
isDigit
rational :: (Fractional a) => Parser a
{-# INLINE rational #-}
rational :: Parser a
rational = Text
"Z.Data.Parser.Numeric.rational" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> a) -> Parser a
forall a. (Scientific -> a) -> Parser a
scientificallyInternal Scientific -> a
forall a b. (Real a, Fractional b) => a -> b
realToFrac
double :: Parser Double
{-# INLINE double #-}
double :: Parser Double
double = Text
"Z.Data.Parser.Numeric.double" Text -> Parser Double -> Parser Double
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> Double) -> Parser Double
forall a. (Scientific -> a) -> Parser a
scientificallyInternal Scientific -> Double
forall a. RealFloat a => Scientific -> a
Sci.toRealFloat
float :: Parser Float
{-# INLINE float #-}
float :: Parser Float
float = Text
"Z.Data.Parser.Numeric.float" Text -> Parser Float -> Parser Float
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> Float) -> Parser Float
forall a. (Scientific -> a) -> Parser a
scientificallyInternal Scientific -> Float
forall a. RealFloat a => Scientific -> a
Sci.toRealFloat
scientific :: Parser Sci.Scientific
{-# INLINE scientific #-}
scientific :: Parser Scientific
scientific = Text
"Z.Data.Parser.Numeric.scientific" Text -> Parser Scientific -> Parser Scientific
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> Scientific) -> Parser Scientific
forall a. (Scientific -> a) -> Parser a
scientificallyInternal Scientific -> Scientific
forall a. a -> a
id
scientifically :: (Sci.Scientific -> a) -> Parser a
{-# INLINE scientifically #-}
scientifically :: (Scientific -> a) -> Parser a
scientifically Scientific -> a
h = Text
"Z.Data.Parser.Numeric.scientifically" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> a) -> Parser a
forall a. (Scientific -> a) -> Parser a
scientificallyInternal Scientific -> a
h
scientificallyInternal :: (Sci.Scientific -> a) -> Parser a
{-# INLINE scientificallyInternal #-}
scientificallyInternal :: (Scientific -> a) -> Parser a
scientificallyInternal Scientific -> a
h = do
!Word8
sign <- Parser Word8
P.peek
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word8
sign Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== PLUS || sign == MINUS) (P.skipWord8)
!Bytes
intPart <- (Word8 -> Bool) -> Parser Bytes
P.takeWhile1 Word8 -> Bool
isDigit
!Scientific
sci <- (do
!Bytes
fracPart <- Word8 -> Parser ()
P.word8 DOT *> P.takeWhile1 isDigit
let !ilen :: Int
ilen = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
intPart
!flen :: Int
flen = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
fracPart
!base :: Integer
base =
if Int
ilen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
flen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= WORD64_MAX_DIGITS_LEN
then Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Bytes -> Word64
forall a. Integral a => a -> Bytes -> a
decLoop @Word64 (Word64 -> Bytes -> Word64
forall a. Integral a => a -> Bytes -> a
decLoop @Word64 Word64
0 Bytes
intPart) Bytes
fracPart)
else
let i :: Integer
i = Bytes -> Integer
decLoopIntegerFast Bytes
intPart
f :: Integer
f = Bytes -> Integer
decLoopIntegerFast Bytes
fracPart
in Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
flen Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
f
Integer -> Int -> Parser Scientific
parseE Integer
base Int
flen) Parser Scientific -> Parser Scientific -> Parser Scientific
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Integer -> Int -> Parser Scientific
parseE (Bytes -> Integer
decLoopIntegerFast Bytes
intPart) Int
0)
a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Parser a) -> a -> Parser a
forall a b. (a -> b) -> a -> b
$! if Word8
sign Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= MINUS then h sci else h (negate sci)
where
{-# INLINE parseE #-}
parseE :: Integer -> Int -> Parser Scientific
parseE Integer
c Int
e =
(do Word8
_ <- (Word8 -> Bool) -> Parser Word8
P.satisfy (\Word8
w -> Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== LITTLE_E || w == BIG_E)
Integer -> Int -> Scientific
Sci.scientific Integer
c (Int -> Scientific) -> (Int -> Int) -> Int -> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
e (Int -> Scientific) -> Parser Int -> Parser Scientific
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Int
forall a. Integral a => Parser a
int) Parser Scientific -> Parser Scientific -> Parser Scientific
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Scientific -> Parser Scientific
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> Int -> Scientific
Sci.scientific Integer
c (Int -> Int
forall a. Num a => a -> a
negate Int
e))
rational' :: (Fractional a) => Parser a
{-# INLINE rational' #-}
rational' :: Parser a
rational' = Text
"Z.Data.Parser.Numeric.rational'" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> a) -> Parser a
forall a. (Scientific -> a) -> Parser a
scientificallyInternal' Scientific -> a
forall a b. (Real a, Fractional b) => a -> b
realToFrac
double' :: Parser Double
{-# INLINE double' #-}
double' :: Parser Double
double' = Text
"Z.Data.Parser.Numeric.double'" Text -> Parser Double -> Parser Double
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> Double) -> Parser Double
forall a. (Scientific -> a) -> Parser a
scientificallyInternal' Scientific -> Double
forall a. RealFloat a => Scientific -> a
Sci.toRealFloat
float' :: Parser Float
{-# INLINE float' #-}
float' :: Parser Float
float' = Text
"Z.Data.Parser.Numeric.float'" Text -> Parser Float -> Parser Float
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> Float) -> Parser Float
forall a. (Scientific -> a) -> Parser a
scientificallyInternal' Scientific -> Float
forall a. RealFloat a => Scientific -> a
Sci.toRealFloat
scientific' :: Parser Sci.Scientific
{-# INLINE scientific' #-}
scientific' :: Parser Scientific
scientific' = Text
"Z.Data.Parser.Numeric.scientific'" Text -> Parser Scientific -> Parser Scientific
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> Scientific) -> Parser Scientific
forall a. (Scientific -> a) -> Parser a
scientificallyInternal' Scientific -> Scientific
forall a. a -> a
id
scientifically' :: (Sci.Scientific -> a) -> P.Parser a
{-# INLINE scientifically' #-}
scientifically' :: (Scientific -> a) -> Parser a
scientifically' Scientific -> a
h = Text
"Z.Data.Parser.Numeric.scientifically'" Text -> Parser a -> Parser a
forall a. Text -> Parser a -> Parser a
<?> (Scientific -> a) -> Parser a
forall a. (Scientific -> a) -> Parser a
scientificallyInternal' Scientific -> a
h
scientificallyInternal' :: (Sci.Scientific -> a) -> P.Parser a
{-# INLINE scientificallyInternal' #-}
scientificallyInternal' :: (Scientific -> a) -> Parser a
scientificallyInternal' Scientific -> a
h = do
!Word8
sign <- Parser Word8
P.peek
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word8
sign Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== MINUS) (P.skipWord8)
!Bytes
intPart <- (Word8 -> Bool) -> Parser Bytes
P.takeWhile1 Word8 -> Bool
isDigit
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
intPart Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 Bool -> Bool -> Bool
&& Bytes -> Word8
forall (v :: * -> *) a. (Vec v a, HasCallStack) => v a -> a
V.head Bytes
intPart Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== C_0) (fail "leading zeros are not allowed")
Maybe Word8
mdot <- Parser (Maybe Word8)
P.peekMaybe
!Scientific
sci <- case Maybe Word8
mdot of
Just DOT -> do
!Bytes
fracPart <- Parser ()
P.skipWord8 Parser () -> Parser Bytes -> Parser Bytes
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Word8 -> Bool) -> Parser Bytes
P.takeWhile1 Word8 -> Bool
isDigit
let !ilen :: Int
ilen = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
intPart
!flen :: Int
flen = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
fracPart
!base :: Integer
base =
if Int
ilen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
flen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= WORD64_MAX_DIGITS_LEN
then Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Bytes -> Word64
forall a. Integral a => a -> Bytes -> a
decLoop @Word64 (Word64 -> Bytes -> Word64
forall a. Integral a => a -> Bytes -> a
decLoop @Word64 Word64
0 Bytes
intPart) Bytes
fracPart)
else
let i :: Integer
i = Bytes -> Integer
decLoopIntegerFast Bytes
intPart
f :: Integer
f = Bytes -> Integer
decLoopIntegerFast Bytes
fracPart
in Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
flen Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
f
Integer -> Int -> Parser Scientific
parseE Integer
base Int
flen
Maybe Word8
_ -> Integer -> Int -> Parser Scientific
parseE (Bytes -> Integer
decLoopIntegerFast Bytes
intPart) Int
0
a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Parser a) -> a -> Parser a
forall a b. (a -> b) -> a -> b
$! if Word8
sign Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= MINUS then h sci else h (negate sci)
where
{-# INLINE parseE #-}
parseE :: Integer -> Int -> Parser Scientific
parseE !Integer
c !Int
e = do
Maybe Word8
me <- Parser (Maybe Word8)
P.peekMaybe
Int
e' <- case Maybe Word8
me of
Just Word8
ec | Word8
ec Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== LITTLE_E || ec == BIG_E -> P.skipWord8 *> int
Maybe Word8
_ -> Int -> Parser Int
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
0
Scientific -> Parser Scientific
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Scientific -> Parser Scientific)
-> Scientific -> Parser Scientific
forall a b. (a -> b) -> a -> b
$! Integer -> Int -> Scientific
Sci.scientific Integer
c (Int
e' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e)
floatToScientific :: Float -> Sci.Scientific
{-# INLINE floatToScientific #-}
floatToScientific :: Float -> Scientific
floatToScientific Float
rf | Float
rf Float -> Float -> Bool
forall a. Ord a => a -> a -> Bool
< Float
0 = -(([Int], Int) -> Scientific
fromFloatingDigits (Float -> ([Int], Int)
B.grisu3_sp (-Float
rf)))
| Float
rf Float -> Float -> Bool
forall a. Eq a => a -> a -> Bool
== Float
0 = Scientific
0
| Bool
otherwise = ([Int], Int) -> Scientific
fromFloatingDigits (Float -> ([Int], Int)
B.grisu3_sp Float
rf)
doubleToScientific :: Double -> Sci.Scientific
{-# INLINE doubleToScientific #-}
doubleToScientific :: Double -> Scientific
doubleToScientific Double
rf | Double
rf Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 = -(([Int], Int) -> Scientific
fromFloatingDigits (Double -> ([Int], Int)
B.grisu3 (-Double
rf)))
| Double
rf Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 = Scientific
0
| Bool
otherwise = ([Int], Int) -> Scientific
fromFloatingDigits (Double -> ([Int], Int)
B.grisu3 Double
rf)
fromFloatingDigits :: ([Int], Int) -> Sci.Scientific
{-# INLINE fromFloatingDigits #-}
fromFloatingDigits :: ([Int], Int) -> Scientific
fromFloatingDigits ([Int]
digits, Int
e) = [Int] -> Int64 -> Int -> Scientific
go [Int]
digits Int64
0 Int
0
where
go :: [Int] -> Int64 -> Int -> Sci.Scientific
go :: [Int] -> Int64 -> Int -> Scientific
go [] !Int64
c !Int
n = Integer -> Int -> Scientific
Sci.scientific (Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
c) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
go (Int
d:[Int]
ds) !Int64
c !Int
n = [Int] -> Int64 -> Int -> Scientific
go [Int]
ds (Int64
c Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
10 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
d) (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)