{-# LANGUAGE RankNTypes          #-}
{-# LANGUAGE ParallelListComp    #-}

{-# OPTIONS_HADDOCK show-extensions #-}

{-|
Module      : Data.ExactPi
Description : Exact rational multiples of powers of pi
License     : MIT
Maintainer  : douglas.mcclean@gmail.com
Stability   : experimental

This type is sufficient to exactly express the closure of Q ∪ {π} under multiplication and division.
As a result it is useful for representing conversion factors
between physical units. Approximate values are included both to close the remainder
of the arithmetic operations in the `Num` typeclass and to encode conversion
factors defined experimentally.
-}
module Data.ExactPi
(
  ExactPi(..),
  approximateValue,
  isZero,
  isExact,
  isExactZero,
  isExactOne,
  areExactlyEqual,
  isExactInteger,
  toExactInteger,
  isExactRational,
  toExactRational,
  rationalApproximations,
  -- * Utils

  getRationalLimit
)
where

import Data.Monoid
import Data.Ratio ((%), numerator, denominator)
import Data.Semigroup
import Prelude

-- | Represents an exact or approximate real value.

-- The exactly representable values are rational multiples of an integer power of pi.

data ExactPi = Exact Integer Rational -- ^ @'Exact' z q@ = q * pi^z. Note that this means there are many representations of zero.

             | Approximate (forall a.Floating a => a) -- ^ An approximate value. This representation was chosen because it allows conversion to floating types using their native definition of 'pi'.


-- | Approximates an exact or approximate value, converting it to a `Floating` type.

-- This uses the value of `pi` supplied by the destination type, to provide the appropriate

-- precision.

approximateValue :: Floating a => ExactPi -> a
approximateValue :: ExactPi -> a
approximateValue (Exact z :: Integer
z q :: Rational
q) = (a
forall a. Floating a => a
pi a -> Integer -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Integer
z) a -> a -> a
forall a. Num a => a -> a -> a
* (Rational -> a
forall a. Fractional a => Rational -> a
fromRational Rational
q)
approximateValue (Approximate x :: forall a. Floating a => a
x) = a
forall a. Floating a => a
x

-- | Identifies whether an 'ExactPi' is an exact or approximate representation of zero.

isZero :: ExactPi -> Bool
isZero :: ExactPi -> Bool
isZero (Exact _ 0)     = Bool
True
isZero (Approximate x :: forall a. Floating a => a
x) = Double
forall a. Floating a => a
x Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== (0 :: Double)
isZero _               = Bool
False

-- | Identifies whether an 'ExactPi' is an exact value.

isExact :: ExactPi -> Bool
isExact :: ExactPi -> Bool
isExact (Exact _ _) = Bool
True
isExact _           = Bool
False

-- | Identifies whether an 'ExactPi' is an exact representation of zero.

isExactZero :: ExactPi -> Bool
isExactZero :: ExactPi -> Bool
isExactZero (Exact _ 0) = Bool
True
isExactZero _ = Bool
False

-- | Identifies whether an 'ExactPi' is an exact representation of one.

isExactOne :: ExactPi -> Bool
isExactOne :: ExactPi -> Bool
isExactOne (Exact 0 1) = Bool
True
isExactOne _ = Bool
False

-- | Identifies whether two 'ExactPi' values are exactly equal.

areExactlyEqual :: ExactPi -> ExactPi -> Bool
areExactlyEqual :: ExactPi -> ExactPi -> Bool
areExactlyEqual (Exact z1 :: Integer
z1 q1 :: Rational
q1) (Exact z2 :: Integer
z2 q2 :: Rational
q2) = (Integer
z1 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
z2 Bool -> Bool -> Bool
&& Rational
q1 Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
== Rational
q2) Bool -> Bool -> Bool
|| (Rational
q1 Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
== 0 Bool -> Bool -> Bool
&& Rational
q2 Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
== 0)
areExactlyEqual _ _ = Bool
False

-- | Identifies whether an 'ExactPi' is an exact representation of an integer.

isExactInteger :: ExactPi -> Bool
isExactInteger :: ExactPi -> Bool
isExactInteger (Exact 0 q :: Rational
q) | Rational -> Integer
forall a. Ratio a -> a
denominator Rational
q Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 1 = Bool
True
isExactInteger _                                = Bool
False

-- | Converts an 'ExactPi' to an exact 'Integer' or 'Nothing'.

toExactInteger :: ExactPi -> Maybe Integer
toExactInteger :: ExactPi -> Maybe Integer
toExactInteger (Exact 0 q :: Rational
q) | Rational -> Integer
forall a. Ratio a -> a
denominator Rational
q Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 1 = Integer -> Maybe Integer
forall a. a -> Maybe a
Just (Integer -> Maybe Integer) -> Integer -> Maybe Integer
forall a b. (a -> b) -> a -> b
$ Rational -> Integer
forall a. Ratio a -> a
numerator Rational
q
toExactInteger _                                = Maybe Integer
forall a. Maybe a
Nothing

-- | Identifies whether an 'ExactPi' is an exact representation of a rational.

isExactRational :: ExactPi -> Bool
isExactRational :: ExactPi -> Bool
isExactRational (Exact 0 _) = Bool
True
isExactRational _           = Bool
False

-- | Converts an 'ExactPi' to an exact 'Rational' or 'Nothing'.

toExactRational :: ExactPi -> Maybe Rational
toExactRational :: ExactPi -> Maybe Rational
toExactRational (Exact 0 q :: Rational
q) = Rational -> Maybe Rational
forall a. a -> Maybe a
Just Rational
q
toExactRational _           = Maybe Rational
forall a. Maybe a
Nothing

-- | Converts an 'ExactPi' to a list of increasingly accurate rational approximations. Note

-- that 'Approximate' values are converted using the 'Real' instance for 'Double' into a

-- singleton list. Note that exact rationals are also converted into a singleton list.

--

-- Implementation is based on Chudnovsky's algorithm.

rationalApproximations :: ExactPi -> [Rational]
rationalApproximations :: ExactPi -> [Rational]
rationalApproximations (Approximate x :: forall a. Floating a => a
x) = [Double -> Rational
forall a. Real a => a -> Rational
toRational (Double
forall a. Floating a => a
x :: Double)]
rationalApproximations (Exact _ 0)     = [0]
rationalApproximations (Exact 0 q :: Rational
q)     = [Rational
q]
rationalApproximations (Exact z :: Integer
z q :: Rational
q)
  | Integer -> Bool
forall a. Integral a => a -> Bool
even Integer
z    = [Rational
q Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* 10005Rational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^Integer
k Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
cRational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^Integer
z     | Rational
c <- [Rational]
chudnovsky]
  | Bool
otherwise = [Rational
q Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* 10005Rational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^Integer
k Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
cRational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^Integer
z Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
r | Rational
c <- [Rational]
chudnovsky | Rational
r <- [Rational]
rootApproximation]
  where k :: Integer
k = Integer
z Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` 2

chudnovsky :: [Rational]
chudnovsky :: [Rational]
chudnovsky = [426880 Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Rational
s | Rational
s <- [Rational]
partials]
  where lk :: [Rational]
lk = (Rational -> Rational) -> Rational -> [Rational]
forall a. (a -> a) -> a -> [a]
iterate (Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+545140134) 13591409
        xk :: [Rational]
xk = (Rational -> Rational) -> Rational -> [Rational]
forall a. (a -> a) -> a -> [a]
iterate (Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
*(-262537412640768000)) 1
        kk :: [Integer]
kk = (Integer -> Integer) -> Integer -> [Integer]
forall a. (a -> a) -> a -> [a]
iterate (Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+12) 6
        mk :: [Rational]
mk = 1Rational -> [Rational] -> [Rational]
forall a. a -> [a] -> [a]
: [Rational
m Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* ((Integer
kInteger -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(3::Int) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- 16Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
k) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
nInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+1)Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^(3::Int)) | Rational
m <- [Rational]
mk | Integer
k <- [Integer]
kk | Integer
n <- [0..]]
        values :: [Rational]
values = [Rational
m Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
l Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Rational
x | Rational
m <- [Rational]
mk | Rational
l <- [Rational]
lk | Rational
x <- [Rational]
xk]
        partials :: [Rational]
partials = (Rational -> Rational -> Rational) -> [Rational] -> [Rational]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
(+) [Rational]
values

-- | Given an infinite converging sequence of rationals, find their limit.

-- Takes a comparison function to determine when convergence is close enough.

--

-- >>> getRationalLimit (==) (rationalApproximations (Exact 1 1)) :: Double

-- 3.141592653589793

getRationalLimit :: Fractional a => (a -> a -> Bool) -> [Rational] -> a
getRationalLimit :: (a -> a -> Bool) -> [Rational] -> a
getRationalLimit cmp :: a -> a -> Bool
cmp = [a] -> a
go ([a] -> a) -> ([Rational] -> [a]) -> [Rational] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rational -> a) -> [Rational] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Rational -> a
forall a. Fractional a => Rational -> a
fromRational
  where go :: [a] -> a
go (x :: a
x:y :: a
y:xs :: [a]
xs)
          | a -> a -> Bool
cmp a
x a
y   = a
y
          | Bool
otherwise = [a] -> a
go (a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs)
        go [x :: a
x] = a
x
        go _ = [Char] -> a
forall a. HasCallStack => [Char] -> a
error "did not converge"

-- | A sequence of convergents approximating @sqrt 10005@, intended to be zipped

-- with 'chudnovsky' in 'rationalApproximations'. Carefully chosen so that

-- the denominator does not increase too rapidly but approximations are still

-- appropriately precise.

--

-- Chudnovsky's series provides no more than 15 digits

-- per iteration, so the root approximation should not

-- have a more rapid rate of convergence.

rootApproximation :: [Rational]
rootApproximation :: [Rational]
rootApproximation = ([Rational] -> Rational) -> [[Rational]] -> [Rational]
forall a b. (a -> b) -> [a] -> [b]
map [Rational] -> Rational
forall a. [a] -> a
head ([[Rational]] -> [Rational])
-> ([Rational] -> [[Rational]]) -> [Rational] -> [Rational]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Rational] -> [Rational]) -> [Rational] -> [[Rational]]
forall a. (a -> a) -> a -> [a]
iterate (Int -> [Rational] -> [Rational]
forall a. Int -> [a] -> [a]
drop 4) ([Rational] -> [Rational]) -> [Rational] -> [Rational]
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer -> Integer -> Integer -> [Rational]
forall t. Integral t => t -> t -> t -> t -> t -> [Ratio t]
go 1 0 100 1 40
  where
    go :: t -> t -> t -> t -> t -> [Ratio t]
go pk' :: t
pk' qk' :: t
qk' pk :: t
pk qk :: t
qk a :: t
a = (t
pk t -> t -> Ratio t
forall a. Integral a => a -> a -> Ratio a
% t
qk)Ratio t -> [Ratio t] -> [Ratio t]
forall a. a -> [a] -> [a]
: t -> t -> t -> t -> t -> [Ratio t]
go t
pk t
qk (t
pk' t -> t -> t
forall a. Num a => a -> a -> a
+ t
at -> t -> t
forall a. Num a => a -> a -> a
*t
pk) (t
qk' t -> t -> t
forall a. Num a => a -> a -> a
+ t
at -> t -> t
forall a. Num a => a -> a -> a
*t
qk) (240t -> t -> t
forall a. Num a => a -> a -> a
-t
a)

instance Show ExactPi where
  show :: ExactPi -> [Char]
show (Exact z :: Integer
z q :: Rational
q) | Integer
z Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = "Exactly " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Rational -> [Char]
forall a. Show a => a -> [Char]
show Rational
q
                   | Integer
z Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== 1 = "Exactly pi * " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Rational -> [Char]
forall a. Show a => a -> [Char]
show Rational
q
                   | Bool
otherwise = "Exactly pi^" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Integer -> [Char]
forall a. Show a => a -> [Char]
show Integer
z [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ " * " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Rational -> [Char]
forall a. Show a => a -> [Char]
show Rational
q
  show (Approximate x :: forall a. Floating a => a
x) = "Approximately " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show (Double
forall a. Floating a => a
x :: Double)

instance Num ExactPi where
  fromInteger :: Integer -> ExactPi
fromInteger n :: Integer
n = Integer -> Rational -> ExactPi
Exact 0 (Integer -> Rational
forall a. Num a => Integer -> a
fromInteger Integer
n)
  (Exact z1 :: Integer
z1 q1 :: Rational
q1) * :: ExactPi -> ExactPi -> ExactPi
* (Exact z2 :: Integer
z2 q2 :: Rational
q2) = Integer -> Rational -> ExactPi
Exact (Integer
z1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
z2) (Rational
q1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
q2)
  (Exact _ 0) * _ = 0
  _ * (Exact _ 0) = 0
  x :: ExactPi
x * y :: ExactPi
y = (forall a. Floating a => a) -> ExactPi
Approximate ((forall a. Floating a => a) -> ExactPi)
-> (forall a. Floating a => a) -> ExactPi
forall a b. (a -> b) -> a -> b
$ ExactPi -> a
forall a. Floating a => ExactPi -> a
approximateValue ExactPi
x a -> a -> a
forall a. Num a => a -> a -> a
* ExactPi -> a
forall a. Floating a => ExactPi -> a
approximateValue ExactPi
y
  (Exact z1 :: Integer
z1 q1 :: Rational
q1) + :: ExactPi -> ExactPi -> ExactPi
+ (Exact z2 :: Integer
z2 q2 :: Rational
q2) | Integer
z1 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
z2 = Integer -> Rational -> ExactPi
Exact Integer
z1 (Rational
q1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational
q2) -- by distributive property

  x :: ExactPi
x + y :: ExactPi
y = (forall a. Floating a => a) -> ExactPi
Approximate ((forall a. Floating a => a) -> ExactPi)
-> (forall a. Floating a => a) -> ExactPi
forall a b. (a -> b) -> a -> b
$ ExactPi -> a
forall a. Floating a => ExactPi -> a
approximateValue ExactPi
x a -> a -> a
forall a. Num a => a -> a -> a
+ ExactPi -> a
forall a. Floating a => ExactPi -> a
approximateValue ExactPi
y
  abs :: ExactPi -> ExactPi
abs (Exact z :: Integer
z q :: Rational
q) = Integer -> Rational -> ExactPi
Exact Integer
z (Rational -> Rational
forall a. Num a => a -> a
abs Rational
q)
  abs (Approximate x :: forall a. Floating a => a
x) = (forall a. Floating a => a) -> ExactPi
Approximate ((forall a. Floating a => a) -> ExactPi)
-> (forall a. Floating a => a) -> ExactPi
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
abs a
forall a. Floating a => a
x
  signum :: ExactPi -> ExactPi
signum (Exact _ q :: Rational
q) = Integer -> Rational -> ExactPi
Exact 0 (Rational -> Rational
forall a. Num a => a -> a
signum Rational
q)
  signum (Approximate x :: forall a. Floating a => a
x) = (forall a. Floating a => a) -> ExactPi
Approximate ((forall a. Floating a => a) -> ExactPi)
-> (forall a. Floating a => a) -> ExactPi
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
signum a
forall a. Floating a => a
x -- we leave this tagged as approximate because we don't know "how" approximate the input was. a case could be made for exact answers here.

  negate :: ExactPi -> ExactPi
negate x :: ExactPi
x = (Integer -> Rational -> ExactPi
Exact 0 (-1)) ExactPi -> ExactPi -> ExactPi
forall a. Num a => a -> a -> a
* ExactPi
x

instance Fractional ExactPi where
  fromRational :: Rational -> ExactPi
fromRational = Integer -> Rational -> ExactPi
Exact 0
  recip :: ExactPi -> ExactPi
recip (Exact z :: Integer
z q :: Rational
q) = Integer -> Rational -> ExactPi
Exact (Integer -> Integer
forall a. Num a => a -> a
negate Integer
z) (Rational -> Rational
forall a. Fractional a => a -> a
recip Rational
q)
  recip (Approximate x :: forall a. Floating a => a
x) = (forall a. Floating a => a) -> ExactPi
Approximate (a -> a
forall a. Fractional a => a -> a
recip a
forall a. Floating a => a
x)

instance Floating ExactPi where
  pi :: ExactPi
pi = Integer -> Rational -> ExactPi
Exact 1 1
  exp :: ExactPi -> ExactPi
exp x :: ExactPi
x | ExactPi -> Bool
isExactZero ExactPi
x = 1
        | Bool
otherwise = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
exp ExactPi
x
  log :: ExactPi -> ExactPi
log (Exact 0 1) = 0
  log x :: ExactPi
x = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
log ExactPi
x
  -- It would be possible to give tighter bounds to the trig functions, preserving exactness for arguments that have an exactly representable result.

  sin :: ExactPi -> ExactPi
sin = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
sin
  cos :: ExactPi -> ExactPi
cos = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
cos
  tan :: ExactPi -> ExactPi
tan = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
tan
  asin :: ExactPi -> ExactPi
asin = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
asin
  atan :: ExactPi -> ExactPi
atan = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
atan
  acos :: ExactPi -> ExactPi
acos = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
acos
  sinh :: ExactPi -> ExactPi
sinh = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
sinh
  cosh :: ExactPi -> ExactPi
cosh = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
cosh
  tanh :: ExactPi -> ExactPi
tanh = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
tanh
  asinh :: ExactPi -> ExactPi
asinh = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
asinh
  acosh :: ExactPi -> ExactPi
acosh = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
acosh
  atanh :: ExactPi -> ExactPi
atanh = (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 forall a. Floating a => a -> a
atanh

approx1 :: (forall a.Floating a => a -> a) -> ExactPi -> ExactPi
approx1 :: (forall a. Floating a => a -> a) -> ExactPi -> ExactPi
approx1 f :: forall a. Floating a => a -> a
f x :: ExactPi
x = (forall a. Floating a => a) -> ExactPi
Approximate (a -> a
forall a. Floating a => a -> a
f (ExactPi -> a
forall a. Floating a => ExactPi -> a
approximateValue ExactPi
x))

-- | The multiplicative semigroup over 'Rational's augmented with multiples of 'pi'.

instance Semigroup ExactPi where
  <> :: ExactPi -> ExactPi -> ExactPi
(<>) = ExactPi -> ExactPi -> ExactPi
forall a. Monoid a => a -> a -> a
mappend

-- | The multiplicative monoid over 'Rational's augmented with multiples of 'pi'.

instance Monoid ExactPi where
  mempty :: ExactPi
mempty = 1
  mappend :: ExactPi -> ExactPi -> ExactPi
mappend = ExactPi -> ExactPi -> ExactPi
forall a. Num a => a -> a -> a
(*)