{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE PatternGuards #-}
module Data.Scientific
( Scientific
, scientific
, coefficient
, base10Exponent
, isFloating
, isInteger
, unsafeFromRational
, fromRationalRepetend
, fromRationalRepetendLimited
, fromRationalRepetendUnlimited
, toRationalRepetend
, floatingOrInteger
, toRealFloat
, toBoundedRealFloat
, toBoundedInteger
, fromFloatDigits
, scientificP
, 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.Hashable (Hashable(..))
import Data.Int (Int8, Int16, Int32, Int64)
import qualified Data.Map as M (Map, empty, insert, lookup)
import Data.Ratio ((%), numerator, denominator)
import Data.Typeable (Typeable)
import qualified Data.Primitive.Array as Primitive
import Data.Word (Word8, Word16, Word32, Word64)
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,9,0)
import Control.Applicative ((*>))
#endif
#if !MIN_VERSION_base(4,8,0)
import Data.Functor ((<$>))
import Data.Word (Word)
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
{ Scientific -> Integer
coefficient :: !Integer
, Scientific -> Int
base10Exponent :: {-# UNPACK #-} !Int
} deriving (Typeable, Typeable Scientific
DataType
Constr
Typeable Scientific =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scientific -> c Scientific)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scientific)
-> (Scientific -> Constr)
-> (Scientific -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scientific))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Scientific))
-> ((forall b. Data b => b -> b) -> Scientific -> Scientific)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r)
-> (forall u. (forall d. Data d => d -> u) -> Scientific -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Scientific -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific)
-> Data Scientific
Scientific -> DataType
Scientific -> Constr
(forall b. Data b => b -> b) -> Scientific -> Scientific
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scientific -> c Scientific
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scientific
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Scientific -> u
forall u. (forall d. Data d => d -> u) -> Scientific -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scientific
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scientific -> c Scientific
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scientific)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scientific)
$cScientific :: Constr
$tScientific :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Scientific -> m Scientific
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific
gmapMp :: (forall d. Data d => d -> m d) -> Scientific -> m Scientific
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific
gmapM :: (forall d. Data d => d -> m d) -> Scientific -> m Scientific
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scientific -> m Scientific
gmapQi :: Int -> (forall d. Data d => d -> u) -> Scientific -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Scientific -> u
gmapQ :: (forall d. Data d => d -> u) -> Scientific -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Scientific -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scientific -> r
gmapT :: (forall b. Data b => b -> b) -> Scientific -> Scientific
$cgmapT :: (forall b. Data b => b -> b) -> Scientific -> Scientific
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scientific)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scientific)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Scientific)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Scientific)
dataTypeOf :: Scientific -> DataType
$cdataTypeOf :: Scientific -> DataType
toConstr :: Scientific -> Constr
$ctoConstr :: Scientific -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scientific
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Scientific
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scientific -> c Scientific
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scientific -> c Scientific
$cp1Data :: Typeable Scientific
Data)
scientific :: Integer -> Int -> Scientific
scientific :: Integer -> Int -> Scientific
scientific = Integer -> Int -> Scientific
Scientific
instance NFData Scientific where
rnf :: Scientific -> ()
rnf (Scientific _ _) = ()
instance Hashable Scientific where
hashWithSalt :: Int -> Scientific -> Int
hashWithSalt salt :: Int
salt s :: Scientific
s = Int
salt Int -> Integer -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Integer
c Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
e
where
Scientific c :: Integer
c e :: Int
e = Scientific -> Scientific
normalize Scientific
s
instance Binary Scientific where
put :: Scientific -> Put
put (Scientific c :: Integer
c e :: Int
e) = Integer -> Put
forall t. Binary t => t -> Put
put Integer
c Put -> Put -> Put
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Integer -> Put
forall t. Binary t => t -> Put
put (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
e)
get :: Get Scientific
get = Integer -> Int -> Scientific
Scientific (Integer -> Int -> Scientific)
-> Get Integer -> Get (Int -> Scientific)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Integer
forall t. Binary t => Get t
get Get (Int -> Scientific) -> Get Int -> Get Scientific
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Get Integer -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Integer
forall t. Binary t => Get t
get)
instance Eq Scientific where
s1 :: Scientific
s1 == :: Scientific -> Scientific -> Bool
== s2 :: Scientific
s2 = Integer
c1 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
c2 Bool -> Bool -> Bool
&& Int
e1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
e2
where
Scientific c1 :: Integer
c1 e1 :: Int
e1 = Scientific -> Scientific
normalize Scientific
s1
Scientific c2 :: Integer
c2 e2 :: Int
e2 = Scientific -> Scientific
normalize Scientific
s2
instance Ord Scientific where
compare :: Scientific -> Scientific -> Ordering
compare s1 :: Scientific
s1 s2 :: Scientific
s2
| Integer
c1 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
c2 Bool -> Bool -> Bool
&& Int
e1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
e2 = Ordering
EQ
| Integer
c1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = if Integer
c2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 then Integer -> Int -> Integer -> Int -> Ordering
cmp (-Integer
c2) Int
e2 (-Integer
c1) Int
e1 else Ordering
LT
| Integer
c1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> 0 = if Integer
c2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> 0 then Integer -> Int -> Integer -> Int -> Ordering
cmp Integer
c1 Int
e1 Integer
c2 Int
e2 else Ordering
GT
| Bool
otherwise = if Integer
c2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> 0 then Ordering
LT else Ordering
GT
where
Scientific c1 :: Integer
c1 e1 :: Int
e1 = Scientific -> Scientific
normalize Scientific
s1
Scientific c2 :: Integer
c2 e2 :: Int
e2 = Scientific -> Scientific
normalize Scientific
s2
cmp :: Integer -> Int -> Integer -> Int -> Ordering
cmp cx :: Integer
cx ex :: Int
ex cy :: Integer
cy ey :: Int
ey
| Int
log10sx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
log10sy = Ordering
LT
| Int
log10sx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
log10sy = Ordering
GT
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = if Integer
cx Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= (Integer
cy Integer -> Integer -> Integer
`quotInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
d)) then Ordering
LT else Ordering
GT
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0 = if Integer
cy Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> (Integer
cx Integer -> Integer -> Integer
`quotInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude Int
d) then Ordering
LT else Ordering
GT
| Bool
otherwise = if Integer
cx Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
cy then Ordering
LT else Ordering
GT
where
log10sx :: Int
log10sx = Int
log10cx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ex
log10sy :: Int
log10sy = Int
log10cy Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ey
log10cx :: Int
log10cx = Integer -> Int
integerLog10' Integer
cx
log10cy :: Int
log10cy = Integer -> Int
integerLog10' Integer
cy
d :: Int
d = Int
log10cx Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
log10cy
instance Num Scientific where
Scientific c1 :: Integer
c1 e1 :: Int
e1 + :: Scientific -> Scientific -> Scientific
+ Scientific c2 :: Integer
c2 e2 :: Int
e2
| Int
e1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
e2 = Integer -> Int -> Scientific
Scientific (Integer
c1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
c2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
l) Int
e1
| Bool
otherwise = Integer -> Int -> Scientific
Scientific (Integer
c1Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
c2 ) Int
e2
where
l :: Integer
l = Int -> Integer
forall a. Num a => Int -> a
magnitude (Int
e2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e1)
r :: Integer
r = Int -> Integer
forall a. Num a => Int -> a
magnitude (Int
e1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e2)
{-# INLINABLE (+) #-}
Scientific c1 :: Integer
c1 e1 :: Int
e1 - :: Scientific -> Scientific -> Scientific
- Scientific c2 :: Integer
c2 e2 :: Int
e2
| Int
e1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
e2 = Integer -> Int -> Scientific
Scientific (Integer
c1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
c2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
l) Int
e1
| Bool
otherwise = Integer -> Int -> Scientific
Scientific (Integer
c1Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
r Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
c2 ) Int
e2
where
l :: Integer
l = Int -> Integer
forall a. Num a => Int -> a
magnitude (Int
e2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e1)
r :: Integer
r = Int -> Integer
forall a. Num a => Int -> a
magnitude (Int
e1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e2)
{-# INLINABLE (-) #-}
Scientific c1 :: Integer
c1 e1 :: Int
e1 * :: Scientific -> Scientific -> Scientific
* Scientific c2 :: Integer
c2 e2 :: Int
e2 =
Integer -> Int -> Scientific
Scientific (Integer
c1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
c2) (Int
e1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e2)
{-# INLINABLE (*) #-}
abs :: Scientific -> Scientific
abs (Scientific c :: Integer
c e :: Int
e) = Integer -> Int -> Scientific
Scientific (Integer -> Integer
forall a. Num a => a -> a
abs Integer
c) Int
e
{-# INLINABLE abs #-}
negate :: Scientific -> Scientific
negate (Scientific c :: Integer
c e :: Int
e) = Integer -> Int -> Scientific
Scientific (Integer -> Integer
forall a. Num a => a -> a
negate Integer
c) Int
e
{-# INLINABLE negate #-}
signum :: Scientific -> Scientific
signum (Scientific c :: Integer
c _) = Integer -> Int -> Scientific
Scientific (Integer -> Integer
forall a. Num a => a -> a
signum Integer
c) 0
{-# INLINABLE signum #-}
fromInteger :: Integer -> Scientific
fromInteger i :: Integer
i = Integer -> Int -> Scientific
Scientific Integer
i 0
{-# INLINABLE fromInteger #-}
instance Real Scientific where
toRational :: Scientific -> Rational
toRational (Scientific c :: Integer
c e :: Int
e)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = Integer
c Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e)
| Bool
otherwise = (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a. Num a => Int -> a
magnitude Int
e) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% 1
{-# INLINABLE toRational #-}
{-# RULES
"realToFrac_toRealFloat_Double"
realToFrac = toRealFloat :: Scientific -> Double #-}
{-# RULES
"realToFrac_toRealFloat_Float"
realToFrac = toRealFloat :: Scientific -> Float #-}
instance Fractional Scientific where
recip :: Scientific -> Scientific
recip = Rational -> Scientific
forall a. Fractional a => Rational -> a
fromRational (Rational -> Scientific)
-> (Scientific -> Rational) -> Scientific -> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Rational
forall a. Fractional a => a -> a
recip (Rational -> Rational)
-> (Scientific -> Rational) -> Scientific -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Rational
forall a. Real a => a -> Rational
toRational
{-# INLINABLE recip #-}
x :: Scientific
x / :: Scientific -> Scientific -> Scientific
/ y :: Scientific
y = Rational -> Scientific
forall a. Fractional a => Rational -> a
fromRational (Rational -> Scientific) -> Rational -> Scientific
forall a b. (a -> b) -> a -> b
$ Scientific -> Rational
forall a. Real a => a -> Rational
toRational Scientific
x Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Scientific -> Rational
forall a. Real a => a -> Rational
toRational Scientific
y
{-# INLINABLE (/) #-}
fromRational :: Rational -> Scientific
fromRational rational :: Rational
rational =
case Maybe Int
mbRepetendIx of
Nothing -> Scientific
s
Just _ix :: Int
_ix -> [Char] -> Scientific
forall a. HasCallStack => [Char] -> a
error ([Char] -> Scientific) -> [Char] -> Scientific
forall a b. (a -> b) -> a -> b
$
"fromRational has been applied to a repeating decimal " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
"which can't be represented as a Scientific! " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
"It's better to avoid performing fractional operations on Scientifics " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
"and convert them to other fractional types like Double as early as possible."
where
(s :: Scientific
s, mbRepetendIx :: Maybe Int
mbRepetendIx) = Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited Rational
rational
unsafeFromRational :: Rational -> Scientific
unsafeFromRational :: Rational -> Scientific
unsafeFromRational rational :: Rational
rational
| Integer
d Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = ArithException -> Scientific
forall a e. Exception e => e -> a
throw ArithException
DivideByZero
| Bool
otherwise = (Integer -> Scientific) -> Integer -> Scientific
forall a b. (Ord a, Num a, Num b) => (a -> b) -> a -> b
positivize (Integer -> Int -> Integer -> Scientific
longDiv 0 0) (Rational -> Integer
forall a. Ratio a -> a
numerator Rational
rational)
where
longDiv :: Integer -> Int -> (Integer -> Scientific)
longDiv :: Integer -> Int -> Integer -> Scientific
longDiv !Integer
c !Int
e 0 = Integer -> Int -> Scientific
Scientific Integer
c Int
e
longDiv !Integer
c !Int
e !Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
d = Integer -> Int -> Integer -> Scientific
longDiv (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10)
| Bool
otherwise = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
d of
(#q :: Integer
q, r :: Integer
r#) -> Integer -> Int -> Integer -> Scientific
longDiv (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
q) Int
e Integer
r
d :: Integer
d = Rational -> Integer
forall a. Ratio a -> a
denominator Rational
rational
fromRationalRepetend
:: Maybe Int
-> Rational
-> Either (Scientific, Rational)
(Scientific, Maybe Int)
fromRationalRepetend :: Maybe Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetend mbLimit :: Maybe Int
mbLimit rational :: Rational
rational =
case Maybe Int
mbLimit of
Nothing -> (Scientific, Maybe Int)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. b -> Either a b
Right ((Scientific, Maybe Int)
-> Either (Scientific, Rational) (Scientific, Maybe Int))
-> (Scientific, Maybe Int)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. (a -> b) -> a -> b
$ Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited Rational
rational
Just l :: Int
l -> Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetendLimited Int
l Rational
rational
fromRationalRepetendLimited
:: Int
-> Rational
-> Either (Scientific, Rational)
(Scientific, Maybe Int)
fromRationalRepetendLimited :: Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetendLimited l :: Int
l rational :: Rational
rational
| Integer
d Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = ArithException
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a e. Exception e => e -> a
throw ArithException
DivideByZero
| Integer
num Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = case Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDiv (-Integer
num) of
Left (s :: Scientific
s, r :: Rational
r) -> (Scientific, Rational)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. a -> Either a b
Left (-Scientific
s, -Rational
r)
Right (s :: Scientific
s, mb :: Maybe Int
mb) -> (Scientific, Maybe Int)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. b -> Either a b
Right (-Scientific
s, Maybe Int
mb)
| Bool
otherwise = Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDiv Integer
num
where
num :: Integer
num = Rational -> Integer
forall a. Ratio a -> a
numerator Rational
rational
longDiv :: Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDiv :: Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDiv = Integer
-> Int
-> Map Integer Int
-> Integer
-> Either (Scientific, Rational) (Scientific, Maybe Int)
longDivWithLimit 0 0 Map Integer Int
forall k a. Map k a
M.empty
longDivWithLimit
:: Integer
-> Int
-> M.Map Integer Int
-> (Integer -> Either (Scientific, Rational)
(Scientific, Maybe Int))
longDivWithLimit :: Integer
-> Int
-> Map Integer Int
-> Integer
-> Either (Scientific, Rational) (Scientific, Maybe Int)
longDivWithLimit !Integer
c !Int
e _ns :: Map Integer Int
_ns 0 = (Scientific, Maybe Int)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. b -> Either a b
Right (Integer -> Int -> Scientific
Scientific Integer
c Int
e, Maybe Int
forall a. Maybe a
Nothing)
longDivWithLimit !Integer
c !Int
e ns :: Map Integer Int
ns !Integer
n
| Just e' :: Int
e' <- Integer -> Map Integer Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Integer
n Map Integer Int
ns = (Scientific, Maybe Int)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. b -> Either a b
Right (Integer -> Int -> Scientific
Scientific Integer
c Int
e, Int -> Maybe Int
forall a. a -> Maybe a
Just (-Int
e'))
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= (-Int
l) = (Scientific, Rational)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. a -> Either a b
Left (Integer -> Int -> Scientific
Scientific Integer
c Int
e, Integer
n Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
d Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e)))
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
d = let !ns' :: Map Integer Int
ns' = Integer -> Int -> Map Integer Int -> Map Integer Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Integer
n Int
e Map Integer Int
ns
in Integer
-> Int
-> Map Integer Int
-> Integer
-> Either (Scientific, Rational) (Scientific, Maybe Int)
longDivWithLimit (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) Map Integer Int
ns' (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10)
| Bool
otherwise = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
d of
(#q :: Integer
q, r :: Integer
r#) -> Integer
-> Int
-> Map Integer Int
-> Integer
-> Either (Scientific, Rational) (Scientific, Maybe Int)
longDivWithLimit (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
q) Int
e Map Integer Int
ns Integer
r
d :: Integer
d = Rational -> Integer
forall a. Ratio a -> a
denominator Rational
rational
fromRationalRepetendUnlimited :: Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited :: Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited rational :: Rational
rational
| Integer
d Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = ArithException -> (Scientific, Maybe Int)
forall a e. Exception e => e -> a
throw ArithException
DivideByZero
| Integer
num Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = case Integer -> (Scientific, Maybe Int)
longDiv (-Integer
num) of
(s :: Scientific
s, mb :: Maybe Int
mb) -> (-Scientific
s, Maybe Int
mb)
| Bool
otherwise = Integer -> (Scientific, Maybe Int)
longDiv Integer
num
where
num :: Integer
num = Rational -> Integer
forall a. Ratio a -> a
numerator Rational
rational
longDiv :: Integer -> (Scientific, Maybe Int)
longDiv :: Integer -> (Scientific, Maybe Int)
longDiv = Integer
-> Int -> Map Integer Int -> Integer -> (Scientific, Maybe Int)
longDivNoLimit 0 0 Map Integer Int
forall k a. Map k a
M.empty
longDivNoLimit :: Integer
-> Int
-> M.Map Integer Int
-> (Integer -> (Scientific, Maybe Int))
longDivNoLimit :: Integer
-> Int -> Map Integer Int -> Integer -> (Scientific, Maybe Int)
longDivNoLimit !Integer
c !Int
e _ns :: Map Integer Int
_ns 0 = (Integer -> Int -> Scientific
Scientific Integer
c Int
e, Maybe Int
forall a. Maybe a
Nothing)
longDivNoLimit !Integer
c !Int
e ns :: Map Integer Int
ns !Integer
n
| Just e' :: Int
e' <- Integer -> Map Integer Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Integer
n Map Integer Int
ns = (Integer -> Int -> Scientific
Scientific Integer
c Int
e, Int -> Maybe Int
forall a. a -> Maybe a
Just (-Int
e'))
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
d = let !ns' :: Map Integer Int
ns' = Integer -> Int -> Map Integer Int -> Map Integer Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Integer
n Int
e Map Integer Int
ns
in Integer
-> Int -> Map Integer Int -> Integer -> (Scientific, Maybe Int)
longDivNoLimit (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) Map Integer Int
ns' (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10)
| Bool
otherwise = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
d of
(#q :: Integer
q, r :: Integer
r#) -> Integer
-> Int -> Map Integer Int -> Integer -> (Scientific, Maybe Int)
longDivNoLimit (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
q) Int
e Map Integer Int
ns Integer
r
d :: Integer
d = Rational -> Integer
forall a. Ratio a -> a
denominator Rational
rational
toRationalRepetend
:: Scientific
-> Int
-> Rational
toRationalRepetend :: Scientific -> Int -> Rational
toRationalRepetend s :: Scientific
s r :: Int
r
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = [Char] -> Rational
forall a. HasCallStack => [Char] -> a
error "toRationalRepetend: Negative repetend index!"
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
f = [Char] -> Rational
forall a. HasCallStack => [Char] -> a
error "toRationalRepetend: Repetend index >= than number of digits in the fractional part!"
| Bool
otherwise = (Integer -> Rational
forall a. Num a => Integer -> a
fromInteger Integer
nonRepetend Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Integer
repetend Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
nines) Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/
Integer -> Rational
forall a. Num a => Integer -> a
fromInteger (Int -> Integer
forall a. Num a => Int -> a
magnitude Int
r)
where
c :: Integer
c = Scientific -> Integer
coefficient Scientific
s
e :: Int
e = Scientific -> Int
base10Exponent Scientific
s
f :: Int
f = (-Int
e)
n :: Int
n = Int
f Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
r
m :: Integer
m = Int -> Integer
forall a. Num a => Int -> a
magnitude Int
n
(#nonRepetend :: Integer
nonRepetend, repetend :: Integer
repetend#) = Integer
c Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
m
nines :: Integer
nines = Integer
m Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- 1
instance RealFrac Scientific where
properFraction :: Scientific -> (b, Scientific)
properFraction s :: Scientific
s@(Scientific c :: Integer
c e :: Int
e)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
then (0, Scientific
s)
else case Integer
c Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e) of
(#q :: Integer
q, r :: Integer
r#) -> (Integer -> b
forall a. Num a => Integer -> a
fromInteger Integer
q, Integer -> Int -> Scientific
Scientific Integer
r Int
e)
| Bool
otherwise = (Scientific -> b
forall a. Num a => Scientific -> a
toIntegral Scientific
s, 0)
{-# INLINABLE properFraction #-}
truncate :: Scientific -> b
truncate = (Integer -> Int -> b) -> Scientific -> b
forall a. Num a => (Integer -> Int -> a) -> Scientific -> a
whenFloating ((Integer -> Int -> b) -> Scientific -> b)
-> (Integer -> Int -> b) -> Scientific -> b
forall a b. (a -> b) -> a -> b
$ \c :: Integer
c e :: Int
e ->
if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
then 0
else Integer -> b
forall a. Num a => Integer -> a
fromInteger (Integer -> b) -> Integer -> b
forall a b. (a -> b) -> a -> b
$ Integer
c Integer -> Integer -> Integer
`quotInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e)
{-# INLINABLE truncate #-}
round :: Scientific -> b
round = (Integer -> Int -> b) -> Scientific -> b
forall a. Num a => (Integer -> Int -> a) -> Scientific -> a
whenFloating ((Integer -> Int -> b) -> Scientific -> b)
-> (Integer -> Int -> b) -> Scientific -> b
forall a b. (a -> b) -> a -> b
$ \c :: Integer
c e :: Int
e ->
if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
then 0
else let (#q :: Integer
q, r :: Integer
r#) = Integer
c Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e)
n :: b
n = Integer -> b
forall a. Num a => Integer -> a
fromInteger Integer
q
m :: b
m | Integer
r Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = b
n b -> b -> b
forall a. Num a => a -> a -> a
- 1
| Bool
otherwise = b
n b -> b -> b
forall a. Num a => a -> a -> a
+ 1
f :: Scientific
f = Integer -> Int -> Scientific
Scientific Integer
r Int
e
in case Integer -> Integer
forall a. Num a => a -> a
signum (Integer -> Integer) -> Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Scientific -> Integer
coefficient (Scientific -> Integer) -> Scientific -> Integer
forall a b. (a -> b) -> a -> b
$ Scientific -> Scientific
forall a. Num a => a -> a
abs Scientific
f Scientific -> Scientific -> Scientific
forall a. Num a => a -> a -> a
- 0.5 of
-1 -> b
n
0 -> if b -> Bool
forall a. Integral a => a -> Bool
even b
n then b
n else b
m
1 -> b
m
_ -> [Char] -> b
forall a. HasCallStack => [Char] -> a
error "round default defn: Bad value"
{-# INLINABLE round #-}
ceiling :: Scientific -> b
ceiling = (Integer -> Int -> b) -> Scientific -> b
forall a. Num a => (Integer -> Int -> a) -> Scientific -> a
whenFloating ((Integer -> Int -> b) -> Scientific -> b)
-> (Integer -> Int -> b) -> Scientific -> b
forall a b. (a -> b) -> a -> b
$ \c :: Integer
c e :: Int
e ->
if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
then if Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= 0
then 0
else 1
else case Integer
c Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e) of
(#q :: Integer
q, r :: Integer
r#) | Integer
r Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= 0 -> Integer -> b
forall a. Num a => Integer -> a
fromInteger Integer
q
| Bool
otherwise -> Integer -> b
forall a. Num a => Integer -> a
fromInteger (Integer
q Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ 1)
{-# INLINABLE ceiling #-}
floor :: Scientific -> b
floor = (Integer -> Int -> b) -> Scientific -> b
forall a. Num a => (Integer -> Int -> a) -> Scientific -> a
whenFloating ((Integer -> Int -> b) -> Scientific -> b)
-> (Integer -> Int -> b) -> Scientific -> b
forall a b. (a -> b) -> a -> b
$ \c :: Integer
c e :: Int
e ->
if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
then if Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0
then -1
else 0
else Integer -> b
forall a. Num a => Integer -> a
fromInteger (Integer
c Integer -> Integer -> Integer
`divInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e))
{-# INLINABLE floor #-}
dangerouslySmall :: Integer -> Int -> Bool
dangerouslySmall :: Integer -> Int -> Bool
dangerouslySmall c :: Integer
c e :: Int
e = Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< (-Int
limit) Bool -> Bool -> Bool
&& Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< (-Integer -> Int
integerLog10' (Integer -> Integer
forall a. Num a => a -> a
abs Integer
c)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1
{-# INLINE dangerouslySmall #-}
limit :: Int
limit :: Int
limit = Int
maxExpt
positivize :: (Ord a, Num a, Num b) => (a -> b) -> (a -> b)
positivize :: (a -> b) -> a -> b
positivize f :: a -> b
f x :: a
x | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = -(a -> b
f (-a
x))
| Bool
otherwise = a -> b
f a
x
{-# INLINE positivize #-}
whenFloating :: (Num a) => (Integer -> Int -> a) -> Scientific -> a
whenFloating :: (Integer -> Int -> a) -> Scientific -> a
whenFloating f :: Integer -> Int -> a
f s :: Scientific
s@(Scientific c :: Integer
c e :: Int
e)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = Integer -> Int -> a
f Integer
c Int
e
| Bool
otherwise = Scientific -> a
forall a. Num a => Scientific -> a
toIntegral Scientific
s
{-# INLINE whenFloating #-}
toIntegral :: (Num a) => Scientific -> a
toIntegral :: Scientific -> a
toIntegral (Scientific c :: Integer
c e :: Int
e) = Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
c a -> a -> a
forall a. Num a => a -> a -> a
* Int -> a
forall a. Num a => Int -> a
magnitude Int
e
{-# INLINE toIntegral #-}
maxExpt :: Int
maxExpt :: Int
maxExpt = 324
expts10 :: Primitive.Array Integer
expts10 :: Array Integer
expts10 = (forall s. ST s (Array Integer)) -> Array Integer
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Array Integer)) -> Array Integer)
-> (forall s. ST s (Array Integer)) -> Array Integer
forall a b. (a -> b) -> a -> b
$ do
MutableArray s Integer
ma <- Int -> Integer -> ST s (MutableArray (PrimState (ST s)) Integer)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> a -> m (MutableArray (PrimState m) a)
Primitive.newArray Int
maxExpt Integer
forall error. error
uninitialised
MutableArray (PrimState (ST s)) Integer
-> Int -> Integer -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a -> Int -> a -> m ()
Primitive.writeArray MutableArray s Integer
MutableArray (PrimState (ST s)) Integer
ma 0 1
MutableArray (PrimState (ST s)) Integer
-> Int -> Integer -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a -> Int -> a -> m ()
Primitive.writeArray MutableArray s Integer
MutableArray (PrimState (ST s)) Integer
ma 1 10
let go :: Int -> ST s (Array Integer)
go !Int
ix
| Int
ix Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
maxExpt = MutableArray (PrimState (ST s)) Integer -> ST s (Array Integer)
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a -> m (Array a)
Primitive.unsafeFreezeArray MutableArray s Integer
MutableArray (PrimState (ST s)) Integer
ma
| Bool
otherwise = do
MutableArray (PrimState (ST s)) Integer
-> Int -> Integer -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a -> Int -> a -> m ()
Primitive.writeArray MutableArray s Integer
MutableArray (PrimState (ST s)) Integer
ma Int
ix Integer
xx
MutableArray (PrimState (ST s)) Integer
-> Int -> Integer -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a -> Int -> a -> m ()
Primitive.writeArray MutableArray s Integer
MutableArray (PrimState (ST s)) Integer
ma (Int
ixInt -> Int -> Int
forall a. Num a => a -> a -> a
+1) (10Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
xx)
Int -> ST s (Array Integer)
go (Int
ixInt -> Int -> Int
forall a. Num a => a -> a -> a
+2)
where
xx :: Integer
xx = Integer
x Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
x
x :: Integer
x = Array Integer -> Int -> Integer
forall a. Array a -> Int -> a
Primitive.indexArray Array Integer
expts10 Int
half
#if MIN_VERSION_base(4,5,0)
!half :: Int
half = Int
ix Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`unsafeShiftR` 1
#else
!half = ix `shiftR` 1
#endif
Int -> ST s (Array Integer)
go 2
uninitialised :: error
uninitialised :: error
uninitialised = [Char] -> error
forall a. HasCallStack => [Char] -> a
error "Data.Scientific: uninitialised element"
magnitude :: Num a => Int -> a
magnitude :: Int -> a
magnitude e :: Int
e | Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
maxExpt = Int -> a
cachedPow10 Int
e
| Bool
otherwise = Int -> a
cachedPow10 Int
hi a -> a -> a
forall a. Num a => a -> a -> a
* 10 a -> Int -> a
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
hi)
where
cachedPow10 :: Int -> a
cachedPow10 = Integer -> a
forall a. Num a => Integer -> a
fromInteger (Integer -> a) -> (Int -> Integer) -> Int -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Integer -> Int -> Integer
forall a. Array a -> Int -> a
Primitive.indexArray Array Integer
expts10
hi :: Int
hi = Int
maxExpt Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1
fromFloatDigits :: (RealFloat a) => a -> Scientific
fromFloatDigits :: a -> Scientific
fromFloatDigits 0 = 0
fromFloatDigits rf :: a
rf = (a -> Scientific) -> a -> Scientific
forall a b. (Ord a, Num a, Num b) => (a -> b) -> a -> b
positivize a -> Scientific
forall a. RealFloat a => a -> Scientific
fromPositiveRealFloat a
rf
where
fromPositiveRealFloat :: a -> Scientific
fromPositiveRealFloat r :: a
r = [Int] -> Integer -> Int -> Scientific
go [Int]
digits 0 0
where
(digits :: [Int]
digits, e :: Int
e) = Integer -> a -> ([Int], Int)
forall a. RealFloat a => Integer -> a -> ([Int], Int)
Numeric.floatToDigits 10 a
r
go :: [Int] -> Integer -> Int -> Scientific
go :: [Int] -> Integer -> Int -> Scientific
go [] !Integer
c !Int
n = Integer -> Int -> Scientific
Scientific Integer
c (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
go (d :: Int
d:ds :: [Int]
ds) !Integer
c !Int
n = [Int] -> Integer -> Int -> Scientific
go [Int]
ds (Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* 10 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
d) (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1)
{-# INLINABLE fromFloatDigits #-}
{-# SPECIALIZE fromFloatDigits :: Double -> Scientific #-}
{-# SPECIALIZE fromFloatDigits :: Float -> Scientific #-}
toRealFloat :: (RealFloat a) => Scientific -> a
toRealFloat :: Scientific -> a
toRealFloat = (a -> a) -> (a -> a) -> Either a a -> a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> a
forall a. a -> a
id a -> a
forall a. a -> a
id (Either a a -> a) -> (Scientific -> Either a a) -> Scientific -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Either a a
forall a. RealFloat a => Scientific -> Either a a
toBoundedRealFloat
{-# INLINABLE toRealFloat #-}
{-# INLINABLE toBoundedRealFloat #-}
{-# SPECIALIZE toRealFloat :: Scientific -> Double #-}
{-# SPECIALIZE toRealFloat :: Scientific -> Float #-}
{-# SPECIALIZE toBoundedRealFloat :: Scientific -> Either Double Double #-}
{-# SPECIALIZE toBoundedRealFloat :: Scientific -> Either Float Float #-}
toBoundedRealFloat :: forall a. (RealFloat a) => Scientific -> Either a a
toBoundedRealFloat :: Scientific -> Either a a
toBoundedRealFloat s :: Scientific
s@(Scientific c :: Integer
c e :: Int
e)
| Integer
c Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = a -> Either a a
forall a b. b -> Either a b
Right 0
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
limit = if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
hiLimit then a -> Either a a
forall a b. a -> Either a b
Left (a -> Either a a) -> a -> Either a a
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
sign (1a -> a -> a
forall a. Fractional a => a -> a -> a
/0)
else a -> Either a a
forall a b. b -> Either a b
Right (a -> Either a a) -> a -> Either a a
forall a b. (a -> b) -> a -> b
$ Rational -> a
forall a. Fractional a => Rational -> a
fromRational ((Integer
c Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a. Num a => Int -> a
magnitude Int
e) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% 1)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< -Int
limit = if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
loLimit Bool -> Bool -> Bool
&& Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
loLimit then a -> Either a a
forall a b. a -> Either a b
Left (a -> Either a a) -> a -> Either a a
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
sign 0
else a -> Either a a
forall a b. b -> Either a b
Right (a -> Either a a) -> a -> Either a a
forall a b. (a -> b) -> a -> b
$ Rational -> a
forall a. Fractional a => Rational -> a
fromRational (Integer
c Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e))
| Bool
otherwise = a -> Either a a
forall a b. b -> Either a b
Right (a -> Either a a) -> a -> Either a a
forall a b. (a -> b) -> a -> b
$ Rational -> a
forall a. Fractional a => Rational -> a
fromRational (Scientific -> Rational
forall a. Real a => a -> Rational
toRational Scientific
s)
where
hiLimit, loLimit :: Int
hiLimit :: Int
hiLimit = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
hi Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
log10Radix)
loLimit :: Int
loLimit = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
lo Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
log10Radix) Int -> Int -> Int
forall a. Num a => a -> a -> a
-
Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
digits Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
log10Radix)
log10Radix :: Double
log10Radix :: Double
log10Radix = Double -> Double -> Double
forall a. Floating a => a -> a -> a
logBase 10 (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
radix
radix :: Integer
radix = a -> Integer
forall a. RealFloat a => a -> Integer
floatRadix (a
forall a. HasCallStack => a
undefined :: a)
digits :: Int
digits = a -> Int
forall a. RealFloat a => a -> Int
floatDigits (a
forall a. HasCallStack => a
undefined :: a)
(lo :: Int
lo, hi :: Int
hi) = a -> (Int, Int)
forall a. RealFloat a => a -> (Int, Int)
floatRange (a
forall a. HasCallStack => a
undefined :: a)
d :: Int
d = Integer -> Int
integerLog10' (Integer -> Integer
forall a. Num a => a -> a
abs Integer
c)
sign :: p -> p
sign x :: p
x | Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = -p
x
| Bool
otherwise = p
x
toBoundedInteger :: forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger :: Scientific -> Maybe i
toBoundedInteger s :: Scientific
s
| Integer
c Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = Integer -> Maybe i
fromIntegerBounded 0
| Bool
integral = if Bool
dangerouslyBig
then Maybe i
forall a. Maybe a
Nothing
else Integer -> Maybe i
fromIntegerBounded Integer
n
| Bool
otherwise = Maybe i
forall a. Maybe a
Nothing
where
c :: Integer
c = Scientific -> Integer
coefficient Scientific
s
integral :: Bool
integral = Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 Bool -> Bool -> Bool
|| Int
e' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0
e :: Int
e = Scientific -> Int
base10Exponent Scientific
s
e' :: Int
e' = Scientific -> Int
base10Exponent Scientific
s'
s' :: Scientific
s' = Scientific -> Scientific
normalize Scientific
s
dangerouslyBig :: Bool
dangerouslyBig = Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
limit Bool -> Bool -> Bool
&&
Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Integer -> Int
integerLog10' (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max (Integer -> Integer
forall a. Num a => a -> a
abs Integer
iMinBound) (Integer -> Integer
forall a. Num a => a -> a
abs Integer
iMaxBound))
fromIntegerBounded :: Integer -> Maybe i
fromIntegerBounded :: Integer -> Maybe i
fromIntegerBounded i :: Integer
i
| Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
iMinBound Bool -> Bool -> Bool
|| Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
iMaxBound = Maybe i
forall a. Maybe a
Nothing
| Bool
otherwise = i -> Maybe i
forall a. a -> Maybe a
Just (i -> Maybe i) -> i -> Maybe i
forall a b. (a -> b) -> a -> b
$ Integer -> i
forall a. Num a => Integer -> a
fromInteger Integer
i
iMinBound :: Integer
iMinBound = i -> Integer
forall a. Integral a => a -> Integer
toInteger (i
forall a. Bounded a => a
minBound :: i)
iMaxBound :: Integer
iMaxBound = i -> Integer
forall a. Integral a => a -> Integer
toInteger (i
forall a. Bounded a => a
maxBound :: i)
n :: Integer
n :: Integer
n = Scientific -> Integer
forall a. Num a => Scientific -> a
toIntegral Scientific
s'
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Int #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Int8 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Int16 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Int32 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Int64 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Word #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Word8 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Word16 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Word32 #-}
{-# SPECIALIZE toBoundedInteger :: Scientific -> Maybe Word64 #-}
floatingOrInteger :: (RealFloat r, Integral i) => Scientific -> Either r i
floatingOrInteger :: Scientific -> Either r i
floatingOrInteger s :: Scientific
s
| Scientific -> Int
base10Exponent Scientific
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 = i -> Either r i
forall a b. b -> Either a b
Right (Scientific -> i
forall a. Num a => Scientific -> a
toIntegral Scientific
s)
| Scientific -> Int
base10Exponent Scientific
s' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 = i -> Either r i
forall a b. b -> Either a b
Right (Scientific -> i
forall a. Num a => Scientific -> a
toIntegral Scientific
s')
| Bool
otherwise = r -> Either r i
forall a b. a -> Either a b
Left (Scientific -> r
forall a. RealFloat a => Scientific -> a
toRealFloat Scientific
s')
where
s' :: Scientific
s' = Scientific -> Scientific
normalize Scientific
s
isFloating :: Scientific -> Bool
isFloating :: Scientific -> Bool
isFloating = Bool -> Bool
not (Bool -> Bool) -> (Scientific -> Bool) -> Scientific -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Bool
isInteger
isInteger :: Scientific -> Bool
isInteger :: Scientific -> Bool
isInteger s :: Scientific
s = Scientific -> Int
base10Exponent Scientific
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 Bool -> Bool -> Bool
||
Scientific -> Int
base10Exponent Scientific
s' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0
where
s' :: Scientific
s' = Scientific -> Scientific
normalize Scientific
s
instance Read Scientific where
readPrec :: ReadPrec Scientific
readPrec = ReadPrec Scientific -> ReadPrec Scientific
forall a. ReadPrec a -> ReadPrec a
Read.parens (ReadPrec Scientific -> ReadPrec Scientific)
-> ReadPrec Scientific -> ReadPrec Scientific
forall a b. (a -> b) -> a -> b
$ ReadP Scientific -> ReadPrec Scientific
forall a. ReadP a -> ReadPrec a
ReadPrec.lift (ReadP ()
ReadP.skipSpaces ReadP () -> ReadP Scientific -> ReadP Scientific
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ReadP Scientific
scientificP)
data SP = SP !Integer {-# UNPACK #-}!Int
scientificP :: ReadP Scientific
scientificP :: ReadP Scientific
scientificP = do
let positive :: ReadP Bool
positive = (('+' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==) (Char -> Bool) -> ReadP Char -> ReadP Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isSign) ReadP Bool -> ReadP Bool -> ReadP Bool
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Bool -> ReadP Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Bool
pos <- ReadP Bool
positive
let step :: Num a => a -> Int -> a
step :: a -> Int -> a
step a :: a
a digit :: Int
digit = a
a a -> a -> a
forall a. Num a => a -> a -> a
* 10 a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
digit
{-# INLINE step #-}
Integer
n <- (Integer -> Int -> Integer) -> Integer -> ReadP Integer
forall a. (a -> Int -> a) -> a -> ReadP a
foldDigits Integer -> Int -> Integer
forall a. Num a => a -> Int -> a
step 0
let s :: SP
s = Integer -> Int -> SP
SP Integer
n 0
fractional :: ReadP SP
fractional = (SP -> Int -> SP) -> SP -> ReadP SP
forall a. (a -> Int -> a) -> a -> ReadP a
foldDigits (\(SP a :: Integer
a e :: Int
e) digit :: Int
digit ->
Integer -> Int -> SP
SP (Integer -> Int -> Integer
forall a. Num a => a -> Int -> a
step Integer
a Int
digit) (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-1)) SP
s
SP coeff :: Integer
coeff expnt :: Int
expnt <- ((Char -> Bool) -> ReadP Char
ReadP.satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '.') ReadP Char -> ReadP SP -> ReadP SP
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ReadP SP
fractional)
ReadP SP -> ReadP SP -> ReadP SP
forall a. ReadP a -> ReadP a -> ReadP a
ReadP.<++ SP -> ReadP SP
forall (m :: * -> *) a. Monad m => a -> m a
return SP
s
let signedCoeff :: Integer
signedCoeff | Bool
pos = Integer
coeff
| Bool
otherwise = (-Integer
coeff)
eP :: ReadP Int
eP = do Bool
posE <- ReadP Bool
positive
Int
e <- (Int -> Int -> Int) -> Int -> ReadP Int
forall a. (a -> Int -> a) -> a -> ReadP a
foldDigits Int -> Int -> Int
forall a. Num a => a -> Int -> a
step 0
if Bool
posE
then Int -> ReadP Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
e
else Int -> ReadP Int
forall (m :: * -> *) a. Monad m => a -> m a
return (-Int
e)
((Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isE ReadP Char -> ReadP Scientific -> ReadP Scientific
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
((Integer -> Int -> Scientific
Scientific Integer
signedCoeff (Int -> Scientific) -> (Int -> Int) -> Int -> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
expnt Int -> Int -> Int
forall a. Num a => a -> a -> a
+)) (Int -> Scientific) -> ReadP Int -> ReadP Scientific
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadP Int
eP)) ReadP Scientific -> ReadP Scientific -> ReadP Scientific
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
Scientific -> ReadP Scientific
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> Int -> Scientific
Scientific Integer
signedCoeff Int
expnt)
foldDigits :: (a -> Int -> a) -> a -> ReadP a
foldDigits :: (a -> Int -> a) -> a -> ReadP a
foldDigits f :: a -> Int -> a
f z :: a
z = do
Char
c <- (Char -> Bool) -> ReadP Char
ReadP.satisfy Char -> Bool
isDecimal
let digit :: Int
digit = Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- 48
a :: a
a = a -> Int -> a
f a
z Int
digit
ReadP [Char]
ReadP.look ReadP [Char] -> ([Char] -> ReadP a) -> ReadP a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> [Char] -> ReadP a
go a
a
where
go :: a -> [Char] -> ReadP a
go !a
a [] = a -> ReadP a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
go !a
a (c :: Char
c:cs :: [Char]
cs)
| Char -> Bool
isDecimal Char
c = do
Char
_ <- ReadP Char
ReadP.get
let digit :: Int
digit = Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- 48
a -> [Char] -> ReadP a
go (a -> Int -> a
f a
a Int
digit) [Char]
cs
| Bool
otherwise = a -> ReadP a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
isDecimal :: Char -> Bool
isDecimal :: Char -> Bool
isDecimal c :: Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= '0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= '9'
{-# INLINE isDecimal #-}
isSign :: Char -> Bool
isSign :: Char -> Bool
isSign c :: Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== '+'
{-# INLINE isSign #-}
isE :: Char -> Bool
isE :: Char -> Bool
isE c :: Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== 'e' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== 'E'
{-# INLINE isE #-}
instance Show Scientific where
show :: Scientific -> [Char]
show s :: Scientific
s | Scientific -> Integer
coefficient Scientific
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = '-'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Scientific -> [Char]
showPositive (-Scientific
s)
| Bool
otherwise = Scientific -> [Char]
showPositive Scientific
s
where
showPositive :: Scientific -> String
showPositive :: Scientific -> [Char]
showPositive = ([Int], Int) -> [Char]
fmtAsGeneric (([Int], Int) -> [Char])
-> (Scientific -> ([Int], Int)) -> Scientific -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> ([Int], Int)
toDecimalDigits
fmtAsGeneric :: ([Int], Int) -> String
fmtAsGeneric :: ([Int], Int) -> [Char]
fmtAsGeneric x :: ([Int], Int)
x@(_is :: [Int]
_is, e :: Int
e)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 Bool -> Bool -> Bool
|| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 7 = ([Int], Int) -> [Char]
fmtAsExponent ([Int], Int)
x
| Bool
otherwise = ([Int], Int) -> [Char]
fmtAsFixed ([Int], Int)
x
fmtAsExponent :: ([Int], Int) -> String
fmtAsExponent :: ([Int], Int) -> [Char]
fmtAsExponent (is :: [Int]
is, e :: Int
e) =
case [Char]
ds of
"0" -> "0.0e0"
[d :: Char
d] -> Char
d Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: '.' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:'0' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: 'e' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
show_e'
(d :: Char
d:ds' :: [Char]
ds') -> Char
d Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: '.' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
ds' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ ('e' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
show_e')
[] -> [Char] -> [Char]
forall a. HasCallStack => [Char] -> a
error "formatScientific/doFmt/FFExponent: []"
where
show_e' :: [Char]
show_e' = Int -> [Char]
forall a. Show a => a -> [Char]
show (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-1)
ds :: [Char]
ds = (Int -> Char) -> [Int] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
intToDigit [Int]
is
fmtAsFixed :: ([Int], Int) -> String
fmtAsFixed :: ([Int], Int) -> [Char]
fmtAsFixed (is :: [Int]
is, e :: Int
e)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 0 = '0'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:'.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:(Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate (-Int
e) '0' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
ds)
| Bool
otherwise =
let
f :: a -> [Char] -> [Char] -> [Char]
f 0 s :: [Char]
s rs :: [Char]
rs = [Char] -> [Char]
mk0 ([Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
s) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ '.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char] -> [Char]
mk0 [Char]
rs
f n :: a
n s :: [Char]
s "" = a -> [Char] -> [Char] -> [Char]
f (a
na -> a -> a
forall a. Num a => a -> a -> a
-1) ('0'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
s) ""
f n :: a
n s :: [Char]
s (r :: Char
r:rs :: [Char]
rs) = a -> [Char] -> [Char] -> [Char]
f (a
na -> a -> a
forall a. Num a => a -> a -> a
-1) (Char
rChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
s) [Char]
rs
in
Int -> [Char] -> [Char] -> [Char]
forall a. (Eq a, Num a) => a -> [Char] -> [Char] -> [Char]
f Int
e "" [Char]
ds
where
mk0 :: [Char] -> [Char]
mk0 "" = "0"
mk0 ls :: [Char]
ls = [Char]
ls
ds :: [Char]
ds = (Int -> Char) -> [Int] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
intToDigit [Int]
is
formatScientific :: FPFormat
-> Maybe Int
-> Scientific
-> String
formatScientific :: FPFormat -> Maybe Int -> Scientific -> [Char]
formatScientific format :: FPFormat
format mbDecs :: Maybe Int
mbDecs s :: Scientific
s
| Scientific -> Integer
coefficient Scientific
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = '-'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Scientific -> [Char]
formatPositiveScientific (-Scientific
s)
| Bool
otherwise = Scientific -> [Char]
formatPositiveScientific Scientific
s
where
formatPositiveScientific :: Scientific -> String
formatPositiveScientific :: Scientific -> [Char]
formatPositiveScientific s' :: Scientific
s' = case FPFormat
format of
Generic -> ([Int], Int) -> [Char]
fmtAsGeneric (([Int], Int) -> [Char]) -> ([Int], Int) -> [Char]
forall a b. (a -> b) -> a -> b
$ Scientific -> ([Int], Int)
toDecimalDigits Scientific
s'
Exponent -> ([Int], Int) -> [Char]
fmtAsExponentMbDecs (([Int], Int) -> [Char]) -> ([Int], Int) -> [Char]
forall a b. (a -> b) -> a -> b
$ Scientific -> ([Int], Int)
toDecimalDigits Scientific
s'
Fixed -> ([Int], Int) -> [Char]
fmtAsFixedMbDecs (([Int], Int) -> [Char]) -> ([Int], Int) -> [Char]
forall a b. (a -> b) -> a -> b
$ Scientific -> ([Int], Int)
toDecimalDigits Scientific
s'
fmtAsGeneric :: ([Int], Int) -> String
fmtAsGeneric :: ([Int], Int) -> [Char]
fmtAsGeneric x :: ([Int], Int)
x@(_is :: [Int]
_is, e :: Int
e)
| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 Bool -> Bool -> Bool
|| Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 7 = ([Int], Int) -> [Char]
fmtAsExponentMbDecs ([Int], Int)
x
| Bool
otherwise = ([Int], Int) -> [Char]
fmtAsFixedMbDecs ([Int], Int)
x
fmtAsExponentMbDecs :: ([Int], Int) -> String
fmtAsExponentMbDecs :: ([Int], Int) -> [Char]
fmtAsExponentMbDecs x :: ([Int], Int)
x = case Maybe Int
mbDecs of
Nothing -> ([Int], Int) -> [Char]
fmtAsExponent ([Int], Int)
x
Just dec :: Int
dec -> Int -> ([Int], Int) -> [Char]
fmtAsExponentDecs Int
dec ([Int], Int)
x
fmtAsFixedMbDecs :: ([Int], Int) -> String
fmtAsFixedMbDecs :: ([Int], Int) -> [Char]
fmtAsFixedMbDecs x :: ([Int], Int)
x = case Maybe Int
mbDecs of
Nothing -> ([Int], Int) -> [Char]
fmtAsFixed ([Int], Int)
x
Just dec :: Int
dec -> Int -> ([Int], Int) -> [Char]
fmtAsFixedDecs Int
dec ([Int], Int)
x
fmtAsExponentDecs :: Int -> ([Int], Int) -> String
fmtAsExponentDecs :: Int -> ([Int], Int) -> [Char]
fmtAsExponentDecs dec :: Int
dec (is :: [Int]
is, e :: Int
e) =
let dec' :: Int
dec' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
dec 1 in
case [Int]
is of
[0] -> '0' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:'.' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take Int
dec' (Char -> [Char]
forall a. a -> [a]
repeat '0') [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ "e0"
_ ->
let
(ei :: Int
ei,is' :: [Int]
is') = Int -> [Int] -> (Int, [Int])
roundTo (Int
dec'Int -> Int -> Int
forall a. Num a => a -> a -> a
+1) [Int]
is
(d :: Char
d:ds' :: [Char]
ds') = (Int -> Char) -> [Int] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
intToDigit (if Int
ei Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0 then [Int] -> [Int]
forall a. [a] -> [a]
init [Int]
is' else [Int]
is')
in
Char
dChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:'.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
ds' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ 'e'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Int -> [Char]
forall a. Show a => a -> [Char]
show (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
-1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ei)
fmtAsFixedDecs :: Int -> ([Int], Int) -> String
fmtAsFixedDecs :: Int -> ([Int], Int) -> [Char]
fmtAsFixedDecs dec :: Int
dec (is :: [Int]
is, e :: Int
e) =
let dec' :: Int
dec' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
dec 0 in
if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 then
let
(ei :: Int
ei,is' :: [Int]
is') = Int -> [Int] -> (Int, [Int])
roundTo (Int
dec' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e) [Int]
is
(ls :: [Char]
ls,rs :: [Char]
rs) = Int -> [Char] -> ([Char], [Char])
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ei) ((Int -> Char) -> [Int] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
intToDigit [Int]
is')
in
[Char] -> [Char]
mk0 [Char]
ls [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ (if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
rs then "" else '.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
rs)
else
let
(ei :: Int
ei,is' :: [Int]
is') = Int -> [Int] -> (Int, [Int])
roundTo Int
dec' (Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (-Int
e) 0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int]
is)
d :: Char
d:ds' :: [Char]
ds' = (Int -> Char) -> [Int] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
intToDigit (if Int
ei Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0 then [Int]
is' else 0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
is')
in
Char
d Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: (if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
ds' then "" else '.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
ds')
where
mk0 :: [Char] -> [Char]
mk0 ls :: [Char]
ls = case [Char]
ls of { "" -> "0" ; _ -> [Char]
ls}
toDecimalDigits :: Scientific -> ([Int], Int)
toDecimalDigits :: Scientific -> ([Int], Int)
toDecimalDigits (Scientific 0 _) = ([0], 0)
toDecimalDigits (Scientific c' :: Integer
c' e' :: Int
e') =
case Integer -> Int -> Scientific
normalizePositive Integer
c' Int
e' of
Scientific c :: Integer
c e :: Int
e -> Integer -> Int -> [Int] -> ([Int], Int)
go Integer
c 0 []
where
go :: Integer -> Int -> [Int] -> ([Int], Int)
go :: Integer -> Int -> [Int] -> ([Int], Int)
go 0 !Int
n ds :: [Int]
ds = ([Int]
ds, Int
ne) where !ne :: Int
ne = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e
go i :: Integer
i !Int
n ds :: [Int]
ds = case Integer
i Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` 10 of
(# q :: Integer
q, r :: Integer
r #) -> Integer -> Int -> [Int] -> ([Int], Int)
go Integer
q (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+1) (Int
dInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
ds)
where
!d :: Int
d = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
r
normalize :: Scientific -> Scientific
normalize :: Scientific -> Scientific
normalize (Scientific c :: Integer
c e :: Int
e)
| Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> 0 = Integer -> Int -> Scientific
normalizePositive Integer
c Int
e
| Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 0 = -(Integer -> Int -> Scientific
normalizePositive (-Integer
c) Int
e)
| Bool
otherwise = Integer -> Int -> Scientific
Scientific 0 0
normalizePositive :: Integer -> Int -> Scientific
normalizePositive :: Integer -> Int -> Scientific
normalizePositive !Integer
c !Int
e = case Integer -> Integer -> (# Integer, Integer #)
quotRemInteger Integer
c 10 of
(# c' :: Integer
c', r :: Integer
r #)
| Integer
r Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 -> Integer -> Int -> Scientific
normalizePositive Integer
c' (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
+1)
| Bool
otherwise -> Integer -> Int -> Scientific
Scientific Integer
c Int
e