deka-0.6.0.0: Decimal floating point arithmetic

Safe HaskellSafe
LanguageHaskell2010

Deka.Dec

Contents

Description

Decimal arithmetic.

Much documentation is copied from documentation for the decNumber C library, available at

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

Synopsis

Documentation

data Dec Source

A decimal value. A decimal consists of:

  • an integral coefficient,
  • an exponent, and
  • a sign.

A decimal may also be a special value, which can be:

  • NaN (Not a Number), which may be either quiet (propagates quietly through operations) or signaling (raises the Invalid operation condition when encountered), or
  • Infinity, either positive or negative.

Instances

Context

String Conversions

fromByteString :: ByteString -> Ctx Dec Source

Converts a character string to a Dec. Implements the _to-number_ conversion from the General Decimal Arithmetic specification.

The conversion is exact provided that the numeric string has no more significant digits than are specified in the Precision in the Ctx and the adjusted exponent is in the range specified by Emin and Emax in the Ctx. If there are more than Precision digits in the string, or the exponent is out of range, the value will be rounded as necessary using the Round rounding mode. The Precision therefore both determines the maximum precision for unrounded numbers and defines the minimum size of the Dec structure required.

Possible errors are conversionSyntax (the string does not have the syntax of a number, which depends on setExtended in the Ctx), overflow (the adjusted exponent of the number is larger than Emax), or underflow (the adjusted exponent is less than Emin and the conversion is not exact). If any of these conditions are set, the number structure will have a defined value as described in the arithmetic specification (this may be a subnormal or infinite value).

toByteString :: Dec -> ByteString Source

Converts a number to scientific notation.

toEngByteString :: Dec -> ByteString Source

Converts a number to engineering notation.

Arithmetic

add :: Dec -> Dec -> Ctx Dec Source

Addition.

subtract :: Dec -> Dec -> Ctx Dec Source

Subtraction.

multiply :: Dec -> Dec -> Ctx Dec Source

Multiplication.

fma :: Dec -> Dec -> Dec -> Ctx Dec Source

fma x y z multiplies x by y and then adds z to that intermediate result. It is equivalent to a multiplication followed by an addition except that the intermediate result is not rounded and will not cause overflow or underflow. That is, only the final result is rounded and checked.

This is a mathematical function; the 10 ^ 6 restrictions on precision and range apply as described above.

divide :: Dec -> Dec -> Ctx Dec Source

Division.

divideInteger :: Dec -> Dec -> Ctx Dec Source

Returns the integer part of the result of division. It must be possible to express the result as an integer. That is, it must have no more digits than Precision in the Ctx. If it does then divisionImpossible is raised.

remainder :: Dec -> Dec -> Ctx Dec Source

remainder a b returns the remainder of a / b.

remainderNear :: Dec -> Dec -> Ctx Dec Source

remainderNear a b returns a - b * n, where n is the integer nearest the exact value of a / b. If two integers are equally near then the even one is chosen.

Signs and absolute value

abs :: Dec -> Ctx Dec Source

Returns the absolute value. The same effect as plus unless the operand is negative, in which case it is the same as minus.

plus :: Dec -> Ctx Dec Source

Returns the result of adding the operand to zero. This takes place according to the settings given in the Ctx, following the usual arithmetic rules. This may therefore be used for rounding or for implementing a prefix plus operation.

minus :: Dec -> Ctx Dec Source

Returns the result of subtracting the operand from zero. hat is, it is negated, following the usual arithmetic rules; this may be used for implementing a prefix minus operation.

Comparisons

compare :: Dec -> Dec -> Ctx Dec Source

compare x y returns -1 if a is less than b, 0 if a is equal to b, and 1 if a is greater than b. invalidOperation is set if at least one of the operands is a signaling NaN.

compareSignal :: Dec -> Dec -> Ctx Dec Source

Identical to compare except that all NaNs (including quiet NaNs) set the invalidOperation condition.

compareTotal :: Dec -> Dec -> Ordering Source

compareTotal x y compares to numbers using the IEEE 754 total ordering. If x is less than y, returns -1. If they are equal (that is, when subtracted the result would be 0), returns 0. If y is greater than x, returns 1.

Here is the total ordering:

-NaN < -sNaN < -Infinity < -finites < -0 < +0 < +finites
  < +Infinity < +SNaN < +NaN

Also, 1.000 < 1.0 (etc.) and NaNs are ordered by payload.

compareTotalMag :: Dec -> Dec -> Ordering Source

Same as compareTotal except that the signs of the operands are ignored and taken to be 0 (non-negative).

max :: Dec -> Dec -> Ctx Dec Source

Compares two numbers numerically and returns the larger. If the numbers compare equal then number is chosen with regard to sign and exponent. Unusually, if one operand is a quiet NaN and the other a number, then the number is returned.

maxMag :: Dec -> Dec -> Ctx Dec Source

Compares the magnitude of two numbers numerically and sets number to the larger. It is identical to max except that the signs of the operands are ignored and taken to be 0 (non-negative).

min :: Dec -> Dec -> Ctx Dec Source

