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

Safe HaskellTrustworthy
LanguageHaskell2010

Numeric.Decimal.Arithmetic

Contents

Description

It is not usually necessary to import this module unless you want to use the arithmetic operations from Numeric.Decimal.Operation or you need precise control over the handling of exceptional conditions in an arithmetic computation.

Synopsis

Decimal arithmetic

Decimal arithmetic is performed within a context that maintains state to handle exceptional conditions such as underflow, rounding, or division by zero (cf. Signal). The Arith monad provides a means to evaluate an arithmetic computation and manipulate its Context.

Context

data Context p r Source

A context for decimal arithmetic, carrying signal flags, trap enabler state, and a trap handler, parameterized by precision p and rounding algorithm r

Instances

MonadState (Context p r) (Arith p r) Source

The Context of an arithmetic computation may be manipulated using get and put, et al. For example, the current signal flags can be observed with gets flags.

newContext :: Context p r Source

Return a new context with all signal flags cleared and all traps disabled.

flags :: Context p r -> Signals Source

The current signal flags of the context

getPrecision :: Precision p => Arith p r (Maybe Int) Source

Return the precision of the arithmetic context (or Nothing if the precision is infinite).

getRounding :: Rounding r => Arith p r RoundingAlgorithm Source

Return the rounding algorithm of the arithmetic context.

data RoundingAlgorithm Source

A value representation of a rounding algorithm (cf. Rounding).

Default contexts

The General Decimal Arithmetic specification defines optional default contexts, which define suitable settings for basic arithmetic and for the extended arithmetic defined by IEEE 854 and IEEE 754.

basicDefaultContext :: Context P9 RoundHalfUp Source

Return a new context with all signal flags cleared, all traps enabled except for Inexact, Rounded, and Subnormal, using a precision of 9 significant decimal digits, and rounding half up. Trapped signals simply call throwError with the corresponding Exception, and can be caught using catchError.

extendedDefaultContext :: Context p RoundHalfEven Source

Return a new context with all signal flags cleared, all traps disabled (IEEE 854 §7), using selectable precision (the IEEE 754 smallest and basic formats correspond to precisions P7, P16, or P34), and rounding half even (IEEE 754 §4.3.3).

The Arith monad

data Arith p r a Source

A decimal arithmetic monad parameterized by the precision p and rounding algorithm r

Instances

Monad (Arith p r) Source 
Functor (Arith p r) Source 
Applicative (Arith p r) Source 
MonadError (Exception p r) (Arith p r) Source

Traps (vis-à-vis TrapHandler) may call throwError to abort the arithmetic computation (or be caught using catchError).

MonadState (Context p r) (Arith p r) Source

The Context of an arithmetic computation may be manipulated using get and put, et al. For example, the current signal flags can be observed with gets flags.

runArith :: Arith p r a -> Context p r -> (Either (Exception p r) a, Context p r) Source

Evaluate an arithmetic computation in the given context and return the final value (or exception) and resulting context.

evalArith :: Arith p r a -> Context p r -> Either (Exception p r) a Source

Evaluate an arithmetic computation in the given context and return the final value or exception, discarding the resulting context.

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

Perform a subcomputation using a different precision and/or rounding algorithm. The subcomputation is evaluated within a new context with all flags cleared and all traps disabled. Any flags set in the context of the subcomputation are ignored, but if an exception is returned it will be re-raised within the current context.

Exceptional conditions

Exceptional conditions are grouped into signals, which can be controlled individually. A Context contains a flag and a trap enabler (i.e. enabled or disabled) for each Signal.

data Exception p r Source

A representation of an exceptional condition

Instances

Show (Exception p r) Source 
MonadError (Exception p r) (Arith p r) Source

Traps (vis-à-vis TrapHandler) may call throwError to abort the arithmetic computation (or be caught using catchError).

exceptionSignal :: Exception p r -> Signal Source

The signal raised by the exceptional condition

exceptionResult :: Exception p r -> Decimal p r Source

The defined result for the exceptional condition

Signals

data Signal Source

Constructors

Clamped

Raised when the exponent of a result has been altered or constrained in order to fit the constraints of a specific concrete representation

DivisionByZero

Raised when a non-zero dividend is divided by zero

Inexact

Raised when a result is not exact (one or more non-zero coefficient digits were discarded during rounding)

InvalidOperation

Raised when a result would be undefined or impossible

Overflow

Raised when the exponent of a result is too large to be represented

Rounded

Raised when a result has been rounded (that is, some zero or non-zero coefficient digits were discarded)

Subnormal

Raised when a result is subnormal (its adjusted exponent is less than Emin), before any rounding

Underflow

Raised when a result is both subnormal and inexact

data Signals Source

A group of signals can be manipulated as a set.

signal :: Signal -> Signals Source

Create a set of signals from a singleton.

signals :: [Signal] -> Signals Source

Create a set of signals from a list.

allSignals :: Signals Source

A set containing every signal

signalMember :: Signal -> Signals -> Bool Source

Determine whether a signal is a member of a set.

raiseSignal :: Signal -> Decimal p r -> Arith p r (Decimal p r) Source

Set the given signal flag in the context of the current arithmetic computation, and call the trap handler if the trap for this signal is currently enabled.

clearFlags :: Signals -> Arith p r () Source

Clear the given signal flags from the context of the current arithmetic computation.

Traps

type TrapHandler p r = Exception p r -> Arith p r (Decimal p r) Source

A trap handler function may return a substitute result for the operation that caused the exceptional condition, or it may call throwError to pass control to an enclosing catchError handler (or abort the arithmetic computation).

trap :: Signals -> TrapHandler p r -> Arith p r a -> Arith p r a Source

Evaluate an arithmetic computation within a modified context that enables the given signals to be trapped by the given handler. The previous trap handler (and enabler state) will be restored during any trap, as well as upon completion. Any existing trap handlers for signals not mentioned remain in effect.