decimal-arithmetic-0.5.1.0: An implementation of the General Decimal Arithmetic Specification

Safe HaskellTrustworthy
LanguageHaskell2010

Numeric.Decimal.Operation

Contents

Description

The operations described in the General Decimal Arithmetic Specification are provided here.

It is suggested to import this module qualified to avoid Prelude name clashes:

import qualified Numeric.Decimal.Operation as Op

Note that it is not usually necessary to import this module unless you want to use operations unavailable through class methods, or you need precise control over the handling of exceptional conditions. (See also Numeric.Decimal.Arithmetic.)

Synopsis

Arithmetic operations

This section describes the arithmetic operations on, and some other functions of, numbers, including subnormal numbers, negative zeros, and special values (see also IEEE 754 §5 and §6).

General arithmetic

add :: (Precision p, Rounding r) => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

add takes two operands. If either operand is a special value then the general rules apply.

Otherwise, the operands are added.

The result is then rounded to precision digits if necessary, counting from the most significant digit of the result.

subtract :: (Precision p, Rounding r) => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

subtract takes two operands. If either operand is a special value then the general rules apply.

Otherwise, the operands are added after inverting the sign used for the second operand.

The result is then rounded to precision digits if necessary, counting from the most significant digit of the result.

multiply :: (Precision p, Rounding r) => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

multiply takes two operands. If either operand is a special value then the general rules apply. Otherwise, the operands are multiplied together (“long multiplication”), resulting in a number which may be as long as the sum of the lengths of the two operands.

The result is then rounded to precision digits if necessary, counting from the most significant digit of the result.

divide :: (FinitePrecision p, Rounding r) => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

divide takes two operands. If either operand is a special value then the general rules apply.

Otherwise, if the divisor is zero then either the Division undefined condition is raised (if the dividend is zero) and the result is NaN, or the Division by zero condition is raised and the result is an Infinity with a sign which is the exclusive or of the signs of the operands.

Otherwise, a “long division” is effected.

The result is then rounded to precision digits, if necessary, according to the rounding algorithm and taking into account the remainder from the division.

power :: (FinitePrecision p, Rounding r) => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

power takes two operands, and raises a number (the left-hand operand) to a power (the right-hand operand). If either operand is a special value then the general rules apply, except as stated below.

The following rules apply:

  • If both operands are zero, or if the left-hand operand is less than zero and the right-hand operand does not have an integral value or is infinite, an Invalid operation condition is raised, the result is NaN, and the following rules do not apply.
  • If the left-hand operand is infinite, the result will be exact and will be infinite if the right-hand side is positive, 1 if the right-hand side is a zero, and 0 if the right-hand side is negative.
  • If the left-hand operand is a zero, the result will be exact and will be infinite if the right-hand side is negative or 0 if the right-hand side is positive.
  • If the right-hand operand is a zero, the result will be 1 and exact.
  • In cases not covered above, the result will be inexact unless the right-hand side has an integral value and the result is finite and can be expressed exactly within precision digits. In this latter case, if the result is unrounded then its exponent will be that which would result if the operation were calculated by repeated multiplication (if the second operand is negative then the reciprocal of the first operand is used, with the absolute value of the second operand determining the multiplications).
  • Inexact finite results should be correctly rounded, but may be up to 1 ulp (unit in last place) in error.
  • The sign of the result will be 1 only if the right-hand side has an integral value and is odd (and is not infinite) and also the sign of the left-hand side is 1. In all other cases, the sign of the result will be 0.

squareRoot :: FinitePrecision p => Decimal a b -> Arith p r (Decimal p RoundHalfEven) Source #

squareRoot takes one operand. If the operand is a special value then the general rules apply.

Otherwise, the ideal exponent of the result is defined to be half the exponent of the operand (rounded to an integer, towards −Infinity, if necessary) and then:

If the operand is less than zero an Invalid operation condition is raised.

If the operand is greater than zero, the result is the square root of the operand. If no rounding is necessary (the exact result requires precision digits or fewer) then the coefficient and exponent giving the correct value and with the exponent closest to the ideal exponent is used. If the result must be inexact, it is rounded using the RoundHalfEven algorithm and the coefficient will have exactly precision digits (unless the result is subnormal), and the exponent will be set to maintain the correct value.