Compares two numbers numerically and sets number to the smaller. If the numbers compare equal then number is chosen with regard to sign and exponent. Unusually, if one operand is a quiet NaN and the other a number, then the number is returned.

minMag :: Dec -> Dec -> Ctx Dec Source

Compares the magnitude of two numbers numerically and sets number to the smaller. It is identical to min except that the signs of the operands are ignored and taken to be 0 (non-negative).

Increments

nextMinus :: Dec -> Ctx Dec Source

Returns the closest representable number that is smaller than the operand.

nextPlus :: Dec -> Ctx Dec Source

Returns the closest representable number that is larger than the operand.

nextToward :: Dec -> Dec -> Ctx Dec Source

nextToward a b returns the representable number closest to a in the direction of b.

Exponent testing and adjustment

sameQuantum :: Dec -> Dec -> Bool Source

True if both operands have the same exponent; False otherwise.

quantize :: Dec -> Dec -> Ctx Dec Source

quantize a b returns the number that is equal in value to a, but has the exponent of b.

rescale :: Dec -> Signed -> Ctx Dec Source

rescale a b returns the number that is equal in value to a, but has the exponent b. Special numbers are copied without signaling. This function is not part of the General Decimal Arithmetic Specification. It is also not equivalent to the rescale function that was removed from the specification.

scaleB :: Dec -> Dec -> Ctx Dec Source

scaleB a b - b must be an integer with exponent 0. If a is infinite, returns a. Otherwise, returns a with the value of b added to the exponent.

Digit-wise and logical

and :: Dec -> Dec -> Ctx Dec Source

Digit-wise logical and.

or :: Dec -> Dec -> Ctx Dec Source

Digit-wise logical inclusive or.

xor :: Dec -> Dec -> Ctx Dec Source

Digit-wise logical exclusive or.

shift :: Dec -> Dec -> Ctx Dec Source

shift a b returns a shifted by b places. b must be in the range [-Precision, Precision]. A negative b indicates a right shift, a positive b a left shift. Digits that do not fit are discarded.

rotate :: Dec -> Dec -> Ctx Dec Source

rotate x y returns x rotated by y places. y must be in the range [-Precision, Precision]. A negative y indicates a right rotation, a positive y a left rotation.

invert :: Dec -> Ctx Dec Source

Digit-wise inversion (a 0 becomes a 1 and vice versa).

Trailing zeroes

Integral rounding

toIntegralExact :: Dec -> Ctx Dec Source

Round to an integer, using the rounding mode of the context. Only a signaling NaN causes an invalidOperation condition.

toIntegralValue :: Dec -> Ctx Dec Source

Like toIntegralExact, but inexact and rounded are never set.

Logarithms, exponents, roots

exp :: Dec -> Ctx Dec Source

Exponentiation. Result is rounded if necessary using the Precision in the Ctx and using the roundHalfEven rounding method.

Finite results will always be full precision and inexact, except when rhs is a zero or -Infinity (giving 1 or 0 respectively). Inexact results will almost always be correctly rounded, but may be up to 1 ulp (unit in last place) in error in rare cases.

This is a mathematical function; the 10 ^ 6 restrictions on precision and range apply as described above.

ln :: Dec -> Ctx Dec Source

Natural logarithm. Results are correctly rounded if setAllCorrectRound is True.

logB :: Dec -> Ctx Dec Source

Returns the adjusted exponent of the operand, according to the rules for logB of IEEE 754. This returns the exponent of the operand as though its decimal point had been moved to follow the first digit while keeping the same value. The result is not limited by Emin or Emax.

If operand is an NaN, the general rules apply. If operand is infinite, the result is +Infinity. If operand is zero, result is -Infinity and invalidOperation is set. Otherwise, the result is the same as the adjusted exponent of the operand, or floor(log10(a)) where a is the operand.

log10 :: Dec -> Ctx Dec Source

Base 10 logarithm. Results are correctly rounded if setAllCorrectRound is True.

power :: Dec -> Dec -> Ctx Dec Source

power b e returns b raised to the power of e. Integer powers are exact, provided that the result is finite and fits into Precision.

Results are not correctly rounded, even if setAllCorrectRound is True. The error of the function is less than 1ULP + t, where t has a maximum of 0.1ULP, but is almost always less than 0.001ULP.

squareRoot :: Dec -> Ctx Dec Source

Returns the square root. This function is always correctly rounded using the roundHalfEven method.

Identification

data PosNeg Source

Constructors

Pos 
Neg 

Instances

data Number Source

Constructors

Infinity 
Normal 
Subnormal 
Zero 

Instances

data Class Source

Constructors

SNaN 
NaN 
Number PosNeg Number 

Instances

numClass :: Dec -> Ctx Class Source

Determines the Class of a Dec.

isNormal :: Dec -> Ctx Bool Source

False if the decimal is special or zero, or the exponent is less than Emin. True otherwise.

isSubnormal :: Dec -> Ctx Bool Source

False if the decimal is special or zero, or the exponent is greater or equal to Emin. True otherwise.

data Sign Source

Constructors

Sign0 
Sign1 

Instances

data EvenOdd Source

Constructors

Even 
Odd 

Instances

Version