{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE PatternGuards #-}
module Data.Scientific
( Scientific
, scientific
, coefficient
, base10Exponent
, isFloating
, isInteger
, fromRationalRepetend
, toRationalRepetend
, floatingOrInteger
, toRealFloat
, toBoundedRealFloat
, toBoundedInteger
, fromFloatDigits
, formatScientific
, FPFormat(..)
, toDecimalDigits
, normalize
) where
import Control.Exception (throw, ArithException(DivideByZero))
import Control.Monad (mplus)
import Control.Monad.ST (runST)
import Control.DeepSeq (NFData, rnf)
import Data.Binary (Binary, get, put)
import Data.Char (intToDigit, ord)
import Data.Data (Data)
import Data.Function (on)
import Data.Hashable (Hashable(..))
import qualified Data.Map as M (Map, empty, insert, lookup)
import Data.Ratio ((%), numerator, denominator)
import Data.Typeable (Typeable)
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as VM
import Math.NumberTheory.Logarithms (integerLog10')
import qualified Numeric (floatToDigits)
import qualified Text.Read as Read
import Text.Read (readPrec)
import qualified Text.ParserCombinators.ReadPrec as ReadPrec
import qualified Text.ParserCombinators.ReadP as ReadP
import Text.ParserCombinators.ReadP ( ReadP )
import Data.Text.Lazy.Builder.RealFloat (FPFormat(..))
#if !MIN_VERSION_base(4,8,0)
import Data.Functor ((<$>))
import Control.Applicative ((<*>))
#endif
#if MIN_VERSION_base(4,5,0)
import Data.Bits (unsafeShiftR)
#else
import Data.Bits (shiftR)
#endif
import GHC.Integer (quotRemInteger, quotInteger)
import GHC.Integer.Compat (divInteger)
import Utils (roundTo)
data Scientific = Scientific
{ coefficient :: !Integer
, base10Exponent :: {-# UNPACK #-} !Int
} deriving (Typeable, Data)
scientific :: Integer -> Int -> Scientific
scientific = Scientific
instance NFData Scientific where
rnf (Scientific _ _) = ()
instance Hashable Scientific where
hashWithSalt salt = hashWithSalt salt . toRational
instance Binary Scientific where
put (Scientific c e) = do
put c
put $ toInteger e
get = Scientific <$> get <*> (fromInteger <$> get)
instance Eq Scientific where
(==) = (==) `on` toRational
{-# INLINE (==) #-}
(/=) = (/=) `on` toRational
{-# INLINE (/=) #-}
instance Ord Scientific where
(<) = (<) `on` toRational
{-# INLINE (<) #-}
(<=) = (<=) `on` toRational
{-# INLINE (<=) #-}
(>) = (>) `on` toRational
{-# INLINE (>) #-}
(>=) = (>=) `on` toRational
{-# INLINE (>=) #-}
compare = compare `on` toRational
{-# INLINE compare #-}
instance Num Scientific where
Scientific c1 e1 + Scientific c2 e2
| e1 < e2 = Scientific (c1 + c2*l) e1
| otherwise = Scientific (c1*r + c2 ) e2
where
l = magnitude (e2 - e1)
r = magnitude (e1 - e2)
{-# INLINE (+) #-}
Scientific c1 e1 - Scientific c2 e2
| e1 < e2 = Scientific (c1 - c2*l) e1
| otherwise = Scientific (c1*r - c2 ) e2
where
l = magnitude (e2 - e1)
r = magnitude (e1 - e2)
{-# INLINE (-) #-}
Scientific c1 e1 * Scientific c2 e2 =
Scientific (c1 * c2) (e1 + e2)
{-# INLINE (*) #-}
abs (Scientific c e) = Scientific (abs c) e
{-# INLINE abs #-}
negate (Scientific c e) = Scientific (negate c) e
{-# INLINE negate #-}
signum (Scientific c _) = Scientific (signum c) 0
{-# INLINE signum #-}
fromInteger i = Scientific i 0
{-# INLINE fromInteger #-}
instance Real Scientific where
toRational (Scientific c e)
| e < 0 = c % magnitude (-e)
| otherwise = (c * magnitude e) % 1
{-# INLINE toRational #-}
{-# RULES
"realToFrac_toRealFloat_Double"
realToFrac = toRealFloat :: Scientific -> Double #-}
{-# RULES
"realToFrac_toRealFloat_Float"
realToFrac = toRealFloat :: Scientific -> Float #-}
instance Fractional Scientific where
recip = fromRational . recip . toRational
{-# INLINE recip #-}
x / y = fromRational $ toRational x / toRational y
{-# INLINE (/) #-}
fromRational rational
| d == 0 = throw DivideByZero
| otherwise = positivize (longDiv 0 0) (numerator rational)
where
longDiv :: Integer -> Int -> (Integer -> Scientific)
longDiv !c !e 0 = Scientific c e
longDiv !c !e !n
| n < d = longDiv (c * 10) (e - 1) (n * 10)
| otherwise = case n `quotRemInteger` d of
(#q, r#) -> longDiv (c + q) e r
d = denominator rational
fromRationalRepetend
:: Maybe Int
-> Rational
-> Either (Scientific, Rational)
(Scientific, Maybe Int)
fromRationalRepetend mbLimit rational
| d == 0 = throw DivideByZero
| num < 0 = case longDiv (-num) of
Left (s, r) -> Left (-s, -r)
Right (s, mb) -> Right (-s, mb)
| otherwise = longDiv num
where
num = numerator rational
longDiv :: Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDiv n = case mbLimit of
Nothing -> Right $ longDivNoLimit 0 0 M.empty n
Just l -> longDivWithLimit (-l) n
longDivNoLimit :: Integer
-> Int
-> M.Map Integer Int
-> (Integer -> (Scientific, Maybe Int))
longDivNoLimit !c !e _ns 0 = (Scientific c e, Nothing)
longDivNoLimit !c !e ns !n
| Just e' <- M.lookup n ns = (Scientific c e, Just (-e'))
| n < d = longDivNoLimit (c * 10) (e - 1) (M.insert n e ns) (n * 10)
| otherwise = case n `quotRemInteger` d of
(#q, r#) -> longDivNoLimit (c + q) e ns r
longDivWithLimit :: Int -> Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDivWithLimit l = go 0 0 M.empty
where
go :: Integer
-> Int
-> M.Map Integer Int
-> (Integer -> Either (Scientific, Rational) (Scientific, Maybe Int))
go !c !e _ns 0 = Right (Scientific c e, Nothing)
go !c !e ns !n
| Just e' <- M.lookup n ns = Right (Scientific c e, Just (-e'))
| e <= l = Left (Scientific c e, n % (d * magnitude (-e)))
| n < d = go (c * 10) (e - 1) (M.insert n e ns) (n * 10)
| otherwise = case n `quotRemInteger` d of
(#q, r#) -> go (c + q) e ns r
d = denominator rational
toRationalRepetend
:: Scientific
-> Int
-> Rational
toRationalRepetend s r
| r < 0 = error "toRationalRepetend: Negative repetend index!"
| r >= f = error "toRationalRepetend: Repetend index >= than number of digits in the fractional part!"
| otherwise = (fromInteger nonRepetend + repetend % nines) /
fromInteger (magnitude r)
where
c = coefficient s
e = base10Exponent s
f = (-e)
n = f - r
m = magnitude n
(#nonRepetend, repetend#) = c `quotRemInteger` m
nines = m - 1
instance RealFrac Scientific where
properFraction s@(Scientific c e)
| e < 0 = if dangerouslySmall c e
then (0, s)
else case c `quotRemInteger` magnitude (-e) of
(#q, r#) -> (fromInteger q, Scientific r e)
| otherwise = (toIntegral s, 0)
{-# INLINE properFraction #-}
truncate = whenFloating $ \c e ->
if dangerouslySmall c e
then 0
else fromInteger $ c `quotInteger` magnitude (-e)
{-# INLINE truncate #-}
round = whenFloating $ \c e ->
if dangerouslySmall c e
then 0
else let (#q, r#) = c `quotRemInteger` magnitude (-e)
n = fromInteger q
m | r < 0 = n - 1
| otherwise = n + 1
f = Scientific r e
in case signum $ coefficient $ abs f - 0.5 of
-1 -> n
0 -> if even n then n else m
1 -> m
_ -> error "round default defn: Bad value"
{-# INLINE round #-}
ceiling = whenFloating $ \c e ->
if dangerouslySmall c e
then if c <= 0
then 0
else 1
else case c `quotRemInteger` magnitude (-e) of
(#q, r#) | r <= 0 -> fromInteger q
| otherwise -> fromInteger (q + 1)
{-# INLINE ceiling #-}
floor = whenFloating $ \c e ->
if dangerouslySmall c e
then if c < 0
then -1
else 0
else fromInteger (c `divInteger` magnitude (-e))
{-# INLINE floor #-}
dangerouslySmall :: Integer -> Int -> Bool
dangerouslySmall c e = e < (-limit) && e < (-integerLog10' (abs c)) - 1
{-# INLINE dangerouslySmall #-}
limit :: Int
limit = maxExpt
positivize :: (Ord a, Num a, Num b) => (a -> b) -> (a -> b)
positivize f x | x < 0 = -(f (-x))
| otherwise = f x
{-# INLINE positivize #-}
whenFloating :: (Num a) => (Integer -> Int -> a) -> Scientific -> a
whenFloating f s@(Scientific c e)
| e < 0 = f c e
| otherwise = toIntegral s
{-# INLINE whenFloating #-}
toIntegral :: (Num a) => Scientific -> a
toIntegral (Scientific c e) = fromInteger c * magnitude e
{-# INLINE toIntegral #-}
maxExpt :: Int
maxExpt = 324
expts10 :: V.Vector Integer
expts10 = runST $ do
mv <- VM.unsafeNew maxExpt
VM.unsafeWrite mv 0 1
VM.unsafeWrite mv 1 10
let go !ix
| ix == maxExpt = V.unsafeFreeze mv
| otherwise = do
VM.unsafeWrite mv ix xx
VM.unsafeWrite mv (ix+1) (10*xx)
go (ix+2)
where
xx = x * x
x = V.unsafeIndex expts10 half
#if MIN_VERSION_base(4,5,0)
!half = ix `unsafeShiftR` 1
#else
!half = ix `shiftR` 1
#endif
go 2
magnitude :: (Num a) => Int -> a
magnitude e | e < maxExpt = cachedPow10 e
| otherwise = cachedPow10 hi * 10 ^ (e - hi)
where
cachedPow10 p = fromInteger (V.unsafeIndex expts10 p)
hi = maxExpt - 1
{-# INLINE magnitude #-}
fromFloatDigits :: (RealFloat a) => a -> Scientific
fromFloatDigits 0 = 0
fromFloatDigits rf = positivize fromPositiveRealFloat rf
where
fromPositiveRealFloat r = go digits 0 0
where
(digits, e) = Numeric.floatToDigits 10 r
go [] !c !n = Scientific c (e - n)
go (d:ds) !c !n = go ds (c * 10 + toInteger d) (n + 1)
toRealFloat :: (RealFloat a) => Scientific -> a
toRealFloat = either id id . toBoundedRealFloat
toBoundedRealFloat :: forall a. (RealFloat a) => Scientific -> Either a a
toBoundedRealFloat s@(Scientific c e)
| c == 0 = Right 0
| e > limit && e > hiLimit = Left $ sign (1/0)
| e < -limit && e < loLimit && e + d < loLimit = Left $ sign 0
| otherwise = Right $ realToFrac s
where
(loLimit, hiLimit) = exponentLimits (undefined :: a)
d = integerLog10' (abs c)
sign x | c < 0 = -x
| otherwise = x
exponentLimits :: forall a. (RealFloat a) => a -> (Int, Int)
exponentLimits _ = (loLimit, hiLimit)
where
loLimit = floor (fromIntegral lo * log10Radix) -
ceiling (fromIntegral digits * log10Radix)
hiLimit = ceiling (fromIntegral hi * log10Radix)
log10Radix :: Double
log10Radix = logBase 10 $ fromInteger radix
radix = floatRadix (undefined :: a)
digits = floatDigits (undefined :: a)
(lo, hi) = floatRange (undefined :: a)
toBoundedInteger :: forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger s
| c == 0 = fromIntegerBounded 0
| integral = if dangerouslyBig
then Nothing
else fromIntegerBounded n
| otherwise = Nothing
where
c = coefficient s
integral = e >= 0 || e' >= 0
e = base10Exponent s
e' = base10Exponent s'
s' = normalize s
dangerouslyBig = e > limit &&
e > integerLog10' (max (abs iMinBound) (abs iMaxBound))
fromIntegerBounded :: Integer -> Maybe i
fromIntegerBounded i
| i < iMinBound || i > iMaxBound = Nothing
| otherwise = Just $ fromInteger i
iMinBound = toInteger (minBound :: i)
iMaxBound = toInteger (maxBound :: i)
n :: Integer
n = toIntegral s'
floatingOrInteger :: (RealFloat r, Integral i) => Scientific -> Either r i
floatingOrInteger s
| base10Exponent s >= 0 = Right (toIntegral s)
| base10Exponent s' >= 0 = Right (toIntegral s')
| otherwise = Left (toRealFloat s')
where
s' = normalize s
isFloating :: Scientific -> Bool
isFloating = not . isInteger
isInteger :: Scientific -> Bool
isInteger s = base10Exponent s >= 0 ||
base10Exponent s' >= 0
where
s' = normalize s
instance Read Scientific where
readPrec = Read.parens $ ReadPrec.lift (ReadP.skipSpaces >> scientificP)
data SP = SP !Integer {-# UNPACK #-}!Int
scientificP :: ReadP Scientific
scientificP = do
let positive = (('+' ==) <$> ReadP.satisfy isSign) `mplus` return True
pos <- positive
let step :: Num a => a -> Int -> a
step a digit = a * 10 + fromIntegral digit
{-# INLINE step #-}
n <- foldDigits step 0
let s = SP n 0
fractional = foldDigits (\(SP a e) digit ->
SP (step a digit) (e-1)) s
SP coeff expnt <- (ReadP.satisfy (== '.') >> fractional)
ReadP.<++ return s
let signedCoeff | pos = coeff
| otherwise = (-coeff)
eP = do posE <- positive
e <- foldDigits step 0
if posE
then return e
else return (-e)
(ReadP.satisfy isE >>
((Scientific signedCoeff . (expnt +)) <$> eP)) `mplus`
return (Scientific signedCoeff expnt)
foldDigits :: (a -> Int -> a) -> a -> ReadP a
foldDigits f z = do
c <- ReadP.satisfy isDecimal
let digit = ord c - 48
a = f z digit
ReadP.look >>= go a
where
go !a [] = return a
go !a (c:cs)
| isDecimal c = do
_ <- ReadP.get
let digit = ord c - 48
go (f a digit) cs
| otherwise = return a
isDecimal :: Char -> Bool
isDecimal c = c >= '0' && c <= '9'
{-# INLINE isDecimal #-}
isSign :: Char -> Bool
isSign c = c == '-' || c == '+'
{-# INLINE isSign #-}
isE :: Char -> Bool
isE c = c == 'e' || c == 'E'
{-# INLINE isE #-}
instance Show Scientific where
show s | coefficient s < 0 = '-':showPositive (-s)
| otherwise = showPositive s
where
showPositive :: Scientific -> String
showPositive = fmtAsGeneric . toDecimalDigits
fmtAsGeneric :: ([Int], Int) -> String
fmtAsGeneric x@(_is, e)
| e < 0 || e > 7 = fmtAsExponent x
| otherwise = fmtAsFixed x
fmtAsExponent :: ([Int], Int) -> String
fmtAsExponent (is, e) =
case ds of
"0" -> "0.0e0"
[d] -> d : '.' :'0' : 'e' : show_e'
(d:ds') -> d : '.' : ds' ++ ('e' : show_e')
[] -> error "formatScientific/doFmt/FFExponent: []"
where
show_e' = show (e-1)
ds = map intToDigit is
fmtAsFixed :: ([Int], Int) -> String
fmtAsFixed (is, e)
| e <= 0 = '0':'.':(replicate (-e) '0' ++ ds)
| otherwise =
let
f 0 s rs = mk0 (reverse s) ++ '.':mk0 rs
f n s "" = f (n-1) ('0':s) ""
f n s (r:rs) = f (n-1) (r:s) rs
in
f e "" ds
where
mk0 "" = "0"
mk0 ls = ls
ds = map intToDigit is
formatScientific :: FPFormat
-> Maybe Int
-> Scientific
-> String
formatScientific format mbDecs s
| coefficient s < 0 = '-':formatPositiveScientific (-s)
| otherwise = formatPositiveScientific s
where
formatPositiveScientific :: Scientific -> String
formatPositiveScientific s' = case format of
Generic -> fmtAsGeneric $ toDecimalDigits s'
Exponent -> fmtAsExponentMbDecs $ toDecimalDigits s'
Fixed -> fmtAsFixedMbDecs $ toDecimalDigits s'
fmtAsGeneric :: ([Int], Int) -> String
fmtAsGeneric x@(_is, e)
| e < 0 || e > 7 = fmtAsExponentMbDecs x
| otherwise = fmtAsFixedMbDecs x
fmtAsExponentMbDecs :: ([Int], Int) -> String
fmtAsExponentMbDecs x = case mbDecs of
Nothing -> fmtAsExponent x
Just dec -> fmtAsExponentDecs dec x
fmtAsFixedMbDecs :: ([Int], Int) -> String
fmtAsFixedMbDecs x = case mbDecs of
Nothing -> fmtAsFixed x
Just dec -> fmtAsFixedDecs dec x
fmtAsExponentDecs :: Int -> ([Int], Int) -> String
fmtAsExponentDecs dec (is, e) =
let dec' = max dec 1 in
case is of
[0] -> '0' :'.' : take dec' (repeat '0') ++ "e0"
_ ->
let
(ei,is') = roundTo (dec'+1) is
(d:ds') = map intToDigit (if ei > 0 then init is' else is')
in
d:'.':ds' ++ 'e':show (e-1+ei)
fmtAsFixedDecs :: Int -> ([Int], Int) -> String
fmtAsFixedDecs dec (is, e) =
let dec' = max dec 0 in
if e >= 0 then
let
(ei,is') = roundTo (dec' + e) is
(ls,rs) = splitAt (e+ei) (map intToDigit is')
in
mk0 ls ++ (if null rs then "" else '.':rs)
else
let
(ei,is') = roundTo dec' (replicate (-e) 0 ++ is)
d:ds' = map intToDigit (if ei > 0 then is' else 0:is')
in
d : (if null ds' then "" else '.':ds')
where
mk0 ls = case ls of { "" -> "0" ; _ -> ls}
toDecimalDigits :: Scientific -> ([Int], Int)
toDecimalDigits (Scientific 0 _) = ([0], 0)
toDecimalDigits (Scientific c' e') =
case normalizePositive c' e' of
Scientific c e -> go c 0 []
where
go :: Integer -> Int -> [Int] -> ([Int], Int)
go 0 !n ds = (ds, ne) where !ne = n + e
go i !n ds = case i `quotRemInteger` 10 of
(# q, r #) -> go q (n+1) (d:ds)
where
!d = fromIntegral r
normalize :: Scientific -> Scientific
normalize (Scientific c e)
| c > 0 = normalizePositive c e
| c < 0 = -(normalizePositive (-c) e)
| otherwise = Scientific 0 0
normalizePositive :: Integer -> Int -> Scientific
normalizePositive !c !e = case quotRemInteger c 10 of
(# c', r #)
| r == 0 -> normalizePositive c' (e+1)
| otherwise -> Scientific c e