Otherwise (the operand is equal to zero), the result will be the zero with the same sign as the operand and with the ideal exponent.

fusedMultiplyAdd :: (Precision p, Rounding r) => Decimal a b -> Decimal c d -> Decimal e f -> Arith p r (Decimal p r) Source #

fusedMultiplyAdd takes three operands; the first two are multiplied together, using multiply, with sufficient precision and exponent range that the result is exact and unrounded. No flags are set by the multiplication unless one of the first two operands is a signaling NaN or one is a zero and the other is an infinity.

Unless the multiplication failed, the third operand is then added to the result of that multiplication, using add, under the current context.

In other words, fusedMultiplyAdd x y z delivers a result which is (x × y) + z with only the one, final, rounding.

Exponential and logarithmic

exp :: FinitePrecision p => Decimal a b -> Arith p r (Decimal p RoundHalfEven) Source #

exp takes one operand. If the operand is a NaN then the general rules for special values apply.

Otherwise, the result is e raised to the power of the operand, with the following cases:

  • If the operand is −Infinity, the result is 0 and exact.
  • If the operand is a zero, the result is 1 and exact.
  • If the operand is +Infinity, the result is +Infinity and exact.
  • Otherwise the result is inexact and will be rounded using the RoundHalfEven algorithm. The coefficient will have exactly precision digits (unless the result is subnormal). These inexact results should be correctly rounded, but may be up to 1 ulp (unit in last place) in error.

ln :: FinitePrecision p => Decimal a b -> Arith p r (Decimal p RoundHalfEven) Source #

ln takes one operand. If the operand is a NaN then the general rules for special values apply.

Otherwise, the operand must be a zero or positive, and the result is the natural (base e) logarithm of the operand, with the following cases:

  • If the operand is a zero, the result is −Infinity and exact.
  • If the operand is +Infinity, the result is +Infinity and exact.
  • If the operand equals one, the result is 0 and exact.
  • Otherwise the result is inexact and will be rounded using the RoundHalfEven algorithm. The coefficient will have exactly precision digits (unless the result is subnormal). These inexact results should be correctly rounded, but may be up to 1 ulp (unit in last place) in error.

log10 :: FinitePrecision p => Decimal a b -> Arith p r (Decimal p RoundHalfEven) Source #

log10 takes one operand. If the operand is a NaN then the general rules for special values apply.

Otherwise, the operand must be a zero or positive, and the result is the base 10 logarithm of the operand, with the following cases:

  • If the operand is a zero, the result is −Infinity and exact.
  • If the operand is +Infinity, the result is +Infinity and exact.
  • If the operand equals an integral power of ten (including 10^0 and negative powers) and there is sufficient precision to hold the integral part of the result, the result is an integer (with an exponent of 0) and exact.
  • Otherwise the result is inexact and will be rounded using the RoundHalfEven algorithm. The coefficient will have exactly precision digits (unless the result is subnormal). These inexact results should be correctly rounded, but may be up to 1 ulp (unit in last place) in error.

Unary sign

plus :: (Precision p, Rounding r) => Decimal a b -> Arith p r (Decimal p r) Source #

plus takes one operand, and corresponds to the prefix plus operator in programming languages.

Note that the result of this operation is affected by context and may set flags.

minus :: (Precision p, Rounding r) => Decimal a b -> Arith p r (Decimal p r) Source #

minus takes one operand, and corresponds to the prefix minus operator in programming languages.

Note that the result of this operation is affected by context and may set flags. The copyNegate operation may be used instead of minus if this is not desired.

abs :: (Precision p, Rounding r) => Decimal a b -> Arith p r (Decimal p r) Source #

abs takes one operand. If the operand is negative, the result is the same as using the minus operation on the operand. Otherwise, the result is the same as using the plus operation on the operand.

Note that the result of this operation is affected by context and may set flags. The copyAbs operation may be used if this is not desired.

Comparison

compare :: Decimal a b -> Decimal c d -> Arith p r (Either (Decimal p r) Ordering) Source #

compare takes two operands and compares their values numerically. If either operand is a special value then the general rules apply. No flags are set unless an operand is a signaling NaN.

Otherwise, the operands are compared, returning Right LT if the first is less than the second, Right EQ if they are equal, or Right GT if the first is greater than the second.

