{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module NumHask.Data.Rational
( Ratio (..),
Rational,
ToRatio (..),
FromRatio (..),
FromRational (..),
reduce,
gcd,
)
where
import Data.Bool (bool)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Word (Word, Word16, Word32, Word64, Word8)
import GHC.Float
import GHC.Natural (Natural (..))
import qualified GHC.Real
import NumHask.Algebra.Additive
import NumHask.Algebra.Field
import NumHask.Algebra.Lattice
import NumHask.Algebra.Metric
import NumHask.Algebra.Multiplicative
import NumHask.Algebra.Ring
import NumHask.Data.Integral
import Prelude (Eq (..), Int, Integer, Ord (..), Ordering (..), Rational, (.))
import qualified Prelude as P
data Ratio a = !a :% !a deriving (Int -> Ratio a -> ShowS
forall a. Show a => Int -> Ratio a -> ShowS
forall a. Show a => [Ratio a] -> ShowS
forall a. Show a => Ratio a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ratio a] -> ShowS
$cshowList :: forall a. Show a => [Ratio a] -> ShowS
show :: Ratio a -> String
$cshow :: forall a. Show a => Ratio a -> String
showsPrec :: Int -> Ratio a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Ratio a -> ShowS
P.Show)
instance (P.Eq a, Subtractive a, EndoBased a, Absolute a, Integral a) => P.Eq (Ratio a) where
a :: Ratio a
a@(a
xa :% a
ya) == :: Ratio a -> Ratio a -> Bool
== b :: Ratio a
b@(a
xb :% a
yb)
| forall a. (Eq a, Additive a) => Ratio a -> Bool
isRNaN Ratio a
a Bool -> Bool -> Bool
P.|| forall a. (Eq a, Additive a) => Ratio a -> Bool
isRNaN Ratio a
b = Bool
P.False
| a
xa forall a. Eq a => a -> a -> Bool
== forall a. Additive a => a
zero Bool -> Bool -> Bool
P.&& a
xb forall a. Eq a => a -> a -> Bool
== forall a. Additive a => a
zero = Bool
P.True
| a
xa forall a. Eq a => a -> a -> Bool
== forall a. Additive a => a
zero Bool -> Bool -> Bool
P.|| a
xb forall a. Eq a => a -> a -> Bool
== forall a. Additive a => a
zero = Bool
P.False
| Bool
P.otherwise =
let (a
xa' :% a
ya', a
xb' :% a
yb') = (forall a.
(Eq a, Subtractive a, EndoBased a, Integral a) =>
a -> a -> Ratio a
reduce a
xa a
ya, forall a.
(Eq a, Subtractive a, EndoBased a, Integral a) =>
a -> a -> Ratio a
reduce a
xb a
yb)
in (a
xa' forall a. Eq a => a -> a -> Bool
P.== a
xb') Bool -> Bool -> Bool
P.&& (a
ya' forall a. Eq a => a -> a -> Bool
P.== a
yb')
isRNaN :: (P.Eq a, Additive a) => Ratio a -> P.Bool
isRNaN :: forall a. (Eq a, Additive a) => Ratio a -> Bool
isRNaN (a
x :% a
y)
| a
x forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero Bool -> Bool -> Bool
P.&& a
y forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = Bool
P.True
| Bool
P.otherwise = Bool
P.False
instance (P.Ord a, Integral a, EndoBased a, Subtractive a) => P.Ord (Ratio a) where
(a
x :% a
y) <= :: Ratio a -> Ratio a -> Bool
<= (a
x' :% a
y') = a
x forall a. Multiplicative a => a -> a -> a
* a
y' forall a. Ord a => a -> a -> Bool
P.<= a
x' forall a. Multiplicative a => a -> a -> a
* a
y
(a
x :% a
y) < :: Ratio a -> Ratio a -> Bool
< (a
x' :% a
y') = a
x forall a. Multiplicative a => a -> a -> a
* a
y' forall a. Ord a => a -> a -> Bool
P.< a
x' forall a. Multiplicative a => a -> a -> a
* a
y
instance (P.Ord a, EndoBased a, Integral a, Ring a) => Additive (Ratio a) where
(a
x :% a
y) + :: Ratio a -> Ratio a -> Ratio a
+ (a
x' :% a
y')
| a
y forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero Bool -> Bool -> Bool
P.&& a
y' forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = forall a. a -> a -> Bool -> a
bool forall a. Multiplicative a => a
one (forall a. Subtractive a => a -> a
negate forall a. Multiplicative a => a
one) (a
x forall a. Additive a => a -> a -> a
+ a
x' forall a. Ord a => a -> a -> Bool
P.< forall a. Additive a => a
zero) forall a. a -> a -> Ratio a
:% forall a. Additive a => a
zero
| a
y forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = a
x forall a. a -> a -> Ratio a
:% a
y
| a
y' forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = a
x' forall a. a -> a -> Ratio a
:% a
y'
| Bool
P.otherwise = forall a.
(Eq a, Subtractive a, EndoBased a, Integral a) =>
a -> a -> Ratio a
reduce ((a
x forall a. Multiplicative a => a -> a -> a
* a
y') forall a. Additive a => a -> a -> a
+ (a
x' forall a. Multiplicative a => a -> a -> a
* a
y)) (a
y forall a. Multiplicative a => a -> a -> a
* a
y')
zero :: Ratio a
zero = forall a. Additive a => a
zero forall a. a -> a -> Ratio a
:% forall a. Multiplicative a => a
one
instance (P.Ord a, EndoBased a, Integral a, Ring a) => Subtractive (Ratio a) where
negate :: Ratio a -> Ratio a
negate (a
x :% a
y) = forall a. Subtractive a => a -> a
negate a
x forall a. a -> a -> Ratio a
:% a
y
instance (P.Ord a, EndoBased a, Integral a, Ring a) => Multiplicative (Ratio a) where
(a
x :% a
y) * :: Ratio a -> Ratio a -> Ratio a
* (a
x' :% a
y') = forall a.
(Eq a, Subtractive a, EndoBased a, Integral a) =>
a -> a -> Ratio a
reduce (a
x forall a. Multiplicative a => a -> a -> a
* a
x') (a
y forall a. Multiplicative a => a -> a -> a
* a
y')
one :: Ratio a
one = forall a. Multiplicative a => a
one forall a. a -> a -> Ratio a
:% forall a. Multiplicative a => a
one
instance
(P.Ord a, EndoBased a, Integral a, Ring a) =>
Divisive (Ratio a)
where
recip :: Ratio a -> Ratio a
recip (a
x :% a
y)
| forall a. Sign a => a -> a
signum a
x forall a. Eq a => a -> a -> Bool
P.== forall a. Subtractive a => a -> a
negate forall a. Multiplicative a => a
one = forall a. Subtractive a => a -> a
negate a
y forall a. a -> a -> Ratio a
:% forall a. Subtractive a => a -> a
negate a
x
| Bool
P.otherwise = a
y forall a. a -> a -> Ratio a
:% a
x
instance (P.Ord a, EndoBased a, Absolute a, ToInt a, Integral a, Ring a) => QuotientField (Ratio a) where
type Whole (Ratio a) = Int
properFraction :: Ratio a -> (Whole (Ratio a), Ratio a)
properFraction (a
n :% a
d) = let (a
w, a
r) = forall a. Integral a => a -> a -> (a, a)
quotRem a
n a
d in (forall a b. ToIntegral a b => a -> b
toIntegral a
w, a
r forall a. a -> a -> Ratio a
:% a
d)
instance (P.Ord a, EndoBased a, Integral a, Ring a) => Basis (Ratio a) where
type Mag (Ratio a) = Ratio a
type Base (Ratio a) = Ratio a
basis :: Ratio a -> Base (Ratio a)
basis (a
n :% a
_) =
case forall a. Ord a => a -> a -> Ordering
compare a
n forall a. Additive a => a
zero of
Ordering
EQ -> forall a. Additive a => a
zero
Ordering
GT -> forall a. Multiplicative a => a
one
Ordering
LT -> forall a. Subtractive a => a -> a
negate forall a. Multiplicative a => a
one
magnitude :: Ratio a -> Mag (Ratio a)
magnitude (a
n :% a
d) = forall a. Absolute a => a -> a
abs a
n forall a. a -> a -> Ratio a
:% forall a. Absolute a => a -> a
abs a
d
instance (P.Ord a, Integral a, EndoBased a, Subtractive a) => JoinSemiLattice (Ratio a) where
\/ :: Ratio a -> Ratio a -> Ratio a
(\/) = forall a. Ord a => a -> a -> a
P.min
instance (P.Ord a, Integral a, EndoBased a, Subtractive a) => MeetSemiLattice (Ratio a) where
/\ :: Ratio a -> Ratio a -> Ratio a
(/\) = forall a. Ord a => a -> a -> a
P.max
instance (P.Ord a, EndoBased a, Integral a, Ring a, MeetSemiLattice a) => Epsilon (Ratio a)
instance (FromIntegral a b, Multiplicative a) => FromIntegral (Ratio a) b where
fromIntegral :: b -> Ratio a
fromIntegral b
x = forall a b. FromIntegral a b => b -> a
fromIntegral b
x forall a. a -> a -> Ratio a
:% forall a. Multiplicative a => a
one
class ToRatio a b where
toRatio :: a -> Ratio b
instance ToRatio Double Integer where
toRatio :: Double -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Float Integer where
toRatio :: Float -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Rational Integer where
toRatio :: Rational -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational
instance ToRatio (Ratio Integer) Integer where
toRatio :: Ratio Integer -> Ratio Integer
toRatio = forall a. a -> a
P.id
instance ToRatio Int Integer where
toRatio :: Int -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Integer Integer where
toRatio :: Integer -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Natural Integer where
toRatio :: Natural -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Int8 Integer where
toRatio :: Int8 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Int16 Integer where
toRatio :: Int16 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Int32 Integer where
toRatio :: Int32 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Int64 Integer where
toRatio :: Int64 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Word Integer where
toRatio :: Word -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Word8 Integer where
toRatio :: Word8 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Word16 Integer where
toRatio :: Word16 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Word32 Integer where
toRatio :: Word32 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
instance ToRatio Word64 Integer where
toRatio :: Word64 -> Ratio Integer
toRatio = Rational -> Ratio Integer
fromBaseRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
P.toRational
class FromRatio a b where
fromRatio :: Ratio b -> a
fromBaseRational :: P.Rational -> Ratio Integer
fromBaseRational :: Rational -> Ratio Integer
fromBaseRational (Integer
n GHC.Real.:% Integer
d) = Integer
n forall a. a -> a -> Ratio a
:% Integer
d
instance FromRatio Double Integer where
fromRatio :: Ratio Integer -> Double
fromRatio (Integer
n :% Integer
d) = Integer -> Integer -> Double
rationalToDouble Integer
n Integer
d
instance FromRatio Float Integer where
fromRatio :: Ratio Integer -> Float
fromRatio (Integer
n :% Integer
d) = Integer -> Integer -> Float
rationalToFloat Integer
n Integer
d
instance FromRatio Rational Integer where
fromRatio :: Ratio Integer -> Rational
fromRatio (Integer
n :% Integer
d) = Integer
n forall a. Integral a => a -> a -> Ratio a
GHC.Real.% Integer
d
class FromRational a where
fromRational :: P.Rational -> a
instance FromRational Double where
fromRational :: Rational -> Double
fromRational (Integer
n GHC.Real.:% Integer
d) = Integer -> Integer -> Double
rationalToDouble Integer
n Integer
d
instance FromRational Float where
fromRational :: Rational -> Float
fromRational (Integer
n GHC.Real.:% Integer
d) = Integer -> Integer -> Float
rationalToFloat Integer
n Integer
d
instance FromRational (Ratio Integer) where
fromRational :: Rational -> Ratio Integer
fromRational (Integer
n GHC.Real.:% Integer
d) = Integer
n forall a. a -> a -> Ratio a
:% Integer
d
reduce ::
(P.Eq a, Subtractive a, EndoBased a, Integral a) => a -> a -> Ratio a
reduce :: forall a.
(Eq a, Subtractive a, EndoBased a, Integral a) =>
a -> a -> Ratio a
reduce a
x a
y
| a
x forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero Bool -> Bool -> Bool
P.&& a
y forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = forall a. Additive a => a
zero forall a. a -> a -> Ratio a
:% forall a. Additive a => a
zero
| a
z forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = forall a. Multiplicative a => a
one forall a. a -> a -> Ratio a
:% forall a. Additive a => a
zero
| Bool
P.otherwise = (a
x forall a. Integral a => a -> a -> a
`quot` a
z) forall {a}.
(Base a ~ a, Eq a, Basis a, Subtractive a, Multiplicative a) =>
a -> a -> Ratio a
% (a
y forall a. Integral a => a -> a -> a
`quot` a
z)
where
z :: a
z = forall a. (Eq a, EndoBased a, Integral a) => a -> a -> a
gcd a
x a
y
a
n % :: a -> a -> Ratio a
% a
d
| forall a. Sign a => a -> a
signum a
d forall a. Eq a => a -> a -> Bool
P.== forall a. Subtractive a => a -> a
negate forall a. Multiplicative a => a
one = forall a. Subtractive a => a -> a
negate a
n forall a. a -> a -> Ratio a
:% forall a. Subtractive a => a -> a
negate a
d
| Bool
P.otherwise = a
n forall a. a -> a -> Ratio a
:% a
d
gcd :: (P.Eq a, EndoBased a, Integral a) => a -> a -> a
gcd :: forall a. (Eq a, EndoBased a, Integral a) => a -> a -> a
gcd a
x a
y = forall {t}. (Eq t, Integral t) => t -> t -> t
gcd' (forall a. Absolute a => a -> a
abs a
x) (forall a. Absolute a => a -> a
abs a
y)
where
gcd' :: t -> t -> t
gcd' t
a t
b
| t
b forall a. Eq a => a -> a -> Bool
P.== forall a. Additive a => a
zero = t
a
| Bool
P.otherwise = t -> t -> t
gcd' t
b (t
a forall a. Integral a => a -> a -> a
`rem` t
b)