deka-0.4.0.0: Decimal floating point arithmetic

Safe HaskellTrustworthy

Data.Deka.Quad

Contents

Description

Floating-point decimals.

This uses the decNumber C library, so you will want to read the documentation about it to fully understand this module:

http://speleotrove.com/decimal/decnumber.html

http://speleotrove.com/decimal/decarith.html

http://speleotrove.com/decimal/

Many of the comments on what these functions do are taken directly from the documentation for the decNumber C library.

In particular, this module implements the decQuad type. decQuad supports up to 34 digits of precision and exponents between -6176 and 6111. It doesn't silently round, overflow, or underflow; rather, the library will notify you if these things happen.

Many functions in this module clash with Prelude names, so you might want to do

 import qualified Data.Deka.Quad as Q

Synopsis

Quad

data Quad Source

Decimal number. As indicated in the General Decimal Arithmetic specification, a Quad might be a finite number (perhaps the most common type) or it might be infinite or a not-a-number. decClass will tell you a little more about a particular Quad.

Instances

Eq Quad

The Eq instance depends on an IEEE 754 total ordering. In particular, note that, for example, 7.5 is not equal to 7.50. See

http://speleotrove.com/decimal/decifaq4.html#order

Ord Quad

Like the Eq instance, this uses an IEEE 754 total ordering.

Show Quad

The Show instance uses toByteString.

Rounding

For more on the rounding algorithms, see

http://speleotrove.com/decimal/damodel.html

data Round Source

Instances

roundCeiling :: RoundSource

Round toward positive infinity.

roundUp :: RoundSource

Round away from zero.

roundHalfUp :: RoundSource

0.5 rounds up

roundHalfEven :: RoundSource

0.5 rounds to nearest even

roundHalfDown :: RoundSource

0.5 rounds down

roundDown :: RoundSource

Round toward zero - truncate

roundFloor :: RoundSource

Round toward negative infinity.

round05Up :: RoundSource

Round for reround

Flags

For more on possible flags, see

http://speleotrove.com/decimal/damodel.html

data Flag Source

A single error or warning condition that may be set in the Ctx.

Instances

divisionUndefined :: FlagSource

0/0 is undefined. It sets this flag and returns a quiet NaN.

divisionByZero :: FlagSource

A non-zero dividend is divided by zero. Unlike 0/0, it has a defined result (a signed Infinity).

invalidOperation :: FlagSource

Raised on a variety of invalid operations, such as an attempt to use compareSignal on an operand that is an NaN.

inexact :: FlagSource

One or more non-zero coefficient digits were discarded during rounding.

underflow :: FlagSource

A result is both subnormal and inexact.

overflow :: FlagSource

The exponent of a result is too large to be represented.

conversionSyntax :: FlagSource

A source string (for instance, in fromByteString) contained errors.

data Flags Source

A container for multiple Flag indicating which are set and which are not. An instance of Exception so you can throw it if you want (no functions in this module throw.)

Instances

Eq Flags 
Ord Flags 
Show Flags

Show gives you a comma-separated list of flags that are set, or an empty string if no flags are set.

Typeable Flags 
Exception Flags 

checkFlag :: Flag -> Flags -> BoolSource

Is this Flag set?

emptyFlags :: FlagsSource

A Flags with no Flag set.

Ctx monad

data Ctx a Source

The Ctx monad

The General Decimal Arithmetic specification states that most computations occur within a context, which affects the manner in which computations are done (for instance, the context determines the rounding algorithm). The context also carries the flags that computations can set (for instance, a computation might set a flag to indicate that the result is rounded or inexact or was a division by zero.) The Ctx monad carries this context.

getStatus :: Ctx FlagsSource

The current status flags, which indicate results from previous computations.

setStatus :: Flags -> Ctx ()Source

Set the current status to whatever you wish.

getRound :: Ctx RoundSource

The current rounding method

setRound :: Round -> Ctx ()Source

Change the current rounding method

runCtx :: Ctx a -> (a, Flags)Source