A Left value is returned if the result is NaN, indicating an “unordered” comparison (see IEEE 754 §5.11).

compareSignal :: Decimal a b -> Decimal c d -> Arith p r (Either (Decimal p r) Ordering) Source #

compareSignal takes two operands and compares their values numerically. This operation is identical to compare, except that if neither operand is a signaling NaN then any quiet NaN operand is treated as though it were a signaling NaN. (That is, all NaNs signal, with signaling NaNs taking precedence over quiet NaNs.)

min :: Decimal a b -> Decimal a b -> Arith p r (Decimal a b) Source #

min takes two operands, compares their values numerically, and returns the minimum. If either operand is a NaN then the general rules apply, unless one is a quiet NaN and the other is numeric, in which case the numeric operand is returned.

max :: Decimal a b -> Decimal a b -> Arith p r (Decimal a b) Source #

max takes two operands, compares their values numerically, and returns the maximum. If either operand is a NaN then the general rules apply, unless one is a quiet NaN and the other is numeric, in which case the numeric operand is returned.

minMagnitude :: Decimal a b -> Decimal a b -> Arith p r (Decimal a b) Source #

minMagnitude takes two operands and compares their values numerically with their sign ignored and assumed to be 0.

If, without signs, the first operand is the smaller then the original first operand is returned (that is, with the original sign). If, without signs, the second operand is the smaller then the original second operand is returned. Otherwise the result is the same as from the min operation.

maxMagnitude :: Decimal a b -> Decimal a b -> Arith p r (Decimal a b) Source #

maxMagnitude takes two operands and compares their values numerically with their sign ignored and assumed to be 0.

If, without signs, the first operand is the larger then the original first operand is returned (that is, with the original sign). If, without signs, the second operand is the larger then the original second operand is returned. Otherwise the result is the same as from the max operation.

Rounding and quantization

roundToIntegralValue :: (Precision a, Rounding r) => Decimal a b -> Arith p r (Decimal a r) Source #

roundToIntegralValue takes one operand. It is identical to the roundToIntegralExact operation except that the Inexact and Rounded flags are never set even if the operand is rounded (that is, the operation is quiet unless the operand is a signaling NaN).

roundToIntegralExact :: (Precision a, Rounding r) => Decimal a b -> Arith p r (Decimal a r) Source #

roundToIntegralExact takes one operand. If the operand is a special value, or the exponent of the operand is non-negative, then the result is the same as the operand (unless the operand is a signaling NaN, as usual).

Otherwise (the operand has a negative exponent) the result is the same as using the quantize operation using the given operand as the left-hand-operand, 1E+0 as the right-hand-operand, and the precision of the operand as the precision setting. The rounding mode is taken from the context, as usual.

quantize :: (Precision p, Rounding r) => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

quantize takes two operands. If either operand is a special value then the general rules apply, except that if either operand is infinite and the other is finite an Invalid operation condition is raised and the result is NaN, or if both are infinite then the result is the first operand.

Otherwise (both operands are finite), quantize returns the number which is equal in value (except for any rounding) and sign to the first (left-hand) operand and which has an exponent set to be equal to the exponent of the second (right-hand) operand.

The coefficient of the result is derived from that of the left-hand operand. It may be rounded using the current rounding setting (if the exponent is being increased), multiplied by a positive power of ten (if the exponent is being decreased), or is unchanged (if the exponent is already equal to that of the right-hand operand).

Unlike other operations, if the length of the coefficient after the quantize operation would be greater than precision then an Invalid operation condition is raised. This guarantees that, unless there is an error condition, the exponent of the result of a quantize is always equal to that of the right-hand operand.

Also unlike other operations, quantize will never raise Underflow, even if the result is subnormal and inexact.

reduce :: (Precision p, Rounding r) => Decimal a b -> Arith p r (Decimal p r) Source #

reduce takes one operand. It has the same semantics as the plus operation, except that if the final result is finite it is reduced to its simplest form, with all trailing zeros removed and its sign preserved.

Miscellaneous operations

This section describes miscellaneous operations on decimal numbers, including non-numeric comparisons, sign and other manipulations, and logical operations.

Some operations return a boolean value described as 0 or 1 in the General Decimal Arithmetic Specification, but which is returned as a Bool in this implementation. These values can be converted to Decimal via fromBool.

