Decimal-0.2.1: Decimal numbers with variable precision

Data.Decimal

Contents

Description

Decimal numbers are represented as m*10^(-e) where m and e are integers. The exponent e is an unsigned Word8. Hence the smallest value that can be represented is 10^-255.

Unary arithmetic results have the exponent of the argument. Binary arithmetic results have an exponent equal to the maximum of the exponents of the arguments.

Decimal numbers are defined as instances of Real. This means that conventional division is not defined. Instead the functions divide and allocate will split a decimal amount into lists of results. These results are guaranteed to sum to the original number. This is a useful property when doing financial arithmetic.

The arithmetic on mantissas is always done using Integer, regardless of the type of DecimalRaw being manipulated. In practice it is recommended that Decimal be used, with other types being used only where necessary (e.g. to conform to a network protocol).

Synopsis

Decimal Values

data Integral i => DecimalRaw i Source

Raw decimal arithmetic type constructor. A decimal value consists of an integer mantissa and a negative exponent which is interpreted as the number of decimal places. The value stored in a Decimal d is therefore equal to:

 decimalMantissa d / (10 ^ decimalPlaces d)

The Show instance will add trailing zeros, so show $ Decimal 3 1500 will return "1.500". Conversely the Read instance will use the decimal places to determine the precision.

Arithmetic and comparision operators convert their arguments to the greater of the two precisions, and return a result of that precision. Regardless of the type of the arguments, all mantissa arithmetic is done using Integer types, so application developers do not need to worry about overflow in the internal algorithms. However the result of each operator will be converted to the mantissa type without checking for overflow.

Constructors

Decimal 

type Decimal = DecimalRaw IntegerSource

Arbitrary precision decimal type. As a rule programs should do decimal arithmetic with this type and only convert to other instances of DecimalRaw where required by an external interface.

Using this type is also faster because it avoids repeated conversions to and from Integer.

realFracToDecimal :: (Integral i, RealFrac r) => Word8 -> r -> DecimalRaw iSource

Convert a real fractional value into a Decimal of the appropriate precision.

decimalConvert :: (Integral a, Integral b) => DecimalRaw a -> DecimalRaw bSource

Convert a DecimalRaw from one base representation to another. Does not check for overflow in the new representation.

roundTo :: Integral i => Word8 -> DecimalRaw i -> DecimalRaw IntegerSource

Round a DecimalRaw to a specified number of decimal places.

(*.) :: (Integral i, RealFrac r) => DecimalRaw i -> r -> DecimalRaw iSource

Multiply a DecimalRaw by a RealFrac value.

divide :: Integral i => DecimalRaw i -> Int -> [(Int, DecimalRaw i)]Source

Divide a DecimalRaw value into one or more portions. The portions will be approximately equal, and the sum of the portions is guaranteed to be the original value.

The portions are represented as a list of pairs. The first part of each pair is the number of portions, and the second part is the portion value. Hence 10 dollars divided 3 ways will produce [(2, 3.33), (1, 3.34)].

allocate :: Integral i => DecimalRaw i -> [Integer] -> [DecimalRaw i]Source

Allocate a DecimalRaw value proportionately with the values in a list. The allocated portions are guaranteed to add up to the original value.

Some of the allocations may be zero or negative, but the sum of the list must not be zero. The allocation is intended to be as close as possible to the following:

 let result = allocate d parts
 in all (== d / sum parts) $ zipWith (/) result parts

QuickCheck Properties

prop_readShow :: Decimal -> BoolSource

read is the inverse of show.

 read (show n) == n

prop_readShowPrecision :: Decimal -> BoolSource

Read and show preserve decimal places.

 decimalPlaces (read (show n)) == decimalPlaces n

prop_fromIntegerZero :: Integer -> BoolSource

fromInteger definition.

 decimalPlaces (fromInteger n) == 0 &&
 decimalMantissa (fromInteger n) == n

prop_increaseDecimals :: Decimal -> PropertySource

Increased precision does not affect equality.

 decimalPlaces d < maxBound ==> roundTo (decimalPlaces d + 1) d == d

prop_decreaseDecimals :: Decimal -> Decimal -> BoolSource

Decreased precision can make two decimals equal, but it can never change their order.

 forAll d1, d2 :: Decimal -> legal beforeRound afterRound
      where
         beforeRound = compare d1 d2
         afterRound = compare (roundTo 0 d1) (roundTo 0 d2)
         legal GT x = x `elem` [GT, EQ]
         legal EQ x = x `elem` [EQ]
         legal LT x = x `elem` [LT, EQ]

prop_inverseAdd :: Decimal -> Decimal -> BoolSource

 (x + y) - y == x

prop_repeatedAdd :: Decimal -> Word8 -> BoolSource

Multiplication is repeated addition.

 forall d, NonNegative i : (sum $ replicate i d) == d * fromIntegral (max i 0)

prop_divisionParts :: Decimal -> Positive Int -> PropertySource

Division produces the right number of parts.

 forall d, Positive i : (sum $ map fst $ divide d i) == i

prop_divisionUnits :: Decimal -> Positive Int -> BoolSource

Division doesn't drop any units.

 forall d, Positive i : (sum $ map (\(n,d1) -> fromIntegral n * d1) $ divide d i) == d

prop_allocateParts :: Decimal -> [Integer] -> PropertySource

Allocate produces the right number of parts.

 sum ps /= 0  ==>  length ps == length (allocate d ps)

prop_allocateUnits :: Decimal -> [Integer] -> PropertySource

Allocate doesn't drop any units.

     sum ps /= 0  ==>  sum (allocate d ps) == d

prop_abs :: Decimal -> BoolSource

Absolute value definition

 decimalPlaces a == decimalPlaces d && 
 decimalMantissa a == abs (decimalMantissa d)
    where a = abs d

prop_signum :: Decimal -> BoolSource

Sign number defintion

 signum d == (fromInteger $ signum $ decimalMantissa d)