By default, rounding is set to roundHalfEven. No status flags are set initially. Returns the final status flags along with the result of the computation.

evalCtx :: Ctx a -> aSource

Like runCtx but does not return the final flags.

Class

data DecClass Source

Different categories of Quad.

sNan :: DecClassSource

Signaling NaN

qNan :: DecClassSource

Quiet NaN

negInf :: DecClassSource

Negative infinity

negNormal :: DecClassSource

Negative normal number

negSubnormal :: DecClassSource

Negative subnormal number

negZero :: DecClassSource

The negative zero

posZero :: DecClassSource

The positive zero

posSubnormal :: DecClassSource

A positive subnormal number

posNormal :: DecClassSource

A positive normal number

posInf :: DecClassSource

Positive infinity

decClass :: Quad -> DecClassSource

More information about a particular Quad.

Converting to and from strings

fromByteString :: ByteString -> Ctx QuadSource

Reads a ByteString, which can be in scientific, engineering, or "regular" decimal notation. Also reads NaN, Infinity, etc. Will return a signaling NaN and set invalidOperation if the string given is invalid.

In the decNumber C library, this function was called fromString; the name was changed here because it doesn't take a regular Haskell String.

toByteString :: Quad -> ByteStringSource

Converts a Quad to a string. May use non-scientific notation, but only if that's unambiguous; otherwise, uses scientific notation.

In the decNumber C library, this is called toString; the name was changed here because this function doesn't return a Haskell String.

toEngByteString :: Quad -> ByteStringSource

Returns a string in engineering notation.

In the decNumber C library, this is called toEngString; the name is changed here because the function does not return a regular Haskell String.

Converting to and from integers

toInt32 :: Round -> Quad -> Ctx C'int32_tSource

Uses the rounding method given rather than the one in the Ctx. If the operand is infinite, an NaN, or if the result of rounding is outside the range of a C'int32_t, then invalidOperation is set. inexact is not set even if rounding occurred.

toInt32Exact :: Round -> Quad -> Ctx C'int32_tSource

Like toInt32 but if rounding removes non-zero digits then inexact is set.

toUInt32 :: Round -> Quad -> Ctx C'uint32_tSource

toUInt32 r x returns the value of x, rounded to an integer if necessary using the rounding mode r rather than the one given in the Ctx. If x is infinite, or outside of the range of a C'uint32_t, then invalidOperation is set. inexact is not set even if rounding occurs.

The negative zero converts to 0 and is valid, but negative numbers are not valid.

toUInt32Exact :: Round -> Quad -> Ctx C'uint32_tSource

Same as toUInt32 but if rounding removes non-zero digits then inexact is set.

Arithmetic

fma :: Quad -> Quad -> Quad -> Ctx QuadSource

Fused multiply add; fma x y z calculates x * y + z. The multiply is carried out first and is exact, so the result has only one final rounding.

divideInteger :: Quad -> Quad -> Ctx QuadSource

divideInteger x y returns the integer part of the result (rounded toward zero), with an exponent of 0. If the the result would not fit because it has too many digits, divisionImpossible is set.

remainder :: Quad -> Quad -> Ctx QuadSource

Remainder from integer division. If the intermediate integer does not fit within a Quad, divisionImpossible is raised.

remainderNear :: Quad -> Quad -> Ctx QuadSource

Like remainder but the nearest integer is used for for the intermediate result instead of the result from divideInteger.

Exponent and coefficient adjustment

quantize :: Quad -> Quad -> Ctx QuadSource

quantize x y returns z which is x set to have the same quantum as y; that is, numerically the same value but rounded or padded if necessary to have the same exponent as y. Useful for rounding monetary quantities.

reduce :: Quad -> Ctx QuadSource

Reduces coefficient to its shortest possible form without changing the value of the result by removing all possible trailing zeroes.

Comparisons

compare :: Quad -> Quad -> Ctx QuadSource

Compares two Quad numerically. The result might be -1, 0, 1, or NaN, where -1 means x is less than y, 0 indicates numerical equality, 1 means y is greater than x. NaN is returned only if x or y is an NaN.