Similarly, the total ordering operations return an Ordering value in this implementation, but can be converted to Decimal via fromOrdering.

Logic and shifting

The logical operations (and, or, xor, and invert) take logical operands, which are finite numbers with a sign of 0, an exponent of 0, and a coefficient whose digits must all be either 0 or 1. The length of the result will be at most precision digits (all of which will be either 0 or 1); operands are truncated on the left or padded with zeros on the left as necessary. The result of a logical operation is never rounded and the only flag that might be set is InvalidOperation (set if an operand is not a valid logical operand).

and :: Precision p => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

and is a logical operation which takes two logical operands. The result is the digit-wise and of the two operands; each digit of the result is the logical and of the corresponding digits of the operands, aligned at the least-significant digit. A result digit is 1 if both of the corresponding operand digits are 1; otherwise it is 0.

or :: Precision p => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

or is a logical operation which takes two logical operands. The result is the digit-wise inclusive or of the two operands; each digit of the result is the logical or of the corresponding digits of the operands, aligned at the least-significant digit. A result digit is 1 if either or both of the corresponding operand digits is 1; otherwise it is 0.

xor :: Precision p => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

xor is a logical operation which takes two logical operands. The result is the digit-wise exclusive or of the two operands; each digit of the result is the logical exclusive-or of the corresponding digits of the operands, aligned at the least-significant digit. A result digit is 1 if one of the corresponding operand digits is 1 and the other is 0; otherwise it is 0.

invert :: FinitePrecision p => Decimal a b -> Arith p r (Decimal p r) Source #

invert is a logical operation which takes one logical operand. The result is the digit-wise inversion of the operand; each digit of the result is the inverse of the corresponding digit of the operand. A result digit is 1 if the corresponding operand digit is 0; otherwise it is 0.

shift :: Precision p => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

shift takes two operands. The second operand must be an integer (with an exponent of 0) in the range −precision through precision. If the first operand is a NaN then the general arithmetic rules apply, and if it is infinite then the result is the Infinity unchanged.

Otherwise (the first operand is finite) the result has the same sign and exponent as the first operand, and a coefficient which is a shifted copy of the digits in the coefficient of the first operand. The number of places to shift is taken from the absolute value of the second operand, with the shift being to the left if the second operand is positive or to the right otherwise. Digits shifted into the coefficient are zeros.

The only flag that might be set is InvalidOperation (set if the first operand is an sNaN or the second is not valid).

The rotate operation can be used to rotate rather than shift a coefficient.

rotate :: FinitePrecision p => Decimal a b -> Decimal c d -> Arith p r (Decimal p r) Source #

rotate takes two operands. The second operand must be an integer (with an exponent of 0) in the range −precision through precision. If the first operand is a NaN then the general arithmetic rules apply, and if it is infinite then the result is the Infinity unchanged.

Otherwise (the first operand is finite) the result has the same sign and exponent as the first operand, and a coefficient which is a rotated copy of the digits in the coefficient of the first operand. The number of places of rotation is taken from the absolute value of the second operand, with the rotation being to the left if the second operand is positive or to the right otherwise.

If the coefficient of the first operand has fewer than precision digits, it is treated as though it were padded on the left with zeros to length precision before the rotation. Similarly, if the coefficient of the first operand has more than precision digits, it is truncated on the left before use.

The only flag that might be set is InvalidOperation (set if the first operand is an sNaN or the second is not valid).

The shift operation can be used to shift rather than rotate a coefficient.

Predicates

isZero :: Decimal a b -> Arith p r Bool Source #

isZero takes one operand. The result is True if the operand is a zero; otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isSigned :: Decimal a b -> Arith p r Bool Source #

isSigned takes one operand. The result is True if the sign of the operand is 1; otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isFinite :: Decimal a b -> Arith p r Bool Source #

isFinite takes one operand. The result is True if the operand is neither infinite nor a NaN (that is, it is a normal number, a subnormal number, or a zero); otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isInfinite :: Decimal a b -> Arith p r Bool Source #

isInfinite takes one operand. The result is True if the operand is an Infinity; otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isNormal :: Precision a => Decimal a b -> Arith p r Bool Source #

isNormal takes one operand. The result is True if the operand is a positive or negative normal number; otherwise it is False. This operation is quiet; no flags are changed in the context.

