module Data.Csv.Conversion.Internal
( decimal
, scientific
, realFloat
) where
import Data.ByteString.Builder (Builder, toLazyByteString, word8, char8,
string8, byteString)
import qualified Data.ByteString.Builder.Prim as BP
import Data.ByteString.Builder.Scientific (scientificBuilder)
import Data.Array.Base (unsafeAt)
import Data.Array.IArray
import qualified Data.ByteString as B
import Data.Char (ord)
import Data.Int
import qualified Data.Monoid as Mon
import Data.Scientific (Scientific)
import Data.Word
import Data.Csv.Util (toStrict)
decimal :: Integral a => a -> B.ByteString
decimal :: forall a. Integral a => a -> ByteString
decimal = LazyByteString -> ByteString
toStrict (LazyByteString -> ByteString)
-> (a -> LazyByteString) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyByteString
toLazyByteString (Builder -> LazyByteString)
-> (a -> Builder) -> a -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. Integral a => a -> Builder
formatDecimal
{-# INLINE decimal #-}
formatDecimal :: Integral a => a -> Builder
{-# RULES "formatDecimal/Int" formatDecimal = formatBoundedSigned
:: Int -> Builder #-}
{-# RULES "formatDecimal/Int8" formatDecimal = formatBoundedSigned
:: Int8 -> Builder #-}
{-# RULES "formatDecimal/Int16" formatDecimal = formatBoundedSigned
:: Int16 -> Builder #-}
{-# RULES "formatDecimal/Int32" formatDecimal = formatBoundedSigned
:: Int32 -> Builder #-}
{-# RULES "formatDecimal/Int64" formatDecimal = formatBoundedSigned
:: Int64 -> Builder #-}
{-# RULES "formatDecimal/Word" formatDecimal = formatPositive
:: Word -> Builder #-}
{-# RULES "formatDecimal/Word8" formatDecimal = formatPositive
:: Word8 -> Builder #-}
{-# RULES "formatDecimal/Word16" formatDecimal = formatPositive
:: Word16 -> Builder #-}
{-# RULES "formatDecimal/Word32" formatDecimal = formatPositive
:: Word32 -> Builder #-}
{-# RULES "formatDecimal/Word64" formatDecimal = formatPositive
:: Word64 -> Builder #-}
{-# NOINLINE formatDecimal #-}
formatDecimal :: forall a. Integral a => a -> Builder
formatDecimal a
i
| a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = Builder
minus Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<>
if a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= -a
128
then a -> Builder
forall a. Integral a => a -> Builder
formatPositive (-(a
i a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
10)) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> a -> Builder
forall a. Integral a => a -> Builder
digit (-(a
i a -> a -> a
forall a. Integral a => a -> a -> a
`rem` a
10))
else a -> Builder
forall a. Integral a => a -> Builder
formatPositive (-a
i)
| Bool
otherwise = a -> Builder
forall a. Integral a => a -> Builder
formatPositive a
i
formatBoundedSigned :: (Integral a, Bounded a) => a -> Builder
{-# SPECIALIZE formatBoundedSigned :: Int -> Builder #-}
{-# SPECIALIZE formatBoundedSigned :: Int8 -> Builder #-}
{-# SPECIALIZE formatBoundedSigned :: Int16 -> Builder #-}
{-# SPECIALIZE formatBoundedSigned :: Int32 -> Builder #-}
{-# SPECIALIZE formatBoundedSigned :: Int64 -> Builder #-}
formatBoundedSigned :: forall a. (Integral a, Bounded a) => a -> Builder
formatBoundedSigned a
i
| a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = Builder
minus Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<>
if a
i a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
forall a. Bounded a => a
minBound
then a -> Builder
forall a. Integral a => a -> Builder
formatPositive (-(a
i a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
10)) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> a -> Builder
forall a. Integral a => a -> Builder
digit (-(a
i a -> a -> a
forall a. Integral a => a -> a -> a
`rem` a
10))
else a -> Builder
forall a. Integral a => a -> Builder
formatPositive (-a
i)
| Bool
otherwise = a -> Builder
forall a. Integral a => a -> Builder
formatPositive a
i
formatPositive :: Integral a => a -> Builder
{-# SPECIALIZE formatPositive :: Int -> Builder #-}
{-# SPECIALIZE formatPositive :: Int8 -> Builder #-}
{-# SPECIALIZE formatPositive :: Int16 -> Builder #-}
{-# SPECIALIZE formatPositive :: Int32 -> Builder #-}
{-# SPECIALIZE formatPositive :: Int64 -> Builder #-}
{-# SPECIALIZE formatPositive :: Word -> Builder #-}
{-# SPECIALIZE formatPositive :: Word8 -> Builder #-}
{-# SPECIALIZE formatPositive :: Word16 -> Builder #-}
{-# SPECIALIZE formatPositive :: Word32 -> Builder #-}
{-# SPECIALIZE formatPositive :: Word64 -> Builder #-}
formatPositive :: forall a. Integral a => a -> Builder
formatPositive = a -> Builder
forall a. Integral a => a -> Builder
go
where go :: a -> Builder
go a
n | a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
10 = a -> Builder
forall a. Integral a => a -> Builder
digit a
n
| Bool
otherwise = a -> Builder
go (a
n a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
10) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> a -> Builder
forall a. Integral a => a -> Builder
digit (a
n a -> a -> a
forall a. Integral a => a -> a -> a
`rem` a
10)
minus :: Builder
minus :: Builder
minus = Word8 -> Builder
word8 Word8
45
zero :: Word8
zero :: Word8
zero = Word8
48
digit :: Integral a => a -> Builder
digit :: forall a. Integral a => a -> Builder
digit a
n = Word8 -> Builder
word8 (Word8 -> Builder) -> Word8 -> Builder
forall a b. (a -> b) -> a -> b
$! Int -> Word8
i2w (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n)
{-# INLINE digit #-}
i2w :: Int -> Word8
i2w :: Int -> Word8
i2w Int
i = Word8
zero Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i
{-# INLINE i2w #-}
scientific :: Scientific -> B.ByteString
scientific :: Scientific -> ByteString
scientific = LazyByteString -> ByteString
toStrict (LazyByteString -> ByteString)
-> (Scientific -> LazyByteString) -> Scientific -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyByteString
toLazyByteString (Builder -> LazyByteString)
-> (Scientific -> Builder) -> Scientific -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Builder
scientificBuilder
{-# INLINE scientific #-}
realFloat :: RealFloat a => a -> B.ByteString
{-# SPECIALIZE realFloat :: Float -> B.ByteString #-}
{-# SPECIALIZE realFloat :: Double -> B.ByteString #-}
realFloat :: forall a. RealFloat a => a -> ByteString
realFloat = LazyByteString -> ByteString
toStrict (LazyByteString -> ByteString)
-> (a -> LazyByteString) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyByteString
toLazyByteString (Builder -> LazyByteString)
-> (a -> Builder) -> a -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FPFormat -> a -> Builder
forall a. RealFloat a => FPFormat -> a -> Builder
formatRealFloat FPFormat
Generic
data FPFormat = Exponent
| Fixed
| Generic
deriving (Int -> FPFormat
FPFormat -> Int
FPFormat -> [FPFormat]
FPFormat -> FPFormat
FPFormat -> FPFormat -> [FPFormat]
FPFormat -> FPFormat -> FPFormat -> [FPFormat]
(FPFormat -> FPFormat)
-> (FPFormat -> FPFormat)
-> (Int -> FPFormat)
-> (FPFormat -> Int)
-> (FPFormat -> [FPFormat])
-> (FPFormat -> FPFormat -> [FPFormat])
-> (FPFormat -> FPFormat -> [FPFormat])
-> (FPFormat -> FPFormat -> FPFormat -> [FPFormat])
-> Enum FPFormat
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FPFormat -> FPFormat
succ :: FPFormat -> FPFormat
$cpred :: FPFormat -> FPFormat
pred :: FPFormat -> FPFormat
$ctoEnum :: Int -> FPFormat
toEnum :: Int -> FPFormat
$cfromEnum :: FPFormat -> Int
fromEnum :: FPFormat -> Int
$cenumFrom :: FPFormat -> [FPFormat]
enumFrom :: FPFormat -> [FPFormat]
$cenumFromThen :: FPFormat -> FPFormat -> [FPFormat]
enumFromThen :: FPFormat -> FPFormat -> [FPFormat]
$cenumFromTo :: FPFormat -> FPFormat -> [FPFormat]
enumFromTo :: FPFormat -> FPFormat -> [FPFormat]
$cenumFromThenTo :: FPFormat -> FPFormat -> FPFormat -> [FPFormat]
enumFromThenTo :: FPFormat -> FPFormat -> FPFormat -> [FPFormat]
Enum, ReadPrec [FPFormat]
ReadPrec FPFormat
Int -> ReadS FPFormat
ReadS [FPFormat]
(Int -> ReadS FPFormat)
-> ReadS [FPFormat]
-> ReadPrec FPFormat
-> ReadPrec [FPFormat]
-> Read FPFormat
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FPFormat
readsPrec :: Int -> ReadS FPFormat
$creadList :: ReadS [FPFormat]
readList :: ReadS [FPFormat]
$creadPrec :: ReadPrec FPFormat
readPrec :: ReadPrec FPFormat
$creadListPrec :: ReadPrec [FPFormat]
readListPrec :: ReadPrec [FPFormat]
Read, Int -> FPFormat -> ShowS
[FPFormat] -> ShowS
FPFormat -> String
(Int -> FPFormat -> ShowS)
-> (FPFormat -> String) -> ([FPFormat] -> ShowS) -> Show FPFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FPFormat -> ShowS
showsPrec :: Int -> FPFormat -> ShowS
$cshow :: FPFormat -> String
show :: FPFormat -> String
$cshowList :: [FPFormat] -> ShowS
showList :: [FPFormat] -> ShowS
Show)
formatRealFloat :: RealFloat a => FPFormat -> a -> Builder
{-# SPECIALIZE formatRealFloat :: FPFormat -> Float -> Builder #-}
{-# SPECIALIZE formatRealFloat :: FPFormat -> Double -> Builder #-}
formatRealFloat :: forall a. RealFloat a => FPFormat -> a -> Builder
formatRealFloat FPFormat
fmt a
x
| a -> Bool
forall a. RealFloat a => a -> Bool
isNaN a
x = String -> Builder
string8 String
"NaN"
| a -> Bool
forall a. RealFloat a => a -> Bool
isInfinite a
x = if a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0
then String -> Builder
string8 String
"-Infinity"
else String -> Builder
string8 String
"Infinity"
| a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
|| a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
x = Builder
minus Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> FPFormat -> ([Int], Int) -> Builder
doFmt FPFormat
fmt (a -> ([Int], Int)
forall a. RealFloat a => a -> ([Int], Int)
floatToDigits (-a
x))
| Bool
otherwise = FPFormat -> ([Int], Int) -> Builder
doFmt FPFormat
fmt (a -> ([Int], Int)
forall a. RealFloat a => a -> ([Int], Int)
floatToDigits a
x)
where
doFmt :: FPFormat -> ([Int], Int) -> Builder
doFmt FPFormat
format ([Int]
is, Int
e) =
let ds :: [Word8]
ds = (Int -> Word8) -> [Int] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Word8
i2d [Int]
is in
case FPFormat
format of
FPFormat
Generic ->
FPFormat -> ([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 FPFormat
Exponent else FPFormat
Fixed)
([Int]
is,Int
e)
FPFormat
Exponent ->
let show_e' :: Builder
show_e' = Int -> Builder
forall a. Integral a => a -> Builder
formatDecimal (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) in
case [Word8]
ds of
[Word8
48] -> String -> Builder
string8 String
"0.0e0"
[Word8
d] -> Word8 -> Builder
word8 Word8
d Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> String -> Builder
string8 String
".0e" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> Builder
show_e'
(Word8
d:[Word8]
ds') -> Word8 -> Builder
word8 Word8
d Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> Char -> Builder
char8 Char
'.' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> [Word8] -> Builder
word8s [Word8]
ds' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<>
Char -> Builder
char8 Char
'e' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> Builder
show_e'
[] -> String -> Builder
forall a. HasCallStack => String -> a
error String
"formatRealFloat/doFmt/Exponent: []"
FPFormat
Fixed
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> String -> Builder
string8 String
"0." Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<>
ByteString -> Builder
byteString (Int -> Word8 -> ByteString
B.replicate (-Int
e) Word8
zero) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<>
[Word8] -> Builder
word8s [Word8]
ds
| Bool
otherwise ->
let
f :: t -> [Word8] -> [Word8] -> Builder
f t
0 [Word8]
s [Word8]
rs = [Word8] -> Builder
mk0 ([Word8] -> [Word8]
forall a. [a] -> [a]
reverse [Word8]
s) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> Char -> Builder
char8 Char
'.' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
Mon.<> [Word8] -> Builder
mk0 [Word8]
rs
f t
n [Word8]
s [] = t -> [Word8] -> [Word8] -> Builder
f (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) (Word8
zeroWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
s) []
f t
n [Word8]
s (Word8
r:[Word8]
rs) = t -> [Word8] -> [Word8] -> Builder
f (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1) (Word8
rWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
s) [Word8]
rs
in
Int -> [Word8] -> [Word8] -> Builder
forall {t}. (Eq t, Num t) => t -> [Word8] -> [Word8] -> Builder
f Int
e [] [Word8]
ds
where mk0 :: [Word8] -> Builder
mk0 [Word8]
ls = case [Word8]
ls of { [] -> Word8 -> Builder
word8 Word8
zero ; [Word8]
_ -> [Word8] -> Builder
word8s [Word8]
ls}
floatToDigits :: (RealFloat a) => a -> ([Int], Int)
{-# SPECIALIZE floatToDigits :: Float -> ([Int], Int) #-}
{-# SPECIALIZE floatToDigits :: Double -> ([Int], Int) #-}
floatToDigits :: forall a. RealFloat a => a -> ([Int], Int)
floatToDigits a
0 = ([Int
0], Int
0)
floatToDigits a
x =
let
(Integer
f0, Int
e0) = a -> (Integer, Int)
forall a. RealFloat a => a -> (Integer, Int)
decodeFloat a
x
(Int
minExp0, Int
_) = a -> (Int, Int)
forall a. RealFloat a => a -> (Int, Int)
floatRange a
x
p :: Int
p = a -> Int
forall a. RealFloat a => a -> Int
floatDigits a
x
b :: Integer
b = a -> Integer
forall a. RealFloat a => a -> Integer
floatRadix a
x
minExp :: Int
minExp = Int
minExp0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
p
(Integer
f, Int
e) =
let n :: Int
n = Int
minExp Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e0 in
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then (Integer
f0 Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` (Integer -> Int -> Integer
expt Integer
b Int
n), Int
e0Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) else (Integer
f0, Int
e0)
(Integer
r, Integer
s, Integer
mUp, Integer
mDn) =
if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then
let be :: Integer
be = Integer -> Int -> Integer
expt Integer
b Int
e in
if Integer
f Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Int -> Integer
expt Integer
b (Int
pInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) then
(Integer
fInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
beInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
bInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer
2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
b, Integer
beInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
b, Integer
be)
else
(Integer
fInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
beInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer
2, Integer
be, Integer
be)
else
if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
minExp Bool -> Bool -> Bool
&& Integer
f Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Int -> Integer
expt Integer
b (Int
pInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) then
(Integer
fInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
bInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer -> Int -> Integer
expt Integer
b (-Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer
b, Integer
1)
else
(Integer
fInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer -> Int -> Integer
expt Integer
b (-Int
e)Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer
1, Integer
1)
k :: Int
k :: Int
k =
let
k0 :: Int
k0 :: Int
k0 =
if Integer
b Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
2 then
let lx :: Int
lx = Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e0
k1 :: Int
k1 = (Int
lx Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8651) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
28738
in if Int
lx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then Int
k1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
k1
else
Float -> Int
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling ((Float -> Float
forall a. Floating a => a -> a
log (Integer -> Float
forall a. Num a => Integer -> a
fromInteger (Integer
fInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1) :: Float) Float -> Float -> Float
forall a. Num a => a -> a -> a
+
Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
e Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float -> Float
forall a. Floating a => a -> a
log (Integer -> Float
forall a. Num a => Integer -> a
fromInteger Integer
b)) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/
Float -> Float
forall a. Floating a => a -> a
log Float
10)
fixup :: Int -> Int
fixup Int
n =
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then
if Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
mUp Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer -> Int -> Integer
expt Integer
10 Int
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
s then Int
n else Int -> Int
fixup (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
else
if Integer -> Int -> Integer
expt Integer
10 (-Int
n) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* (Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
mUp) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
s then Int
n else Int -> Int
fixup (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
in
Int -> Int
fixup Int
k0
gen :: [t] -> t -> t -> t -> t -> [t]
gen [t]
ds t
rn t
sN t
mUpN t
mDnN =
let
(t
dn, t
rn') = (t
rn t -> t -> t
forall a. Num a => a -> a -> a
* t
10) t -> t -> (t, t)
forall a. Integral a => a -> a -> (a, a)
`quotRem` t
sN
mUpN' :: t
mUpN' = t
mUpN t -> t -> t
forall a. Num a => a -> a -> a
* t
10
mDnN' :: t
mDnN' = t
mDnN t -> t -> t
forall a. Num a => a -> a -> a
* t
10
in
case (t
rn' t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< t
mDnN', t
rn' t -> t -> t
forall a. Num a => a -> a -> a
+ t
mUpN' t -> t -> Bool
forall a. Ord a => a -> a -> Bool
> t
sN) of
(Bool
True, Bool
False) -> t
dn t -> [t] -> [t]
forall a. a -> [a] -> [a]
: [t]
ds
(Bool
False, Bool
True) -> t
dnt -> t -> t
forall a. Num a => a -> a -> a
+t
1 t -> [t] -> [t]
forall a. a -> [a] -> [a]
: [t]
ds
(Bool
True, Bool
True) -> if t
rn' t -> t -> t
forall a. Num a => a -> a -> a
* t
2 t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< t
sN then t
dn t -> [t] -> [t]
forall a. a -> [a] -> [a]
: [t]
ds else t
dnt -> t -> t
forall a. Num a => a -> a -> a
+t
1 t -> [t] -> [t]
forall a. a -> [a] -> [a]
: [t]
ds
(Bool
False, Bool
False) -> [t] -> t -> t -> t -> t -> [t]
gen (t
dnt -> [t] -> [t]
forall a. a -> [a] -> [a]
:[t]
ds) t
rn' t
sN t
mUpN' t
mDnN'
rds :: [Integer]
rds =
if Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then
[Integer] -> Integer -> Integer -> Integer -> Integer -> [Integer]
forall {t}. Integral t => [t] -> t -> t -> t -> t -> [t]
gen [] Integer
r (Integer
s Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer -> Int -> Integer
expt Integer
10 Int
k) Integer
mUp Integer
mDn
else
let bk :: Integer
bk = Integer -> Int -> Integer
expt Integer
10 (-Int
k) in
[Integer] -> Integer -> Integer -> Integer -> Integer -> [Integer]
forall {t}. Integral t => [t] -> t -> t -> t -> t -> [t]
gen [] (Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
bk) Integer
s (Integer
mUp Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
bk) (Integer
mDn Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
bk)
in
((Integer -> Int) -> [Integer] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Integer] -> [Integer]
forall a. [a] -> [a]
reverse [Integer]
rds), Int
k)
minExpt, maxExpt :: Int
minExpt :: Int
minExpt = Int
0
maxExpt :: Int
maxExpt = Int
1100
expt :: Integer -> Int -> Integer
expt :: Integer -> Int -> Integer
expt Integer
base Int
n
| Integer
base Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
2 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
minExpt Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
maxExpt = Array Int Integer
expts Array Int Integer -> Int -> Integer
forall i. Ix i => Array i Integer -> Int -> Integer
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
`unsafeAt` Int
n
| Integer
base Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
10 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
maxExpt10 = Array Int Integer
expts10 Array Int Integer -> Int -> Integer
forall i. Ix i => Array i Integer -> Int -> Integer
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> Int -> e
`unsafeAt` Int
n
| Bool
otherwise = Integer
baseInteger -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Int
n
expts :: Array Int Integer
expts :: Array Int Integer
expts = (Int, Int) -> [(Int, Integer)] -> Array Int Integer
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Int
minExpt,Int
maxExpt) [(Int
n,Integer
2Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Int
n) | Int
n <- [Int
minExpt .. Int
maxExpt]]
maxExpt10 :: Int
maxExpt10 :: Int
maxExpt10 = Int
324
expts10 :: Array Int Integer
expts10 :: Array Int Integer
expts10 = (Int, Int) -> [(Int, Integer)] -> Array Int Integer
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Int
minExpt,Int
maxExpt10) [(Int
n,Integer
10Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Int
n) | Int
n <- [Int
minExpt .. Int
maxExpt10]]
{-# INLINE i2d #-}
i2d :: Int -> Word8
i2d :: Int -> Word8
i2d Int
i = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i)
word8s :: [Word8] -> Builder
word8s :: [Word8] -> Builder
word8s = FixedPrim Word8 -> [Word8] -> Builder
forall a. FixedPrim a -> [a] -> Builder
BP.primMapListFixed FixedPrim Word8
BP.word8