module Data.BigFloating
( piChudnovsky
, sqr
, nthRoot
)
where
import Data.BigDecimal
import Data.List (find)
import Data.Maybe (fromMaybe)
import GHC.Real ((%), Ratio ((:%)))
instance Floating BigDecimal where
pi = piChudnovsky defaultMC
exp = undefined
log = undefined
sin = undefined
cos = undefined
asin = undefined
acos = undefined
atan = undefined
sinh = undefined
cosh = undefined
asinh = undefined
acosh = undefined
atanh = undefined
sqrt x = sqr x defaultMC
x ** y = nthRoot (x^b) n defaultMC
where
(b :% n) = toRational y
defaultMC = (DOWN, Just 100)
sqr :: BigDecimal -> MathContext -> BigDecimal
sqr x mc
| x < 0 = error "can't determine the square root of negative numbers"
| x == 0 = 0
| otherwise = fst $ fromMaybe (error "did not find a sqrt") $ refine x 1 mc
where
refine x initial mc@(_, Just scale) = find withinPrecision $ iterate nextGuess (initial, 0)
where
withinPrecision (guess, count) = abs (guess^2 - x) < BigDecimal 10 scale || count > 10 * scale * precision x
nextGuess (guess, count) = (nf $ divide (guess + divide (x, guess) mc, 2) mc, count+1)
nthRoot :: BigDecimal -> Integer -> MathContext -> BigDecimal
nthRoot x n mc@(r,Just s)
| x < 0 && even n = error "can't determine even roots of negative numbers"
| x < 0 && odd n = - nthRoot x (-n) mc
| x == 0 = 0
| otherwise = roundBD (fst (fromMaybe (error "did not find a sqrt") $ refine x 1 (r, Just (s+4)))) mc
where
refine x initial mc@(_, Just scale) = find withinPrecision $ iterate nextGuess (initial, 0)
where
withinPrecision (guess, count) = abs (guess^n - x) < BigDecimal (n*10) scale || count > 10 * scale * precision x
nextGuess (guess, count) =
(nf $ divide ((guess * BigDecimal (n-1) 0) + divide (x, guess^(n-1)) mc, BigDecimal n 0) mc, count+1)
piChudnovsky :: MathContext -> BigDecimal
piChudnovsky mc@(rMode, Just scale) = divide (1, 12 * divide (fromRatio s mc,f) mc') mc
where
mc' = (rMode, Just $ scale + 3)
steps = 1 + div scale 14
s = sum [chudnovsky n | n <- [0..steps]] :: Rational
f = sqr (fromInteger c^3) mc
chudnovsky :: Integer -> Rational
chudnovsky k
| even k = quot
| otherwise = -quot
where
quot = num % den
num = facDiv (6 * k) (3 * k) * (a + b * k)
den = fac k ^ 3 * (c ^ (3 * k))
fac :: (Enum a, Num a) => a -> a
fac n = product [1..n]
facDiv :: Integer -> Integer -> Integer
facDiv n m
| n > m = product [n, n - 1 .. m + 1]
| n == m = 1
| otherwise = facDiv m n
a = 13591409
b = 545140134
c = 640320