isSubnormal :: Precision a => Decimal a b -> Arith p r Bool Source #

isSubnormal takes one operand. The result is True if the operand is a positive or negative subnormal number; otherwise it is False. This operation is quiet; no flags are changed in the context.

isNaN :: Decimal a b -> Arith p r Bool Source #

isNaN takes one operand. The result is True if the operand is a NaN (quiet or signaling); otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isQNaN :: Decimal a b -> Arith p r Bool Source #

isQNaN takes one operand. The result is True if the operand is a quiet NaN; otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isSNaN :: Decimal a b -> Arith p r Bool Source #

isSNaN takes one operand. The result is True if the operand is a signaling NaN; otherwise it is False. This operation is unaffected by context and is quiet — no flags are changed in the context.

isCanonical :: Decimal a b -> Arith p r Bool Source #

isCanonical takes one operand. The result is True if the operand is canonical; otherwise it is False. The definition of canonical is implementation-defined; if more than one internal encoding for a given NaN, Infinity, or finite number is possible then one “preferred” encoding is deemed canonical. This operation then tests whether the internal encoding is that preferred encoding.

If all possible operands have just one internal encoding each, then isCanonical always returns True. This operation is unaffected by context and is quiet — no flags are changed in the context.

Total comparison and classification

compareTotal :: Decimal a b -> Decimal c d -> Arith p r Ordering Source #

compareTotal takes two operands and compares them using their abstract representation rather than their numerical value. A total ordering is defined for all possible abstract representations, as described below. If the first operand is lower in the total order than the second operand then the result is LT, if the operands have the same abstract representation then the result is EQ, and if the first operand is higher in the total order than the second operand then the result is GT. The total ordering is defined as follows.

  1. The following items describe the ordering for representations whose sign is 0. If the sign is 1, the order is reversed. A representation with a sign of 1 is always lower in the ordering than one with a sign of 0.
  2. Numbers (representations which are not NaNs) are ordered such that a larger numerical value is higher in the ordering. If two representations have the same numerical value then the exponent is taken into account; larger (more positive) exponents are higher in the ordering.
  3. All quiet NaNs are higher in the total ordering than all signaling NaNs.
  4. Quiet NaNs and signaling NaNs are ordered according to their payload; a larger payload is higher in the ordering.

For example, the following values are ordered from lowest to highest: -NaN -sNaN -Infinity -127 -1 -1.00 -0 -0.000 0 1.2300 1.23 1E+9 Infinity sNaN NaN NaN456.

compareTotalMagnitude :: Decimal a b -> Decimal c d -> Arith p r Ordering Source #

compareTotalMagnitude takes two operands and compares them using their abstract representation rather than their numerical value and with their sign ignored and assumed to be 0. The result is identical to that obtained by using compareTotal on two operands which are the copyAbs copies of the operands to compareTotalMagnitude.

class' :: Precision a => Decimal a b -> Arith p r Class Source #

class' takes one operand. The result is an indication of the class of the operand, where the class is one of ten possibilities, corresponding to one of the strings "sNaN" (signaling NaN), "NaN" (quiet NaN), "-Infinity" (negative infinity), "-Normal" (negative normal finite number), "-Subnormal" (negative subnormal finite number), "-Zero" (negative zero), "+Zero" (non-negative zero), "+Subnormal" (positive subnormal finite number), "+Normal" (positive normal finite number), or "+Infinity" (positive infinity). This operation is quiet; no flags are changed in the context.

Note that unlike the special values in the model, the sign of any NaN is ignored in the classification, as required by IEEE 754.

data Class Source #

Constructors

NumberClass Sign NumberClass

Number (finite or infinite)

NaNClass NaNClass

Not a number (quiet or signaling)

Instances
Eq Class Source # 
Instance details

Defined in Numeric.Decimal.Operation

Methods

(==) :: Class -> Class -> Bool #

(/=) :: Class -> Class -> Bool #

Show Class Source # 
Instance details

Defined in Numeric.Decimal.Operation

Methods

showsPrec :: Int -> Class -> ShowS #

show :: Class -> String #

showList :: [Class] -> ShowS #

data Sign Source #

Constructors

Pos

Positive or non-negative

Neg

Negative

Instances
Enum Sign Source # 
Instance details