Thus, this function does not return an Ordering because the result might be an NaN.

compareOrd :: Quad -> Quad -> Maybe OrderingSource

Wrapper for compare that returns an Ordering rather than a Quad. Returns Just LT rather than -1, Just EQ rather than 0, and Just GT rather than 1, and Nothing rather than NaN. This is a pure function; it does not affect the Ctx.

compareSignal :: Quad -> Quad -> Ctx QuadSource

Same as compare, but a quietNaN is treated like a signaling NaN (sets invalidOperation).

compareTotal :: Quad -> Quad -> OrderingSource

Compares using an IEEE 754 total ordering, which takes into account the exponent. IEEE 754 says that this function might return different results depending upon whether the operands are canonical; Quad are always canonical so you don't need to worry about that here.

compareTotalMag :: Quad -> Quad -> OrderingSource

Same as compareTotal but compares the absolute value of the two arguments.

max :: Quad -> Quad -> Ctx QuadSource

max x y returns the larger argument; if either (but not both) x or y is a quiet NaN then the other argument is the result; otherwise, NaNs, are handled as for arithmetic operations.

maxMag :: Quad -> Quad -> Ctx QuadSource

Like max but the absolute values of the arguments are used.

min :: Quad -> Quad -> Ctx QuadSource

min x y returns the smaller argument; if either (but not both) x or y is a quiet NaN then the other argument is the result; otherwise, NaNs, are handled as for arithmetic operations.

minMag :: Quad -> Quad -> Ctx QuadSource

Like min but the absolute values of the arguments are used.

sameQuantum :: Quad -> Quad -> BoolSource

True only if both operands have the same exponent or are both NaNs (quiet or signaling) or both infinite.

Tests

isFinite :: Quad -> BoolSource

True if x is neither infinite nor a NaN.

isInfinite :: Quad -> BoolSource

True for infinities.

isInteger :: Quad -> BoolSource

True if x is finite and has exponent of 0; False otherwise. This tests the exponent, not the adjusted exponent. This can lead to results you may not expect:

>>> isInteger . evalCtx . fromByteString . pack $ "3.00e2"
True
>>> isInteger . evalCtx . fromByteString . pack $ "3e2"
False
>>> isInteger . evalCtx . fromByteString . pack $ "3.00e0"
False

isLogical :: Quad -> BoolSource

True only if x is zero or positive, an integer (finite with exponent of 0), and the coefficient is only zeroes and/or ones.

isNaN :: Quad -> BoolSource

True for NaNs.

isNegative :: Quad -> BoolSource

True only if x is less than zero and is not an NaN.

isNormal :: Quad -> BoolSource

True only if x is finite, non-zero, and not subnormal.

isPositive :: Quad -> BoolSource

True only if x is greater than zero and is not an NaN.

isSignaling :: Quad -> BoolSource

True only if x is a signaling NaN.

isSigned :: Quad -> BoolSource

True only if x has a sign of 1. Note that zeroes and NaNs may have sign of 1.

isSubnormal :: Quad -> BoolSource

True only if x is subnormal - that is, finite, non-zero, and with a magnitude less than 10 ^ emin.

isZero :: Quad -> BoolSource

True only if x is a zero.

Signs

plus :: Quad -> Ctx QuadSource

Same effect as 0 + x where the exponent of the zero is the same as that of x if x is finite). NaNs are handled as for arithmetic operations.

minus :: Quad -> Ctx QuadSource

Negation. Result has the same effect as 0 - x when the exponent of the zero is the same as that of x, if x is finite.

abs :: Quad -> Ctx QuadSource

