Fixed precision decimal numbers type
Example of defining 256-bit signed decimal with 10-digit fractional part:
{-# LANGUAGE DataKinds #-}
import Data.DoubleWord (Int256)
import Data.Fixed.Decimal (Decimal)
type DecimalI256 = Decimal Int256 10
>>>
minBound :: Decimal Int 5
-92233720368547.75808
>>>
maxBound :: Decimal Int256 25
5789604461865809771178549250434395392663499233282028.2019728792003956564819967
>>>
1 / 3 :: Decimal Integer 50
0.33333333333333333333333333333333333333333333333333
[
Skip to Readme]
fixed-decimal
Fixed-precision decimals for Haskell
The purpose of this package
To provide simple high-performance fixed-precision decimals data types for Haskell.
High-performance in this implementation is achieved due to core "unchecked" implementation approach:
- The implementation is "precision-fixed" on type-level and is never recalculated so internally only fast integral arithmetic is used;
- Core implementation does not check for arithmetic overflows or precision overflows;
- Core implementation does not do any rounding of the result of any operation.
As a result the performance of this implementation, especially for smaller Integral
mantissas is in-par (or faster) than standard Double
and much faster than arbitrary precision decimal implementations.
NB: Subsequent versions might add optional rounding and overflow detection but the core "unchecked" functionality will still be available for user code which does not need such checks but needs better performance.
How to use it
The core of this library is type Decimal (m :: Type) (s :: Nat)
which expects two arguments:
- Integral
m :: Type
to store mantissa:
Any Integral
type can be passed as m
parameter: standard Int
, double-word's signed Int256
or unsigned Word128
or even Integer
for mantissa or arbitrary length;
- Type-level number
s :: Nat
which specifies the fractional part size (in decimal digits).
The following example defines decimal number type which uses (signed) 256 bits to store mantissa with 10-digit fractional part:
{-# LANGUAGE DataKinds #-}
import Data.DoubleWord (Int256)
import Data.Fixed.Decimal (Decimal)
type DecimalI256 = Decimal Int256 10
Minimum and maximum values which can be stored for various Decimal m s
flavours:
>>> minBound :: Decimal Int 5
-92233720368547.75808
>>> maxBound :: Decimal Int256 25
5789604461865809771178549250434395392663499233282028.2019728792003956564819967
>>> minBound :: Decimal Word128 10
0
>>> maxBound :: Decimal Word128 10
34028236692093846346337460743.1768211455
To use mantissa of arbitrary length use Integer
:
>>> 1 / 3 :: Decimal Integer 50
0.33333333333333333333333333333333333333333333333333
Fixed-precision vs floating point numeric types
In comparison to floating-point numeric data types like Float
or Double
fixed-precision decimals can store decimal numbers with exact precision.
For example Double
cannot represent number 0.01
exactly:
>>> sum $ replicate 10 (0.01 :: Double)
9.999999999999999e-2
>>> sum $ replicate 100 (0.01 :: Double)
1.0000000000000007
while Decimal m s
can:
>>> sum $ replicate 10 (0.01 :: Decimal Int 2)
0.1
>>> sum $ replicate 100 (0.01 :: Decimal Int 2)
1
In spirit of other Haskell numeric types Decimal m s
does not detect or handle numeric overflows, i.e. when the result of operation cannot be represented using the supplied m :: Type
mantissa type or s :: Nat
-digits fractional part. In such case no error will be thrown while the resulting number will be incorrect.
The only way to avoid this situation is to select appropriate m
and s
: large enough to store any possible results.
NB: Smaller m :: Type
however exhibit better performance, e.g. Decimal Int 5
will be more performant that Decimal Int256 5
and much better then Decimal Integer 5
Benchmarks
Benchmarks for various flavours of Decimal m s
plus the results for the same benchmarks for Double
and Decimal