{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE Trustworthy #-}

#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE StandaloneDeriving #-}
#else
{-# LANGUAGE TemplateHaskell #-}
#endif

-- |
-- Module      :  Data.Scientific
-- Copyright   :  Bas van Dijk 2013
-- License     :  BSD3
-- Maintainer  :  Bas van Dijk <v.dijk.bas@gmail.com>
--
-- This module provides the number type 'Scientific'. Scientific numbers are
-- arbitrary precision and space efficient. They are represented using
-- <http://en.wikipedia.org/wiki/Scientific_notation scientific notation>. The
-- implementation uses an 'Integer' 'coefficient' @c@ and an 'Int'
-- 'base10Exponent' @e@. A scientific number corresponds to the 'Fractional'
-- number: @'fromInteger' c * 10 '^^' e@.
--
-- Note that since we're using an 'Int' to represent the exponent these numbers
-- aren't truly arbitrary precision. I intend to change the type of the exponent
-- to 'Integer' in a future release.
--
-- /WARNING:/ Although @Scientific@ has instances for all numeric classes the
-- methods should be used with caution when applied to scientific numbers coming
-- from untrusted sources. See the warnings of the instances belonging to
-- 'Scientific'.
--
-- The main application of 'Scientific' is to be used as the target of parsing
-- arbitrary precision numbers coming from an untrusted source. The advantages
-- over using 'Rational' for this are that:
--
-- * A 'Scientific' is more efficient to construct. Rational numbers need to be
-- constructed using '%' which has to compute the 'gcd' of the 'numerator' and
-- 'denominator'.
--
-- * 'Scientific' is safe against numbers with huge exponents. For example:
-- @1e1000000000 :: 'Rational'@ will fill up all space and crash your
-- program. Scientific works as expected:
--
--  > > read "1e1000000000" :: Scientific
--  > 1.0e1000000000
--
-- * Also, the space usage of converting scientific numbers with huge exponents
-- to @'Integral's@ (like: 'Int') or @'RealFloat's@ (like: 'Double' or 'Float')
-- will always be bounded by the target type.
--
-- This module is designed to be imported qualified:
--
-- @import qualified Data.Scientific as Scientific@
module Data.Scientific
    ( Scientific

      -- * Construction
    , scientific

      -- * Projections
    , coefficient
    , base10Exponent

      -- * Predicates
    , isFloating
    , isInteger

      -- * Conversions
      -- ** Rational
    , unsafeFromRational
    , fromRationalRepetend
    , fromRationalRepetendLimited
    , fromRationalRepetendUnlimited
    , toRationalRepetend

      -- ** Floating & integer
    , floatingOrInteger
    , toRealFloat
    , toBoundedRealFloat
    , toBoundedInteger
    , fromFloatDigits

      -- * Parsing
    , scientificP

      -- * Pretty printing
    , formatScientific
    , FPFormat(..)

    , toDecimalDigits

      -- * Normalization
    , normalize
    ) where


----------------------------------------------------------------------
-- Imports
----------------------------------------------------------------------

import           Control.Exception            (throw, ArithException(DivideByZero))
import           Control.Monad                (mplus)
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           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

import GHC.Integer.Compat (quotRemInteger, quotInteger, divInteger)
import Utils              (maxExpt, roundTo, magnitude)

import Language.Haskell.TH.Syntax (Lift (..))

----------------------------------------------------------------------
-- Type
----------------------------------------------------------------------

-- | An arbitrary-precision number represented using
-- <http://en.wikipedia.org/wiki/Scientific_notation scientific notation>.
--
-- This type describes the set of all @'Real's@ which have a finite
-- decimal expansion.
--
-- A scientific number with 'coefficient' @c@ and 'base10Exponent' @e@
-- corresponds to the 'Fractional' number: @'fromInteger' c * 10 '^^' e@
data Scientific = Scientific
    { Scientific -> Integer
coefficient :: !Integer
      -- ^ The coefficient of a scientific number.
      --
      -- Note that this number is not necessarily normalized, i.e.
      -- it could contain trailing zeros.
      --
      -- Scientific numbers are automatically normalized when pretty printed or
      -- in 'toDecimalDigits'.
      --
      -- Use 'normalize' to do manual normalization.
      --
      -- /WARNING:/ 'coefficient' and 'base10exponent' violate
      -- substantivity of 'Eq'.
      --
      -- >>> let x = scientific 1 2
      -- >>> let y = scientific 100 0
      -- >>> x == y
      -- True
      --
      -- but
      --
      -- >>> (coefficient x == coefficient y, base10Exponent x == base10Exponent y)
      -- (False,False)
      --

    , Scientific -> Int
base10Exponent :: {-# UNPACK #-} !Int
      -- ^ The base-10 exponent of a scientific number.
    } 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 c e@ constructs a scientific number which corresponds
-- to the 'Fractional' number: @'fromInteger' c * 10 '^^' e@.
scientific :: Integer -> Int -> Scientific
scientific :: Integer -> Int -> Scientific
scientific = Integer -> Int -> Scientific
Scientific

----------------------------------------------------------------------
-- Instances
----------------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 800
-- | @since 0.3.7.0
deriving instance Lift Scientific
#else
instance Lift Scientific where
    lift (Scientific c e) = [| Scientific c e |]
#endif


instance NFData Scientific where
    rnf :: Scientific -> ()
rnf (Scientific Integer
_ Int
_) = ()

-- | A hash can be safely calculated from a @Scientific@. No magnitude @10^e@ is
-- calculated so there's no risk of a blowup in space or time when hashing
-- scientific numbers coming from untrusted sources.
--
-- >>> import Data.Hashable (hash)
-- >>> let x = scientific 1 2
-- >>> let y = scientific 100 0
-- >>> (x == y, hash x == hash y)
-- (True,True)
--
instance Hashable Scientific where
    hashWithSalt :: Int -> Scientific -> Int
hashWithSalt Int
salt 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 Integer
c Int
e = Scientific -> Scientific
normalize Scientific
s

-- | Note that in the future I intend to change the type of the 'base10Exponent'
-- from @Int@ to @Integer@. To be forward compatible the @Binary@ instance
-- already encodes the exponent as 'Integer'.
instance Binary Scientific where
    put :: Scientific -> Put
put (Scientific Integer
c 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)

-- | Scientific numbers can be safely compared for equality. No magnitude @10^e@
-- is calculated so there's no risk of a blowup in space or time when comparing
-- scientific numbers coming from untrusted sources.
instance Eq Scientific where
    Scientific
s1 == :: Scientific -> Scientific -> Bool
== 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 Integer
c1 Int
e1 = Scientific -> Scientific
normalize Scientific
s1
        Scientific Integer
c2 Int
e2 = Scientific -> Scientific
normalize Scientific
s2

-- | Scientific numbers can be safely compared for ordering. No magnitude @10^e@
-- is calculated so there's no risk of a blowup in space or time when comparing
-- scientific numbers coming from untrusted sources.
instance Ord Scientific where
    compare :: Scientific -> Scientific -> Ordering
compare Scientific
s1 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
< Integer
0    = if Integer
c2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
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
> Integer
0    = if Integer
c2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
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
> Integer
0 then Ordering
LT else Ordering
GT
      where
        Scientific Integer
c1 Int
e1 = Scientific -> Scientific
normalize Scientific
s1
        Scientific Integer
c2 Int
e2 = Scientific -> Scientific
normalize Scientific
s2

        cmp :: Integer -> Int -> Integer -> Int -> Ordering
cmp Integer
cx Int
ex Integer
cy 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
< Int
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
> Int
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

-- | /WARNING:/ '+' and '-' compute the 'Integer' magnitude: @10^e@ where @e@ is
-- the difference between the @'base10Exponent's@ of the arguments. If these
-- methods are applied to arguments which have huge exponents this could fill up
-- all space and crash your program! So don't apply these methods to scientific
-- numbers coming from untrusted sources. The other methods can be used safely.
instance Num Scientific where
    Scientific Integer
c1 Int
e1 + :: Scientific -> Scientific -> Scientific
+ Scientific Integer
c2 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 Integer
c1 Int
e1 - :: Scientific -> Scientific -> Scientific
- Scientific Integer
c2 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 Integer
c1 Int
e1 * :: Scientific -> Scientific -> Scientific
* Scientific Integer
c2 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 Integer
c 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 Integer
c 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 Integer
c Int
_) = Integer -> Int -> Scientific
Scientific (Integer -> Integer
forall a. Num a => a -> a
signum Integer
c) Int
0
    {-# INLINABLE signum #-}

    fromInteger :: Integer -> Scientific
fromInteger Integer
i = Integer -> Int -> Scientific
Scientific Integer
i Int
0
    {-# INLINABLE fromInteger #-}

-- | /WARNING:/ 'toRational' needs to compute the 'Integer' magnitude:
-- @10^e@. If applied to a huge exponent this could fill up all space
-- and crash your program!
--
-- Avoid applying 'toRational' (or 'realToFrac') to scientific numbers
-- coming from an untrusted source and use 'toRealFloat' instead. The
-- latter guards against excessive space usage.
instance Real Scientific where
    toRational :: Scientific -> Rational
toRational (Scientific Integer
c Int
e)
      | Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
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
% Integer
1
    {-# INLINABLE toRational #-}

{-# RULES
  "realToFrac_toRealFloat_Double"
   realToFrac = toRealFloat :: Scientific -> Double #-}

{-# RULES
  "realToFrac_toRealFloat_Float"
   realToFrac = toRealFloat :: Scientific -> Float #-}

-- | /WARNING:/ 'recip' and '/' will throw an error when their outputs are
-- <https://en.wikipedia.org/wiki/Repeating_decimal repeating decimals>.
--
-- These methods also compute 'Integer' magnitudes (@10^e@). If these methods
-- are applied to arguments which have huge exponents this could fill up all
-- space and crash your program! So don't apply these methods to scientific
-- numbers coming from untrusted sources.
--
-- 'fromRational' will throw an error when the input 'Rational' is a repeating
-- decimal.  Consider using 'fromRationalRepetend' for these rationals which
-- will detect the repetition and indicate where it starts.
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

    Scientific Integer
c1 Int
e1 / :: Scientific -> Scientific -> Scientific
/ Scientific Integer
c2 Int
e2
        | Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = Rational -> Scientific
forall a. Fractional a => Rational -> a
fromRational (Rational
x 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
d))))
        | Bool
otherwise = Rational -> Scientific
forall a. Fractional a => Rational -> a
fromRational (Rational
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
*  Integer -> Rational
forall a. Num a => Integer -> a
fromInteger (Int -> Integer
forall a. Num a => Int -> a
magnitude   Int
d))
      where
        d :: Int
d = Int
e1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e2
        x :: Rational
x = Integer
c1 Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
c2

    fromRational :: Rational -> Scientific
fromRational Rational
rational =
        case Maybe Int
mbRepetendIx of
          Maybe Int
Nothing -> Scientific
s
          Just Int
_ix -> [Char] -> Scientific
forall a. HasCallStack => [Char] -> a
error ([Char] -> Scientific) -> [Char] -> Scientific
forall a b. (a -> b) -> a -> b
$
            [Char]
"fromRational has been applied to a repeating decimal " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
            [Char]
"which can't be represented as a Scientific! " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
            [Char]
"It's better to avoid performing fractional operations on Scientifics " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
            [Char]
"and convert them to other fractional types like Double as early as possible."
      where
        (Scientific
s, Maybe Int
mbRepetendIx) = Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited Rational
rational

-- | Although 'fromRational' is unsafe because it will throw errors on
-- <https://en.wikipedia.org/wiki/Repeating_decimal repeating decimals>,
-- @unsafeFromRational@ is even more unsafe because it will diverge instead (i.e
-- loop and consume all space). Though it will be more efficient because it
-- doesn't need to consume space linear in the number of digits in the resulting
-- scientific to detect the repetition.
--
-- Consider using 'fromRationalRepetend' for these rationals which will detect
-- the repetition and indicate where it starts.
unsafeFromRational :: Rational -> Scientific
unsafeFromRational :: Rational -> Scientific
unsafeFromRational Rational
rational
    | Integer
d Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
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 Integer
0 Int
0) (Rational -> Integer
forall a. Ratio a -> a
numerator Rational
rational)
  where
    -- Divide the numerator by the denominator using long division.
    longDiv :: Integer -> Int -> (Integer -> Scientific)
    longDiv :: Integer -> Int -> Integer -> Scientific
longDiv !Integer
c !Int
e  Integer
0 = Integer -> Int -> Scientific
Scientific Integer
c Int
e
    longDiv !Integer
c !Int
e !Integer
n
                      -- TODO: Use a logarithm here!
        | 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
* Integer
10) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10)
        | Bool
otherwise = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
d of
                        (#Integer
q, 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

-- | Like 'fromRational' and 'unsafeFromRational', this function converts a
-- `Rational` to a `Scientific` but instead of failing or diverging (i.e loop
-- and consume all space) on
-- <https://en.wikipedia.org/wiki/Repeating_decimal repeating decimals>
-- it detects the repeating part, the /repetend/, and returns where it starts.
--
-- To detect the repetition this function consumes space linear in the number of
-- digits in the resulting scientific. In order to bound the space usage an
-- optional limit can be specified. If the number of digits reaches this limit
-- @Left (s, r)@ will be returned. Here @s@ is the 'Scientific' constructed so
-- far and @r@ is the remaining 'Rational'. @toRational s + r@ yields the
-- original 'Rational'
--
-- If the limit is not reached or no limit was specified @Right (s,
-- mbRepetendIx)@ will be returned. Here @s@ is the 'Scientific' without any
-- repetition and @mbRepetendIx@ specifies if and where in the fractional part
-- the repetend begins.
--
-- For example:
--
-- @fromRationalRepetend Nothing (1 % 28) == Right (3.571428e-2, Just 2)@
--
-- This represents the repeating decimal: @0.03571428571428571428...@
-- which is sometimes also unambiguously denoted as @0.03(571428)@.
-- Here the repetend is enclosed in parentheses and starts at the 3rd digit (index 2)
-- in the fractional part. Specifying a limit results in the following:
--
-- @fromRationalRepetend (Just 4) (1 % 28) == Left (3.5e-2, 1 % 1400)@
--
-- You can expect the following property to hold.
--
-- @ forall (mbLimit :: Maybe Int) (r :: Rational).
-- r == (case 'fromRationalRepetend' mbLimit r of
--        Left (s, r') -> toRational s + r'
--        Right (s, mbRepetendIx) ->
--          case mbRepetendIx of
--            Nothing         -> toRational s
--            Just repetendIx -> 'toRationalRepetend' s repetendIx)
-- @
fromRationalRepetend
    :: Maybe Int -- ^ Optional limit
    -> Rational
    -> Either (Scientific, Rational)
              (Scientific, Maybe Int)
fromRationalRepetend :: Maybe Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetend Maybe Int
mbLimit Rational
rational =
    case Maybe Int
mbLimit of
      Maybe Int
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 Int
l  -> Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetendLimited Int
l Rational
rational

-- | Like 'fromRationalRepetend' but always accepts a limit.
fromRationalRepetendLimited
    :: Int -- ^ limit
    -> Rational
    -> Either (Scientific, Rational)
              (Scientific, Maybe Int)
fromRationalRepetendLimited :: Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetendLimited Int
l Rational
rational
        | Integer
d Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
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
< Integer
0   = case Integer -> Either (Scientific, Rational) (Scientific, Maybe Int)
longDiv (-Integer
num) of
                        Left  (Scientific
s, Rational
r)  -> (Scientific, Rational)
-> Either (Scientific, Rational) (Scientific, Maybe Int)
forall a b. a -> Either a b
Left  (-Scientific
s, -Rational
r)
                        Right (Scientific
s, 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 Integer
0 Int
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 Map Integer Int
_ns Integer
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  Map Integer Int
ns !Integer
n
            | Just 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
* Integer
10) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Map Integer Int
ns' (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10)
            | Bool
otherwise = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
d of
                            (#Integer
q, 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

-- | Like 'fromRationalRepetend' but doesn't accept a limit.
fromRationalRepetendUnlimited :: Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited :: Rational -> (Scientific, Maybe Int)
fromRationalRepetendUnlimited Rational
rational
        | Integer
d Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
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
< Integer
0   = case Integer -> (Scientific, Maybe Int)
longDiv (-Integer
num) of
                        (Scientific
s, 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 Integer
0 Int
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 Map Integer Int
_ns Integer
0 = (Integer -> Int -> Scientific
Scientific Integer
c Int
e, Maybe Int
forall a. Maybe a
Nothing)
        longDivNoLimit !Integer
c !Int
e  Map Integer Int
ns !Integer
n
            | Just 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
* Integer
10) (Int
e Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Map Integer Int
ns' (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10)
            | Bool
otherwise = case Integer
n Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
d of
                            (#Integer
q, 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

-- |
-- Converts a `Scientific` with a /repetend/ (a repeating part in the fraction),
-- which starts at the given index, into its corresponding 'Rational'.
--
-- For example to convert the repeating decimal @0.03(571428)@ you would use:
-- @toRationalRepetend 0.03571428 2 == 1 % 28@
--
-- Preconditions for @toRationalRepetend s r@:
--
-- * @r >= 0@
--
-- * @r < -(base10Exponent s)@
--
-- /WARNING:/ @toRationalRepetend@ needs to compute the 'Integer' magnitude:
-- @10^^n@. Where @n@ is based on the 'base10Exponent` of the scientific. If
-- applied to a huge exponent this could fill up all space and crash your
-- program! So don't apply this function to untrusted input.
--
-- The formula to convert the @Scientific@ @s@
-- with a repetend starting at index @r@ is described in the paper:
-- <http://fiziko.bureau42.com/teaching_tidbits/turning_repeating_decimals_into_fractions.pdf turning_repeating_decimals_into_fractions.pdf>
-- and is defined as follows:
--
-- @
--   (fromInteger nonRepetend + repetend % nines) /
--   fromInteger (10^^r)
-- where
--   c  = coefficient s
--   e  = base10Exponent s
--
--   -- Size of the fractional part.
--   f = (-e)
--
--   -- Size of the repetend.
--   n = f - r
--
--   m = 10^^n
--
--   (nonRepetend, repetend) = c \`quotRem\` m
--
--   nines = m - 1
-- @
-- Also see: 'fromRationalRepetend'.
toRationalRepetend
    :: Scientific
    -> Int -- ^ Repetend index
    -> Rational
toRationalRepetend :: Scientific -> Int -> Rational
toRationalRepetend Scientific
s Int
r
    | Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0  = [Char] -> Rational
forall a. HasCallStack => [Char] -> a
error [Char]
"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 [Char]
"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

    -- Size of the fractional part.
    f :: Int
f = (-Int
e)

    -- Size of the repetend.
    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

    (#Integer
nonRepetend, 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
- Integer
1

-- | /WARNING:/ the methods of the @RealFrac@ instance need to compute the
-- magnitude @10^e@. If applied to a huge exponent this could take a long
-- time. Even worse, when the destination type is unbounded (i.e. 'Integer') it
-- could fill up all space and crash your program!
instance RealFrac Scientific where
    -- | The function 'properFraction' takes a Scientific number @s@
    -- and returns a pair @(n,f)@ such that @s = n+f@, and:
    --
    -- * @n@ is an integral number with the same sign as @s@; and
    --
    -- * @f@ is a fraction with the same type and sign as @s@,
    --   and with absolute value less than @1@.
    properFraction :: Scientific -> (b, Scientific)
properFraction s :: Scientific
s@(Scientific Integer
c Int
e)
        | Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
                      then (b
0, Scientific
s)
                      else case Integer
c Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e) of
                             (#Integer
q, 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, Scientific
0)
    {-# INLINABLE properFraction #-}

    -- | @'truncate' s@ returns the integer nearest @s@
    -- between zero and @s@
    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
$ \Integer
c Int
e ->
                 if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
                 then b
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' s@ returns the nearest integer to @s@;
    --   the even integer if @s@ is equidistant between two integers
    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
$ \Integer
c Int
e ->
              if Integer -> Int -> Bool
dangerouslySmall Integer
c Int
e
              then b
0
              else let (#Integer
q, 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
< Integer
0     = b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1
                         | Bool
otherwise = b
n b -> b -> b
forall a. Num a => a -> a -> a
+ b
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
- Scientific
0.5 of
                        -1 -> b
n
                        Integer
0  -> if b -> Bool
forall a. Integral a => a -> Bool
even b
n then b
n else b
m
                        Integer
1  -> b
m
                        Integer
_  -> [Char] -> b
forall a. HasCallStack => [Char] -> a
error [Char]
"round default defn: Bad value"
    {-# INLINABLE round #-}

    -- | @'ceiling' s@ returns the least integer not less than @s@
    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
$ \Integer
c 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
<= Integer
0
                     then b
0
                     else b
1
                else case Integer
c Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Int -> Integer
forall a. Num a => Int -> a
magnitude (-Int
e) of
                       (#Integer
q, Integer
r#) | Integer
r Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
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
+ Integer
1)
    {-# INLINABLE ceiling #-}

    -- | @'floor' s@ returns the greatest integer not greater than @s@
    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
$ \Integer
c 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
< Integer
0
                   then -b
1
                   else b
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 #-}


----------------------------------------------------------------------
-- Internal utilities
----------------------------------------------------------------------

-- | This function is used in the 'RealFrac' methods to guard against
-- computing a huge magnitude (-e) which could take up all space.
--
-- Think about parsing a scientific number from an untrusted
-- string. An attacker could supply 1e-1000000000. Lets say we want to
-- 'floor' that number to an 'Int'. When we naively try to floor it
-- using:
--
-- @
-- floor = whenFloating $ \c e ->
--           fromInteger (c `div` magnitude (-e))
-- @
--
-- We will compute the huge Integer: @magnitude 1000000000@. This
-- computation will quickly fill up all space and crash the program.
--
-- Note that for large /positive/ exponents there is no risk of a
-- space-leak since 'whenFloating' will compute:
--
-- @fromInteger c * magnitude e :: a@
--
-- where @a@ is the target type (Int in this example). So here the
-- space usage is bounded by the target type.
--
-- For large negative exponents we check if the exponent is smaller
-- than some limit (currently -324). In that case we know that the
-- scientific number is really small (unless the coefficient has many
-- digits) so we can immediately return -1 for negative scientific
-- numbers or 0 for positive numbers.
--
-- More precisely if @dangerouslySmall c e@ returns 'True' the
-- scientific number @s@ is guaranteed to be between:
-- @-0.1 > s < 0.1@.
--
-- Note that we avoid computing the number of decimal digits in c
-- (log10 c) if the exponent is not below the limit.
dangerouslySmall :: Integer -> Int -> Bool
dangerouslySmall :: Integer -> Int -> Bool
dangerouslySmall Integer
c 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
- Int
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 a -> b
f a
x | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
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 Integer -> Int -> a
f s :: Scientific
s@(Scientific Integer
c Int
e)
    | Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = Integer -> Int -> a
f Integer
c Int
e
    | Bool
otherwise = Scientific -> a
forall a. Num a => Scientific -> a
toIntegral Scientific
s
{-# INLINE whenFloating #-}

-- | Precondition: the 'Scientific' @s@ needs to be an integer:
-- @base10Exponent (normalize s) >= 0@
toIntegral :: (Num a) => Scientific -> a
toIntegral :: Scientific -> a
toIntegral (Scientific Integer
c 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 #-}






----------------------------------------------------------------------
-- Conversions
----------------------------------------------------------------------

-- | Convert a 'RealFloat' (like a 'Double' or 'Float') into a 'Scientific'
-- number.
--
-- Note that this function uses 'Numeric.floatToDigits' to compute the digits
-- and exponent of the 'RealFloat' number. Be aware that the algorithm used in
-- 'Numeric.floatToDigits' doesn't work as expected for some numbers, e.g. as
-- the 'Double' @1e23@ is converted to @9.9999999999999991611392e22@, and that
-- value is shown as @9.999999999999999e22@ rather than the shorter @1e23@; the
-- algorithm doesn't take the rounding direction for values exactly half-way
-- between two adjacent representable values into account, so if you have a
-- value with a short decimal representation exactly half-way between two
-- adjacent representable values, like @5^23*2^e@ for @e@ close to 23, the
-- algorithm doesn't know in which direction the short decimal representation
-- would be rounded and computes more digits
fromFloatDigits :: (RealFloat a) => a -> Scientific
fromFloatDigits :: a -> Scientific
fromFloatDigits a
0  = Scientific
0
fromFloatDigits 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 a
r = [Int] -> Integer -> Int -> Scientific
go [Int]
digits Integer
0 Int
0
        where
          ([Int]
digits, Int
e) = Integer -> a -> ([Int], Int)
forall a. RealFloat a => Integer -> a -> ([Int], Int)
Numeric.floatToDigits Integer
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 (Int
d:[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
* Integer
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
+ Int
1)

{-# INLINABLE fromFloatDigits #-}

{-# SPECIALIZE fromFloatDigits :: Double -> Scientific #-}
{-# SPECIALIZE fromFloatDigits :: Float  -> Scientific #-}

-- | Safely convert a 'Scientific' number into a 'RealFloat' (like a 'Double' or a
-- 'Float').
--
-- Note that this function uses 'realToFrac' (@'fromRational' . 'toRational'@)
-- internally but it guards against computing huge Integer magnitudes (@10^e@)
-- that could fill up all space and crash your program. If the 'base10Exponent'
-- of the given 'Scientific' is too big or too small to be represented in the
-- target type, Infinity or 0 will be returned respectively. Use
-- 'toBoundedRealFloat' which explicitly handles this case by returning 'Left'.
--
-- Always prefer 'toRealFloat' over 'realToFrac' when converting from scientific
-- numbers coming from an untrusted source.
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  #-}

-- | Preciser version of `toRealFloat`. If the 'base10Exponent' of the given
-- 'Scientific' is too big or too small to be represented in the target type,
-- Infinity or 0 will be returned as 'Left'.
toBoundedRealFloat :: forall a. (RealFloat a) => Scientific -> Either a a
toBoundedRealFloat :: Scientific -> Either a a
toBoundedRealFloat s :: Scientific
s@(Scientific Integer
c Int
e)
    | Integer
c Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0     = a -> Either a a
forall a b. b -> Either a b
Right a
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 (a
1a -> a -> a
forall a. Fractional a => a -> a -> a
/a
0) -- Infinity
                   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
% Integer
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 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 -> 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)
                       -- We can't use realToFrac here
                       -- because that will cause an infinite loop
                       -- when the function is specialized for Double and Float
                       -- caused by the realToFrac_toRealFloat_Double/Float rewrite RULEs.
  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 Double
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)
    (Int
lo, 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 p
x | Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0     = -p
x
           | Bool
otherwise =  p
x

-- | Convert a `Scientific` to a bounded integer.
--
-- If the given `Scientific` doesn't fit in the target representation, it will
-- return `Nothing`.
--
-- This function also guards against computing huge Integer magnitudes (@10^e@)
-- that could fill up all space and crash your program.
toBoundedInteger :: forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger :: Scientific -> Maybe i
toBoundedInteger Scientific
s
    | Integer
c Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0    = Integer -> Maybe i
fromIntegerBounded Integer
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
>= Int
0 Bool -> Bool -> Bool
|| Int
e' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
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 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)

    -- This should not be evaluated if the given Scientific is dangerouslyBig
    -- since it could consume all space and crash the process:
    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@ determines if the scientific is floating point or
-- integer.
--
-- In case it's floating-point the scientific is converted to the desired
-- 'RealFloat' using 'toRealFloat' and wrapped in 'Left'.
--
-- In case it's integer to scientific is converted to the desired 'Integral' and
-- wrapped in 'Right'.
--
-- /WARNING:/ To convert the scientific to an integral the magnitude @10^e@
-- needs to be computed. If applied to a huge exponent this could take a long
-- time. Even worse, when the destination type is unbounded (i.e. 'Integer') it
-- could fill up all space and crash your program! So don't apply this function
-- to untrusted input but use 'toBoundedInteger' instead.
--
-- Also see: 'isFloating' or 'isInteger'.
floatingOrInteger :: (RealFloat r, Integral i) => Scientific -> Either r i
floatingOrInteger :: Scientific -> Either r i
floatingOrInteger Scientific
s
    | Scientific -> Int
base10Exponent Scientific
s  Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
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
>= Int
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


----------------------------------------------------------------------
-- Predicates
----------------------------------------------------------------------

-- | Return 'True' if the scientific is a floating point, 'False' otherwise.
--
-- Also see: 'floatingOrInteger'.
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

-- | Return 'True' if the scientific is an integer, 'False' otherwise.
--
-- Also see: 'floatingOrInteger'.
isInteger :: Scientific -> Bool
isInteger :: Scientific -> Bool
isInteger Scientific
s = Scientific -> Int
base10Exponent Scientific
s  Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
||
              Scientific -> Int
base10Exponent Scientific
s' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
  where
    s' :: Scientific
s' = Scientific -> Scientific
normalize Scientific
s


----------------------------------------------------------------------
-- Parsing
----------------------------------------------------------------------

-- | Supports the skipping of parentheses and whitespaces. Example:
--
-- > > read " ( ((  -1.0e+3 ) ))" :: Scientific
-- > -1000.0
--
-- (Note: This @Read@ instance makes internal use of
-- 'scientificP' to parse the floating-point number.)
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)

-- A strict pair
data SP = SP !Integer {-# UNPACK #-}!Int

-- | A parser for parsing a floating-point
-- number into a 'Scientific' value. Example:
--
-- > > import Text.ParserCombinators.ReadP (readP_to_S)
-- > > readP_to_S scientificP "3"
-- > [(3.0,"")]
-- > > readP_to_S scientificP "3.0e2"
-- > [(3.0,"e2"),(300.0,"")]
-- > > readP_to_S scientificP "+3.0e+2"
-- > [(3.0,"e+2"),(300.0,"")]
-- > > readP_to_S scientificP "-3.0e-2"
-- > [(-3.0,"e-2"),(-3.0e-2,"")]
--
-- Note: This parser only parses the number itself; it does
-- not parse any surrounding parentheses or whitespaces.
scientificP :: ReadP Scientific
scientificP :: ReadP Scientific
scientificP = do
  let positive :: ReadP Bool
positive = ((Char
'+' 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 Int
digit = a
a a -> a -> a
forall a. Num a => 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 Integer
0

  let s :: SP
s = Integer -> Int -> SP
SP Integer
n Int
0
      fractional :: ReadP SP
fractional = (SP -> Int -> SP) -> SP -> ReadP SP
forall a. (a -> Int -> a) -> a -> ReadP a
foldDigits (\(SP Integer
a Int
e) 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
-Int
1)) SP
s

  SP Integer
coeff Int
expnt <- ((Char -> Bool) -> ReadP Char
ReadP.satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') 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 Int
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 a -> Int -> a
f 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
- Int
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 (Char
c:[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
- Int
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 Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9'
{-# INLINE isDecimal #-}

isSign :: Char -> Bool
isSign :: Char -> Bool
isSign Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+'
{-# INLINE isSign #-}

isE :: Char -> Bool
isE :: Char -> Bool
isE Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'e' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'E'
{-# INLINE isE #-}


----------------------------------------------------------------------
-- Pretty Printing
----------------------------------------------------------------------

-- | See 'formatScientific' if you need more control over the rendering.
instance Show Scientific where
    showsPrec :: Int -> Scientific -> [Char] -> [Char]
showsPrec Int
d Scientific
s
        | Scientific -> Integer
coefficient Scientific
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Bool -> ([Char] -> [Char]) -> [Char] -> [Char]
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
prefixMinusPrec) (([Char] -> [Char]) -> [Char] -> [Char])
-> ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
               Char -> [Char] -> [Char]
showChar Char
'-' ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> [Char] -> [Char]
showPositive (-Scientific
s)
        | Bool
otherwise         = Scientific -> [Char] -> [Char]
showPositive   Scientific
s
      where
        prefixMinusPrec :: Int
        prefixMinusPrec :: Int
prefixMinusPrec = Int
6

        showPositive :: Scientific -> ShowS
        showPositive :: Scientific -> [Char] -> [Char]
showPositive = [Char] -> [Char] -> [Char]
showString ([Char] -> [Char] -> [Char])
-> (Scientific -> [Char]) -> Scientific -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([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@([Int]
_is, Int
e)
            | 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 = ([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 ([Int]
is, Int
e) =
    case [Char]
ds of
      [Char]
"0"     -> [Char]
"0.0e0"
      [Char
d]     -> Char
d Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
'.' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
'0' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
'e' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
show_e'
      (Char
d:[Char]
ds') -> Char
d Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Char
'.' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
ds' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ (Char
'e' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: [Char]
show_e')
      []      -> [Char] -> [Char]
forall a. HasCallStack => [Char] -> a
error [Char]
"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
-Int
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 ([Int]
is, Int
e)
    | Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = Char
'0'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
'.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:(Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate (-Int
e) Char
'0' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
ds)
    | Bool
otherwise =
        let
           f :: a -> [Char] -> [Char] -> [Char]
f a
0 [Char]
s    [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] -> [Char]
forall a. a -> [a] -> [a]
:[Char] -> [Char]
mk0 [Char]
rs
           f a
n [Char]
s    [Char]
""  = a -> [Char] -> [Char] -> [Char]
f (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1) (Char
'0'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
s) [Char]
""
           f a
n [Char]
s (Char
r:[Char]
rs) = a -> [Char] -> [Char] -> [Char]
f (a
na -> a -> a
forall a. Num a => 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]
"" [Char]
ds
  where
    mk0 :: [Char] -> [Char]
mk0 [Char]
"" = [Char]
"0"
    mk0 [Char]
ls = [Char]
ls

    ds :: [Char]
ds = (Int -> Char) -> [Int] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
intToDigit [Int]
is

-- | Like 'show' but provides rendering options.
formatScientific :: FPFormat
                 -> Maybe Int  -- ^ Number of decimal places to render.
                 -> Scientific
                 -> String
formatScientific :: FPFormat -> Maybe Int -> Scientific -> [Char]
formatScientific FPFormat
format Maybe Int
mbDecs Scientific
s
    | Scientific -> Integer
coefficient Scientific
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Char
'-'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 Scientific
s' = case FPFormat
format of
        FPFormat
Generic  -> ([Int], Int) -> [Char]
fmtAsGeneric        (([Int], Int) -> [Char]) -> ([Int], Int) -> [Char]
forall a b. (a -> b) -> a -> b
$ Scientific -> ([Int], Int)
toDecimalDigits Scientific
s'
        FPFormat
Exponent -> ([Int], Int) -> [Char]
fmtAsExponentMbDecs (([Int], Int) -> [Char]) -> ([Int], Int) -> [Char]
forall a b. (a -> b) -> a -> b
$ Scientific -> ([Int], Int)
toDecimalDigits Scientific
s'
        FPFormat
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@([Int]
_is, Int
e)
        | 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 = ([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 ([Int], Int)
x = case Maybe Int
mbDecs of
                              Maybe Int
Nothing  -> ([Int], Int) -> [Char]
fmtAsExponent ([Int], Int)
x
                              Just Int
dec -> Int -> ([Int], Int) -> [Char]
fmtAsExponentDecs Int
dec ([Int], Int)
x

    fmtAsFixedMbDecs :: ([Int], Int) -> String
    fmtAsFixedMbDecs :: ([Int], Int) -> [Char]
fmtAsFixedMbDecs ([Int], Int)
x = case Maybe Int
mbDecs of
                           Maybe Int
Nothing  -> ([Int], Int) -> [Char]
fmtAsFixed ([Int], Int)
x
                           Just Int
dec -> Int -> ([Int], Int) -> [Char]
fmtAsFixedDecs Int
dec ([Int], Int)
x

    fmtAsExponentDecs :: Int -> ([Int], Int) -> String
    fmtAsExponentDecs :: Int -> ([Int], Int) -> [Char]
fmtAsExponentDecs Int
dec ([Int]
is, Int
e) =
        let dec' :: Int
dec' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
dec Int
1 in
            case [Int]
is of
             [Int
0] -> Char
'0' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:Char
'.' 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 Char
'0') [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"e0"
             [Int]
_ ->
              let
               (Int
ei,[Int]
is') = Int -> [Int] -> (Int, [Int])
roundTo (Int
dec'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [Int]
is
               (Char
d:[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
> Int
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] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
ds' [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Char
'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
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
ei)

    fmtAsFixedDecs :: Int -> ([Int], Int) -> String
    fmtAsFixedDecs :: Int -> ([Int], Int) -> [Char]
fmtAsFixedDecs Int
dec ([Int]
is, Int
e) =
        let dec' :: Int
dec' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
dec Int
0 in
        if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then
         let
          (Int
ei,[Int]
is') = Int -> [Int] -> (Int, [Int])
roundTo (Int
dec' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e) [Int]
is
          ([Char]
ls,[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 [Char]
"" else Char
'.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
rs)
        else
         let
          (Int
ei,[Int]
is') = Int -> [Int] -> (Int, [Int])
roundTo Int
dec' (Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (-Int
e) Int
0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int]
is)
          Char
d:[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
> Int
0 then [Int]
is' else Int
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 [Char]
"" else Char
'.'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
ds')
      where
        mk0 :: [Char] -> [Char]
mk0 [Char]
ls = case [Char]
ls of { [Char]
"" -> [Char]
"0" ; [Char]
_ -> [Char]
ls}

----------------------------------------------------------------------

-- | Similar to 'Numeric.floatToDigits', @toDecimalDigits@ takes a
-- positive 'Scientific' number, and returns a list of digits and
-- a base-10 exponent. In particular, if @x>=0@, and
--
-- > toDecimalDigits x = ([d1,d2,...,dn], e)
--
-- then
--
--     1. @n >= 1@
--     2. @x = 0.d1d2...dn * (10^^e)@
--     3. @0 <= di <= 9@
--     4. @null $ takeWhile (==0) $ reverse [d1,d2,...,dn]@
--
-- The last property means that the coefficient will be normalized, i.e. doesn't
-- contain trailing zeros.
toDecimalDigits :: Scientific -> ([Int], Int)
toDecimalDigits :: Scientific -> ([Int], Int)
toDecimalDigits (Scientific Integer
0  Int
_)  = ([Int
0], Int
0)
toDecimalDigits (Scientific Integer
c' Int
e') =
    case Integer -> Int -> Scientific
normalizePositive Integer
c' Int
e' of
      Scientific Integer
c Int
e -> Integer -> Int -> [Int] -> ([Int], Int)
go Integer
c Int
0 []
        where
          go :: Integer -> Int -> [Int] -> ([Int], Int)
          go :: Integer -> Int -> [Int] -> ([Int], Int)
go Integer
0 !Int
n [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 Integer
i !Int
n [Int]
ds = case Integer
i Integer -> Integer -> (# Integer, Integer #)
`quotRemInteger` Integer
10 of
                         (# Integer
q, Integer
r #) -> Integer -> Int -> [Int] -> ([Int], Int)
go Integer
q (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
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


----------------------------------------------------------------------
-- Normalization
----------------------------------------------------------------------

-- | Normalize a scientific number by dividing out powers of 10 from the
-- 'coefficient' and incrementing the 'base10Exponent' each time.
--
-- You should rarely have a need for this function since scientific numbers are
-- automatically normalized when pretty-printed and in 'toDecimalDigits'.
normalize :: Scientific -> Scientific
normalize :: Scientific -> Scientific
normalize (Scientific Integer
c Int
e)
    | Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 =   Integer -> Int -> Scientific
normalizePositive   Integer
c  Int
e
    | Integer
c Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = -(Integer -> Int -> Scientific
normalizePositive (-Integer
c) Int
e)
    | Bool
otherwise {- c == 0 -} = Integer -> Int -> Scientific
Scientific Integer
0 Int
0

normalizePositive :: Integer -> Int -> Scientific
normalizePositive :: Integer -> Int -> Scientific
normalizePositive !Integer
c !Int
e = case Integer -> Integer -> (# Integer, Integer #)
quotRemInteger Integer
c Integer
10 of
                            (# Integer
c', Integer
r #)
                                | Integer
r Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0    -> Integer -> Int -> Scientific
normalizePositive Integer
c' (Int
eInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
                                | Bool
otherwise -> Integer -> Int -> Scientific
Scientific Integer
c Int
e