Absolute value. NaNs are handled normally (the sign of an NaN is not affected, and an sNaN sets invalidOperation.

copySign :: Quad -> Quad -> QuadSource

copySign x y returns z, which is a copy of x but has the sign of y. This function never raises any signals.

Increment and decrement

nextMinus :: Quad -> Ctx QuadSource

Decrements toward negative infinity.

nextPlus :: Quad -> Ctx QuadSource

Increments toward positive infinity.

nextToward :: Quad -> Quad -> Ctx QuadSource

nextToward x y returns the next Quad in the direction of y.

Digit-wise

and :: Quad -> Quad -> Ctx QuadSource

Digit-wise logical and. Operands must be:

  • zero or positive
  • integers
  • comprise only zeroes and/or ones

If not, invalidOperation is set.

or :: Quad -> Quad -> Ctx QuadSource

Digit wise logical inclusive Or. Operands must be:

  • zero or positive
  • integers
  • comprise only zeroes and/or ones

If not, invalidOperation is set.

xor :: Quad -> Quad -> Ctx QuadSource

Digit-wise logical exclusive or. Operands must be:

  • zero or positive
  • integers
  • comprise only zeroes and/or ones

If not, invalidOperation is set.

invert :: Quad -> Ctx QuadSource

Digit-wise logical inversion. The operand must be:

  • zero or positive
  • integers
  • comprise only zeroes and/or ones

If not, invalidOperation is set.

shift :: Quad -> Quad -> Ctx QuadSource

shift x y shifts digits the digits of x to the left (if y is positive) or right (if y is negative) without adjusting the exponent or sign of x. Any digits shifted in from the left or right will be 0.

y is a count of positions to shift; it must be a finite integer in the range negate coefficientLen to coefficientLen. NaNs propagate as usual. If x is infinite the result is an infinity of the same sign. No status is set unless y is invalid or the operand is an NaN.

rotate :: Quad -> Quad -> Ctx QuadSource

rotate x y rotates the digits of x to the left (if y is positive) or right (if y is negative) without adjusting the exponent or sign of x. y is the number of positions to rotate and must be in the range negate coefficientLen to coefficentLen.

NaNs are propagated as usual. No status is set unless y is invalid or an operand is an NaN.

log and scale

logB :: Quad -> Ctx QuadSource

logB x Returns the adjusted exponent of x, according to IEEE 754 rules. If x is infinite, returns +Infinity. If x is zero, the result is -Infinity, and divisionByZero is set. If x is less than zero, the absolute value of x is used. If x is one, the result is 0. NaNs are propagated as for arithmetic operations.

scaleB :: Quad -> Quad -> Ctx QuadSource

scaleB x y calculates x * 10 ^ y. y must be an integer (finite with exponent of 0) in the range of plus or minus 2 * coefficientLen + coefficientLen), typically resulting from logB. Underflow and overflow might occur; NaNs propagate as usual.

Attributes

digits :: Quad -> IntSource

Number of significant digits. If zero or infinite, returns 1. If NaN, returns number of digits in the payload.

Integral rounding

If you want to round but not to an integral value (e.g. round to two decimal places), see quantize.

toIntegralExact :: Quad -> Ctx QuadSource

Rounds to an integral using the rounding mode set in the Ctx. If the operand is infinite, an infinity of the same sign is returned. If the operand is an NaN, the result is the same as for other arithmetic operations. If rounding removes non-zero digits then inexact is set.

toIntegralValue :: Round -> Quad -> Ctx QuadSource

toIntegralValue r x returns an integral value of x using the rounding mode r rather than the one specified in the Ctx. If the operand is an NaN, the result is the same as for other arithmetic operations. inexact is not set even if rounding occurred.

Constants

zero :: QuadSource

A Quad whose coefficient, exponent, and sign are all 0.

one :: QuadSource

A Quad with coefficient D1, exponent 0, and sign Sign0.

version :: ByteStringSource

Identifies the version of the decNumber C library.

Complete encoding and decoding

These convert a Quad to a Decoded, which is a pure Haskell type containing all the information in the Quad.

Digits

data Digit Source

A single decimal digit.

Constructors

D0 
D1 
D2 
D3 
D4 
D5 
D6 
D7 
D8 
D9 

digitsToInteger :: [Digit] -> IntegerSource

The most significant digit is at the head of the list.

integralToDigits :: Integral a => a -> [Digit]Source

The most significant digit is at the head of the list. Sign of number is not relevant.

