scientific-0.3.7.0: Numbers represented using scientific notation
CopyrightBas van Dijk 2013
LicenseBSD3
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Scientific

Description

This module provides the number type Scientific. Scientific numbers are arbitrary precision and space efficient. They are represented using 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 Integrals (like: Int) or RealFloats (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
Synopsis

Documentation

data Scientific Source #

An arbitrary-precision number represented using scientific notation.

This type describes the set of all Reals which have a finite decimal expansion.

A scientific number with coefficient c and base10Exponent e corresponds to the Fractional number: fromInteger c * 10 ^^ e

Instances

Instances details
Eq Scientific Source #

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 details

Defined in Data.Scientific

Fractional Scientific Source #

WARNING: recip and / will throw an error when their outputs are 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 details

Defined in Data.Scientific

Data Scientific Source # 
Instance details

Defined in Data.Scientific

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scientific -> c Scientific #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scientific #

toConstr :: Scientific -> Constr #

dataTypeOf :: Scientific -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scientific) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scientific) #

gmapT :: (forall b. Data b => b -> b) -> Scientific -> Scientific #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scientific -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scientific -> r #

gmapQ :: (forall d. Data d => d -> u) -> Scientific -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Scientific -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific #

Num Scientific Source #

WARNING: + and - compute the Integer magnitude: 10^e where e is the difference between the base10Exponents 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 details

Defined in Data.Scientific

Ord Scientific Source #

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 details

Defined in Data.Scientific

Read Scientific Source #

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 details

Defined in Data.Scientific

Real Scientific Source #

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 details

Defined in Data.Scientific

RealFrac Scientific Source #

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 details

Defined in Data.Scientific

Show Scientific Source #

See formatScientific if you need more control over the rendering.

Instance details

Defined in Data.Scientific

Binary Scientific Source #

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 details

Defined in Data.Scientific

NFData Scientific Source # 
Instance details

Defined in Data.Scientific

Methods

rnf :: Scientific -> () #

Hashable Scientific Source #

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 details

Defined in Data.Scientific

Lift Scientific Source #

Since: 0.3.7.0

Instance details

Defined in Data.Scientific

Construction

scientific :: Integer -> Int -> Scientific Source #

scientific c e constructs a scientific number which corresponds to the Fractional number: fromInteger c * 10 ^^ e.

Projections

coefficient :: Scientific -> Integer Source #

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)

base10Exponent :: Scientific -> Int Source #

The base-10 exponent of a scientific number.

Predicates

isFloating :: Scientific -> Bool Source #

Return True if the scientific is a floating point, False otherwise.

Also see: floatingOrInteger.

isInteger :: Scientific -> Bool Source #

Return True if the scientific is an integer, False otherwise.

Also see: floatingOrInteger.

Conversions

Rational

unsafeFromRational :: Rational -> Scientific Source #

Although fromRational is unsafe because it will throw errors on 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.

fromRationalRepetend Source #

Arguments

:: Maybe Int

Optional limit

-> Rational 
-> Either (Scientific, Rational) (Scientific, Maybe Int) 

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 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)

fromRationalRepetendLimited Source #

Arguments

:: Int

limit

-> Rational 
-> Either (Scientific, Rational) (Scientific, Maybe Int) 

Like fromRationalRepetend but always accepts a limit.

toRationalRepetend Source #

Arguments

:: Scientific 
-> Int

Repetend index

-> 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: 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.

Floating & integer

floatingOrInteger :: (RealFloat r, Integral i) => Scientific -> Either r i Source #

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.

toRealFloat :: RealFloat a => Scientific -> a Source #

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.

toBoundedRealFloat :: forall a. RealFloat a => Scientific -> Either a a Source #

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.

toBoundedInteger :: forall i. (Integral i, Bounded i) => Scientific -> Maybe i Source #

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.

fromFloatDigits :: RealFloat a => a -> Scientific Source #

Convert a RealFloat (like a Double or Float) into a Scientific number.

Note that this function uses floatToDigits to compute the digits and exponent of the RealFloat number. Be aware that the algorithm used in 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

Parsing

scientificP :: ReadP Scientific Source #

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.

Pretty printing

formatScientific Source #

Arguments

:: FPFormat 
-> Maybe Int

Number of decimal places to render.

-> Scientific 
-> String 

Like show but provides rendering options.

data FPFormat #

Control the rendering of floating point numbers.

Constructors

Exponent

Scientific notation (e.g. 2.3e123).

Fixed

Standard decimal notation.

Generic

Use decimal notation for values between 0.1 and 9,999,999, and scientific notation otherwise.

toDecimalDigits :: Scientific -> ([Int], Int) Source #

Similar to 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.

Normalization

normalize :: Scientific -> Scientific Source #

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.