module Data.Number.FixedPrec (
Precision,
P0, P1, P10, P100, P1000, P2000,
PPlus1, PPlus3, PPlus10, PPlus100, PPlus1000,
FixedPrec,
getprec,
cast,
upcast,
downcast,
with_added_digits,
fractional,
solve_quadratic,
log_double
) where
import Data.Ratio
import System.Random
divi :: Integer -> Integer -> Integer
divi a b = (a + (b `div` 2)) `div` b
infixl 7 `divi`
decshiftR :: Int -> Integer -> Integer
decshiftR n x = x `divi` 10^n
dectruncR :: Int -> Integer -> Integer
dectruncR n x = x `quot` 10^n
decshiftL :: Int -> Integer -> Integer
decshiftL n x = x * 10^n
hibit :: Integer -> Int
hibit 0 = 0
hibit n = aux 1 where
aux k
| n >= 2^k = aux (2*k)
| otherwise = aux2 k (k `div` 2)
aux2 upper lower
| upper lower < 2 = upper
| n >= 2^middle = aux2 upper middle
| otherwise = aux2 middle lower
where
middle = (upper + lower) `div` 2
intsqrt :: (Integral n) => n -> n
intsqrt n
| n <= 0 = 0
| otherwise = iterate a
where
iterate m
| m_sq <= n && m_sq + 2*m + 1 > n = m
| otherwise = iterate ((m + n `div` m) `div` 2)
where
m_sq = m*m
a = 2^(b `div` 2)
b = hibit (fromIntegral n)
intquad :: Integer -> Integer -> Maybe Integer
intquad b c
| b^2 4*c < 0 = Nothing
| x1^2 + b*x1 + c >= 0 = Just x1
| otherwise = Just (iterate x0)
where
iterate x
| px <= 0 && px + 2*x+1+b > 0 = x+1
| otherwise = iterate ((x^2 c) `div` (2*x + b))
where
px = x^2 + b*x + c
x1 = (b `div` 2)
x0 = x1 + 2^(h `div` 2)
h = hibit (b^2 4*c)
floorlog :: (Fractional b, Ord b) => b -> b -> (Integer, b)
floorlog b x
| x <= 0 = error "floorlog: argument not positive"
| 1 <= x && x < b = (0, x)
| 1 <= x*b && x < 1 = (1, b*x)
| r < b = (2*n, r)
| otherwise = (2*n+1, r/b)
where
(n, r) = floorlog (b^2) x
log_double :: (Floating a, Real a) => a -> Double
log_double x = y where
e = exp 1
(n, r) = floorlog e x
y = fromInteger n + log (to_double r)
to_double = fromRational . toRational
class Precision e where
digits :: e -> Int
data P0
instance Precision P0 where
digits e = 0
data P1
instance Precision P1 where
digits e = 1
data P10
instance Precision P10 where
digits e = 10
data P100
instance Precision P100 where
digits e = 100
data P1000
instance Precision P1000 where
digits e = 1000
data P2000
instance Precision P2000 where
digits e = 2000
data PPlus1 e
instance Precision e => Precision (PPlus1 e) where
digits e = digits (un e) + 1 where
un :: PPlus1 e -> e
un = undefined
data PPlus3 e
instance Precision e => Precision (PPlus3 e) where
digits e = digits (un e) + 3 where
un :: PPlus3 e -> e
un = undefined
data PPlus10 e
instance Precision e => Precision (PPlus10 e) where
digits e = digits (un e) + 10 where
un :: PPlus10 e -> e
un = undefined
data PPlus100 e
instance Precision e => Precision (PPlus100 e) where
digits e = digits (un e) + 100 where
un :: PPlus100 e -> e
un = undefined
data PPlus1000 e
instance Precision e => Precision (PPlus1000 e) where
digits e = digits (un e) + 1000 where
un :: PPlus1000 e -> e
un = undefined
newtype FixedPrec e = F Integer
deriving (Eq, Ord)
getprec :: (Precision e) => FixedPrec e -> Int
getprec = digits . un where
un :: FixedPrec e -> e
un = undefined
cast :: (Precision e, Precision f) => FixedPrec e -> FixedPrec f
cast a@(F x) = b where
b = F y
px = getprec a
py = getprec b
y = if (px >= py) then
decshiftR (px py) x
else
decshiftL (py px) x
upcast :: (Precision e) => FixedPrec e -> FixedPrec (PPlus3 e)
upcast = cast
downcast :: (Precision e) => FixedPrec (PPlus3 e) -> FixedPrec e
downcast = cast
with_added_digits :: forall a f.(Precision f) => Int -> (forall e.(Precision e) => FixedPrec e -> a) -> FixedPrec f -> a
with_added_digits d f x = loop d (un x)
where
un :: FixedPrec e -> e
un = undefined
loop :: forall e.(Precision e) => Int -> e -> a
loop d e
| d >= 1000 = loop (d1000) (undefined :: PPlus1000 e)
| d >= 100 = loop (d100) (undefined :: PPlus100 e)
| d >= 10 = loop (d10) (undefined :: PPlus10 e)
| d > 0 = loop (d1) (undefined :: PPlus1 e)
| otherwise = f (cast x :: FixedPrec e)
(..*) :: Integer -> FixedPrec e -> FixedPrec e
n ..* (F x) = F (n * x)
infixl 7 ..*
(/..) :: FixedPrec e -> Integer -> FixedPrec e
(F x) /.. n = F (x `divi` n)
infixl 7 /..
fractional :: (Precision e) => FixedPrec e -> FixedPrec e
fractional a@(F x) = F (x `mod` one) where
p = getprec a
one = (decshiftL p 1)
solve_quadratic :: (Precision e) => FixedPrec e -> FixedPrec e -> Maybe (FixedPrec e, FixedPrec e)
solve_quadratic b c = do
let p = getprec b + 3
b' = floor (b * 10^p)
c' = floor (c * 100^p)
x2' <- intquad b' c'
let x1' = b' x2'
return (fromInteger x1' / 10^p, fromInteger x2' / 10^p)
accs :: (Rational -> Integer -> Rational) -> [Rational]
accs f = scanl f 1 [1..]
powerseries :: (Precision e) => [Rational] -> FixedPrec e -> FixedPrec e
powerseries [] x = 0
powerseries (h:t) x
| h' == 0 = a
| otherwise = a + x * powerseries t x
where
a@(F h') = fromRational h
sin_p :: (Precision e) => FixedPrec e -> FixedPrec e
sin_p x = x * powerseries (accs (\a n -> a * (1 % (2*n*(2*n+1))))) (x^2)
cos_p :: (Precision e) => FixedPrec e -> FixedPrec e
cos_p x = powerseries (accs (\a n -> a * (1 % (2*n*(2*n1))))) (x^2)
exp_p :: (Precision e) => FixedPrec e -> FixedPrec e
exp_p x = powerseries (accs (\a n -> a * (1 % n))) x
log_p :: (Precision e) => FixedPrec e -> FixedPrec e
log_p x = (x1) * powerseries [ 1 % ((4)^n * (n+1)) | n <- [0..] ] (4*(x1))
atan_p :: (Precision e) => FixedPrec e -> FixedPrec e
atan_p x = x * powerseries [ 1 % ((5)^n * (2*n+1)) | n <- [0..]] (5*x*x)
atan_p2 :: (Precision e) => FixedPrec e -> FixedPrec e
atan_p2 x = x * powerseries [ 1 % ((25)^n * (2*n+1)) | n <- [0..]] (25*x*x)
atan_p3 :: (Precision e) => FixedPrec e -> FixedPrec e
atan_p3 x = x * powerseries [ 1 % ((57121)^n * (2*n+1)) | n <- [0..]] (57121*x*x)
sin_raw :: (Precision e) => FixedPrec e -> FixedPrec e
sin_raw x
| 1 <= x && x < 1 = sin_p x
| m == 0 = sin_p x'
| m == 1 = cos_p x'
| m == 2 = sin_p x'
| otherwise = cos_p x'
where
n = round (x / p2)
m = n `mod` 4
x' = x n ..* p2
p2 = pi /.. 2
cos_raw :: (Precision e) => FixedPrec e -> FixedPrec e
cos_raw x
| 1 <= x && x < 1 = cos_p x
| m == 0 = cos_p x'
| m == 1 = sin_p x'
| m == 2 = cos_p x'
| otherwise = sin_p x'
where
n = round (x / p2)
m = n `mod` 4
x' = x n ..* p2
p2 = pi /.. 2
exp_raw :: (Precision e) => FixedPrec e -> FixedPrec e
exp_raw x
| 1 <= x && x <= 1 = exp_p x
| otherwise = exp_raw (x/2) ^2
log_raw :: (Precision e) => FixedPrec e -> FixedPrec e
log_raw x
| x <= 0 = error "log: argument out of range"
| 0.75 <= x && x <= 1.25 = log_p x
| x > 3.5 = fromInteger n + log r
| x > 1 = 0.5 + log (x / e2)
| otherwise = log (1 / x)
where
e2 = exp_p 0.5
e = exp_p 1
(n, r) = floorlog e x
power_raw :: (Precision e) => FixedPrec e -> FixedPrec e -> FixedPrec e
power_raw x y = exp_raw (log_raw x * y)
logBase_raw :: (Precision e) => FixedPrec e -> FixedPrec e -> FixedPrec e
logBase_raw x y = log y / log x
sqrt_raw :: (Precision e) => FixedPrec e -> FixedPrec e
sqrt_raw a@(F x)
| a >= 0 = F y
| otherwise = error "sqrt: argument out of range"
where
p = getprec a
y = intsqrt (x * 10^p)
atan_raw :: (Precision e) => FixedPrec e -> FixedPrec e
atan_raw x
| 0.44 <= x && x <= 0.44 = atan_p x
| x < 0 = atan (x)
| x >= 2.27 = p2 atan_p (1/x)
| otherwise = p4 + atan_p ((x1)/(x+1))
where
p2 = pi /.. 2
p4 = pi /.. 4
pi_raw :: (Precision e) => FixedPrec e
pi_raw = 16 ..* atan_p2 (1/5) 4 ..* atan_p3 (1/239)
asin_raw :: (Precision e) => FixedPrec e -> FixedPrec e
asin_raw x
| 0.7 <= x && x <= 0.7 = atan (x / cos)
| x > 0 && x <= 1 = p2 atan (cos / x)
| x < 0 && x >= 1 = p2 atan (cos / x)
| otherwise = error "asin: argument out of range"
where
cos = sqrt(1 x^2)
p2 = pi /.. 2
acos_raw :: (Precision e) => FixedPrec e -> FixedPrec e
acos_raw x
| 0.7 <= x && x <= 0.7 = p2 atan (x / sin)
| x > 0 && x <= 1 = atan (sin / x)
| x < 0 && x >= 1 = pi + atan (sin / x)
| otherwise = error "acos: argument out of range"
where
sin = sqrt(1 x^2)
p2 = pi /.. 2
sinh_raw :: (Precision e) => FixedPrec e -> FixedPrec e
sinh_raw x = (e 1/e) /.. 2 where e = exp x
cosh_raw :: (Precision e) => FixedPrec e -> FixedPrec e
cosh_raw x = (e + 1/e) /.. 2 where e = exp x
atanh_raw :: (Precision e) => FixedPrec e -> FixedPrec e
atanh_raw x = log ((1+x) / (1x)) /.. 2
asinh_raw :: (Precision e) => FixedPrec e -> FixedPrec e
asinh_raw x = log (x + sqrt (x^2+1))
acosh_raw :: (Precision e) => FixedPrec e -> FixedPrec e
acosh_raw x
| x >= 1 = log (x + sqrt (x^21))
| otherwise = error "acosh: argument out of range"
instance (Precision e) => Show (FixedPrec e) where
show a@(F x) = sign ++ integral ++ "." ++ fractional where
x' = abs x
sign = if x < 0 then "-" else ""
integral = show (dectruncR p x')
fractional' = show $ x' `mod` (decshiftL p 1)
fractional = pad_to_length p '0' fractional'
p = getprec a
pad_to_length p c l = replicate (p length l) c ++ l
instance (Precision e) => Num (FixedPrec e) where
F x + F y = F (x+y)
a@(F x) * F y = F (decshiftR (getprec a) (x*y))
F x F y = F (xy)
negate (F x) = F (negate x)
abs (F x) = F (abs x)
signum (F x) = fromInteger (signum x)
fromInteger x = y where
y = F (decshiftL p x) where
p = getprec y
instance (Precision e) => Fractional (FixedPrec e) where
a@(F x) / F y = F ((10^p * x) `divi` y) where
p = getprec a
fromRational r = fromInteger num / fromInteger denom where
num = numerator r
denom = denominator r
instance (Precision e) => Real (FixedPrec e) where
toRational a@(F x) = x % one where
p = getprec a
one = (decshiftL p 1)
instance (Precision e) => RealFrac (FixedPrec e) where
properFraction a@(F x) = (fromInteger n, F y) where
p = getprec a
y = x `rem` one
n = x `quot` one
one = (decshiftL p 1)
instance (Precision e) => Floating (FixedPrec e) where
pi = downcast pi_raw
sin = downcast . sin_raw . upcast
cos = downcast . cos_raw . upcast
log = downcast . log_raw . upcast
sqrt = downcast . sqrt_raw . upcast
atan = downcast . atan_raw . upcast
asin = downcast . asin_raw . upcast
acos = downcast . acos_raw . upcast
sinh = downcast . sinh_raw . upcast
cosh = downcast . cosh_raw . upcast
atanh = downcast . atanh_raw . upcast
asinh = downcast . asinh_raw . upcast
acosh = downcast . acosh_raw . upcast
exp x
| x <= 1 = exp_raw x
| otherwise = with_added_digits d (cast . exp_raw) x
where
d = 1 + ceiling (x * 0.45)
x ** y
| x <= 1 = power_raw x y
| otherwise = with_added_digits d (cast . (power_raw (cast x))) y
where
d = 1 + ceiling (0.45 * y * cast (log_raw (cast x :: FixedPrec P10)))
logBase x y
| (x < 0.36 || x > 2.72) && lo < y && y < hi = downcast (logBase_raw (upcast x) (upcast y))
| otherwise = with_added_digits d (cast . (logBase_raw (cast x))) y
where
dx = ceiling (0.45 * log (abs (log_double x)))
dy = ceiling (0.45 * log (abs (log_double y)))
d = max dx (2*dx + dy)
lo = 10000000000
hi = 0.0000000001
instance Precision e => Random (FixedPrec e) where
randomR (lo, hi) g = (x, g1) where
n = getprec x
lo_n = floor (lo * 10^n)
hi_n = floor (hi * 10^n)
(x_n, g1) = randomR (lo_n, hi_n) g
x = 0.1^n * fromInteger x_n
random = randomR (0, 1)