Coefficients

coefficientLen :: IntSource

Maximum number of digits in a coefficient.

payloadLen :: IntSource

Maximum number of digits in a payload.

data Coefficient Source

A list of digits, less than or equal to coefficientLen long. Corresponds only to finite numbers.

coefficient :: [Digit] -> Maybe CoefficientSource

Creates a Coefficient. Checks to ensure it is not null and that it is not longer than coefficientLen and that it does not have leading zeroes (if it is 0, a single D0 is allowed).

data Payload Source

A list of digits, less than or equal to payloadLen long. Accompanies an NaN, potentially with diagnostic information (I do not know if decNumber actually makes use of this.)

payload :: [Digit] -> Maybe PayloadSource

Creates a Payload. Checks to ensure it is not null, not longer than payloadLen and that it does not have leading zeroes (if it is 0, a single D0 is allowed).

zeroPayload :: PayloadSource

Payload of [D0]

Exponents

data Exponent Source

The signed integer which indicates the power of ten by which the coefficient is multiplied.

exponent :: Int -> Maybe ExponentSource

Ensures that the exponent is within the range allowed by minMaxExp.

zeroExponent :: ExponentSource

An Exponent whose value is 0.

minMaxExp :: (Int, Int)Source

The minimum and maximum possible exponent.

data AdjustedExp Source

An adjusted exponent is the value of an exponent of a number when that number is expressed as though in scientific notation with one digit before any decimal point. This is the finite exponent + (number of significant digits - 1).

minNormalAdj :: AdjustedExpSource

The smallest possible adjusted exponent that is still normal. Adjusted exponents smaller than this are subnormal.

minNormalExp :: Coefficient -> ExponentSource

Like minNormalAdj, but returns the size of the regular exponent rather than the adjusted exponent.

Sign, NaN, Value, Decoded

data Sign Source

Constructors

Sign0

The number is positive or is zero

Sign1

The number is negative or the negative zero

data NaN Source

Constructors

Quiet 
Signaling 

Instances

data Decoded Source

A pure Haskell type which holds information identical to that in a Quad.

Constructors

Decoded 

Fields

dSign :: Sign
 
dValue :: Value
 

fromBCD :: Decoded -> QuadSource

Encodes a new Quad.

toBCD :: Quad -> DecodedSource

Decodes a Quad to a pure Haskell type which holds identical information.

scientific :: Decoded -> StringSource

Converts a Decoded to scientific notation. Unlike toByteString this will always use scientific notation. For NaNs and infinities, the notation is identical to that of decNumber (see Decimal Arithmetic Specification page 19). This means that a quiet NaN is NaN while a signaling NaN is sNaN, and infinity is Infinity.

Like decQuadToString, the payload of an NaN is not shown if it is zero.

ordinary :: Decoded -> StringSource

Converts Decoded to ordinary decimal notation. For NaNs and infinities, the notation is identical to that of scientific. Unlike scientific, though the result can always be converted back to a Quad using fromByteString, the number of significant digits might change. For example, though 1.2E3 has two significant digits, using ordinary on this value and then reading it back in with fromByteString will give you 1200E0, which has four significant digits.

decodedToRational :: Decoded -> Maybe RationalSource

Converts a Decoded to a Rational. Returns Nothing if the Decoded is not finite.

Decoded predicates

Duplicates of Quad tests that return Bool

These duplicate the tests that are available for the Quad type directly.

dIsLogical :: Decoded -> BoolSource

True only if x is zero or positive, an integer (finite with exponent of 0), and the coefficient is only zeroes and/or ones. The sign must be Sign0 (that is, you cannot have a negative zero.)

dIsNegative :: Decoded -> BoolSource

True only if x is less than zero and is not an NaN. It's not enough for the sign to be Sign1; the coefficient (if finite) must be greater than zero.

dIsZero :: Decoded -> BoolSource

True for any zero (negative or positive zero).

dDigits :: Coefficient -> IntSource

The number of significant digits. Zero returns 1.

Duplicates of Quad tests that return DecClass