module Data.BigDecimal
( BigDecimal (..)
, RoundingMode (..)
, MathContext
, getScale
, getValue
, precision
, trim
, nf
, divide
, roundBD
, fromRatio
, halfUp
, fromString
, matchScales
, toString
)
where
import Data.List (find, elemIndex)
import Data.Maybe (fromMaybe)
import GHC.Real ((%), Ratio ((:%)))
data RoundingMode
= UP
| DOWN
| CEILING
| FLOOR
| HALF_UP
| HALF_DOWN
| HALF_EVEN
| PRECISE
data BigDecimal =
BigDecimal Integer Integer
deriving (Show, Read)
getScale :: BigDecimal -> Integer
getScale (BigDecimal _ s) = s
getValue :: BigDecimal -> Integer
getValue (BigDecimal v _) = v
type MathContext = (RoundingMode, Maybe Integer)
instance Num BigDecimal where
a + b = plus (a, b)
a * b = mul (a, b)
abs (BigDecimal v s) = BigDecimal (abs v) s
signum (BigDecimal v _) = BigDecimal (signum v) 0
fromInteger i = BigDecimal i 0
negate (BigDecimal v s) = BigDecimal (-v) s
instance Eq BigDecimal where
a == b =
let (BigDecimal valA _, BigDecimal valB _) = matchScales (a, b)
in valA == valB
instance Fractional BigDecimal where
a / b = nf $ divide (matchScales (a, b)) (HALF_UP, Nothing)
fromRational ratio@(x :% y) = fromRatio ratio (HALF_UP, Nothing)
fromRatio :: Rational -> MathContext -> BigDecimal
fromRatio (x :% y) = divide (fromInteger x, fromInteger y)
instance Real BigDecimal where
toRational (BigDecimal val scale) = toRational val * 10^^(-scale)
instance Ord BigDecimal where
compare a b =
let (BigDecimal valA _, BigDecimal valB _) = matchScales (a, b)
in compare valA valB
plus :: (BigDecimal, BigDecimal) -> BigDecimal
plus (a@(BigDecimal valA scaleA), b@(BigDecimal valB scaleB))
| scaleA == scaleB = BigDecimal (valA + valB) scaleA
| otherwise = plus $ matchScales (a,b)
mul :: (BigDecimal, BigDecimal) -> BigDecimal
mul (BigDecimal valA scaleA, BigDecimal valB scaleB) = BigDecimal (valA * valB) (scaleA + scaleB)
divide :: (BigDecimal, BigDecimal)
-> MathContext
-> BigDecimal
divide (a, b) (rMode, prefScale) =
let (BigDecimal numA _, BigDecimal numB _) = matchScales (a, b)
maxPrecision = fromMaybe (precision a + round (fromInteger (precision b) * 10 / 3)) prefScale
in trim maxPrecision (BigDecimal (divUsing rMode (numA * (10 :: Integer) ^ maxPrecision) numB) maxPrecision)
divUsing :: RoundingMode -> Integer -> Integer -> Integer
divUsing rounding a b =
let (quot, rem) = quotRem a b
delta = (10 * abs rem `div` abs b) - 5
in case rounding of
PRECISE -> if rem == 0 then quot else error "non-terminating decimal expansion"
UP -> if abs rem > 0 then quot + signum quot else quot
CEILING -> if abs rem > 0 && quot >= 0 then quot + 1 else quot
HALF_UP -> if delta >= 0 then quot + signum quot else quot
HALF_DOWN -> if delta <= 0 then quot else quot + signum quot
DOWN -> quot
FLOOR -> if quot >= 0 then quot else quot - 1
HALF_EVEN
| delta > 0 -> quot + signum quot
| delta == 0 && odd quot -> quot + signum quot
| otherwise -> quot
roundBD :: BigDecimal -> MathContext -> BigDecimal
roundBD bd@(BigDecimal val scale) mc@(rMode, Just n)
| n < 0 || n >= scale = bd
| otherwise = BigDecimal (divUsing rMode val (10 ^ (scale-n))) n
matchScales :: (BigDecimal, BigDecimal) -> (BigDecimal, BigDecimal)
matchScales (a@(BigDecimal integerA scaleA), b@(BigDecimal integerB scaleB))
| scaleA < scaleB = (BigDecimal (integerA * 10 ^ (scaleB - scaleA)) scaleB, b)
| scaleA > scaleB = (a, BigDecimal (integerB * 10 ^ (scaleA - scaleB)) scaleA)
| otherwise = (a, b)
precision :: BigDecimal -> Integer
precision 0 = 1
precision (BigDecimal val _) = 1 + floor (logBase 10 $ abs $ fromInteger val)
trim :: Integer -> BigDecimal -> BigDecimal
trim prefScale bd@(BigDecimal val scale) =
let (v, r) = quotRem val 10
in if r == 0 && 0 <= prefScale && prefScale < scale
then trim prefScale $ BigDecimal v (scale - 1)
else bd
nf :: BigDecimal -> BigDecimal
nf = trim 0
fromString :: String -> BigDecimal
fromString s =
let maybeIndex = elemIndex '.' s
intValue = read (filter (/= '.') s) :: Integer
in case maybeIndex of
Nothing -> BigDecimal intValue 0
Just i -> BigDecimal intValue $ toInteger (length s - i - 1)
toString :: BigDecimal -> String
toString bd@(BigDecimal intValue scale) =
let s = show $ abs intValue
filled =
if fromInteger scale >= length s
then replicate (1 + fromInteger scale - length s) '0' ++ s
else s
splitPos = length filled - fromInteger scale
(ints, decimals) = splitAt splitPos filled
sign = if intValue < 0 then "-" else ""
in sign ++ if not (null decimals) then ints ++ "." ++ decimals else ints
halfUp :: Integer -> MathContext
halfUp scale = (HALF_UP, Just scale)