Defined in Numeric.Decimal.Number

Methods

succ :: Sign -> Sign #

pred :: Sign -> Sign #

toEnum :: Int -> Sign #

fromEnum :: Sign -> Int #

enumFrom :: Sign -> [Sign] #

enumFromThen :: Sign -> Sign -> [Sign] #

enumFromTo :: Sign -> Sign -> [Sign] #

enumFromThenTo :: Sign -> Sign -> Sign -> [Sign] #

Eq Sign Source # 
Instance details

Defined in Numeric.Decimal.Number

Methods

(==) :: Sign -> Sign -> Bool #

(/=) :: Sign -> Sign -> Bool #

NFData Sign Source # 
Instance details

Defined in Numeric.Decimal.Number

Methods

rnf :: Sign -> () #

data NumberClass Source #

Constructors

ZeroClass

Zero

SubnormalClass

Subnormal finite number

NormalClass

Normal finite number

InfinityClass

Infinity

Instances
Eq NumberClass Source # 
Instance details

Defined in Numeric.Decimal.Operation

Exponent manipulation

logb :: (Precision p, Rounding r) => Decimal a b -> Arith p r (Decimal p r) Source #

logb takes one operand. If the operand is a NaN then the general arithmetic rules apply. If the operand is infinite then +Infinity is returned. If the operand is a zero, then −Infinity is returned and the Division by zero exceptional condition is raised.

Otherwise, the result is the integer which is the exponent of the magnitude of the most significant digit of the operand (as though the operand were truncated to a single digit while maintaining the value of that digit and without limiting the resulting exponent). All results are exact unless an integer result does not fit in the available precision.

scaleb :: Decimal a b -> Decimal c d -> Arith p r (Decimal a b) Source #

scaleb takes two operands. If either operand is a NaN then the general arithmetic rules apply. Otherwise, the second operand must be a finite integer with an exponent of zero and in the range ±2 × (Emax + precision) inclusive, where Emax is the largest value that can be returned by the logb operation at the same precision setting. (If is is not, the Invalid Operation condition is raised and the result is NaN.)

If the first operand is infinite then that Infinity is returned, otherwise the result is the first operand modified by adding the value of the second operand to its exponent. The result may Overflow or Underflow.

sameQuantum :: Decimal a b -> Decimal c d -> Arith p r Bool Source #

sameQuantum takes two operands, and returns True if the two operands have the same exponent or False otherwise. The result is never affected by either the sign or the coefficient of either operand.

If either operand is a special value, True is returned only if both operands are NaNs or both are infinities.

sameQuantum does not change any flags in the context.

radix :: Precision p => Arith p r (Decimal p r) Source #

radix takes no operands. The result is the radix (base) in which arithmetic is effected; for this specification the result will have the value 10.

Sign manipulation and conversion

copyAbs :: Decimal a b -> Arith p r (Decimal a b) Source #

copyAbs takes one operand. The result is a copy of the operand with the sign set to 0. Unlike the abs operation, this operation is unaffected by context and is quiet — no flags are changed in the context.

copyNegate :: Decimal a b -> Arith p r (Decimal a b) Source #

copyNegate takes one operand. The result is a copy of the operand with the sign inverted (a sign of 0 becomes 1 and vice versa). Unlike the minus operation, this operation is unaffected by context and is quiet — no flags are changed in the context.

copySign :: Decimal a b -> Decimal c d -> Arith p r (Decimal a b) Source #

copySign takes two operands. The result is a copy of the first operand with the sign set to be the same as the sign of the second operand. This operation is unaffected by context and is quiet — no flags are changed in the context.

copy :: Decimal a b -> Arith p r (Decimal a b) Source #

copy takes one operand. The result is a copy of the operand. This operation is unaffected by context and is quiet — no flags are changed in the context.

canonical :: Decimal a b -> Arith p r (Decimal a b) Source #

canonical takes one operand. The result has the same value as the operand but always uses a canonical encoding. The definition of canonical is implementation-defined; if more than one internal encoding for a given NaN, Infinity, or finite number is possible then one “preferred” encoding is deemed canonical. This operation then returns the value using that preferred encoding.

If all possible operands have just one internal encoding each, then canonical always returns the operand unchanged (that is, it has the same effect as copy). This operation is unaffected by context and is quiet — no flags are changed in the context.