{-# LANGUAGE MultiParamTypeClasses,FunctionalDependencies, FlexibleInstances, PatternSynonyms, ViewPatterns #-}
module Math.NumberTheory.Canon.Simple (
SimpleCanon(..), SC,
toSimpleCanon, toSC, toSimpleCanonViaUserFunc,
fromSimpleCanon, fromSC,
CanonConv,
scGCD, scLCM,
scLog, scLogDouble,
scNegative, scPositive,
scToInteger, scToI,
RationalSimpleCanon(..), RC,
toRationalSimpleCanon, toRC, toRationalSimpleCanonViaUserFunc,
fromRationalSimpleCanon, fromRC,
rcNegative, rcPositive,
getNumer, getDenom, getNumerDenom,
getNumerAsRC, getDenomAsRC, getNumerDenomAsRCs,
rcLog, rcLogDouble,
(>^), (<^), (%),
SimpleCanonRoot, SimpleCanonExpnt
)
where
import GHC.Real (Ratio(..))
import Math.NumberTheory.Canon.Internals
import Math.NumberTheory.Canon.Additive
import Math.NumberTheory.Canon.AurifCyclo (crCycloInitMap)
newtype SimpleCanon = MakeSC CR_ deriving (Eq)
toSimpleCanonViaUserFunc :: CR_ -> (Integer -> Bool) -> SimpleCanon
toSimpleCanonViaUserFunc c f | crValidIntegralViaUserFunc c f == False = error $ invalidError
| otherwise = MakeSC c
where invalidError = "toSimpleCanonViaUserFunc: Invalid integral canonical rep passed to constructor: " ++ (show c)
fromSimpleCanon, fromSC :: SimpleCanon -> CR_
fromSimpleCanon (MakeSC i) = i
fromSC = fromSimpleCanon
type SC = SimpleCanon
instance Show SimpleCanon where
show c = crShow $ fromSC c
instance Enum SimpleCanon where
toEnum n = toSimpleCanon $ fst $ crFromI $ fromIntegral n
fromEnum c = fromIntegral $ crToI $ fromSC c
instance Ord SimpleCanon where
compare x y = crCmp (fromSC x) (fromSC y)
instance Real SimpleCanon where
toRational c = scToI c :% 1
instance Integral SimpleCanon where
toInteger c = scToI c
quotRem n m = (MakeSC n', MakeSC m')
where (n', m') = fst $ crQuotRem (fromSC n) (fromSC m) crCycloInitMap
mod n m = MakeSC $ fst $ crMod (fromSC n) (fromSC m)
instance Fractional SimpleCanon where
fromRational (n :% d) | m == 0 = MakeSC $ fst $ crFromI q
| otherwise = error "Modulus not zero. Use Rational SimpleCanons for non-Integers."
where (q, m) = quotRem n d
(/) x y = MakeSC $ crDivStrict (fromSC x) (fromSC y)
instance Num SimpleCanon where
fromInteger n = MakeSC $ fst $ crFromI n
x + y = MakeSC $ fst $ crAdd (fromSC x) (fromSC y) crCycloInitMap
x - y = MakeSC $ fst $ crSubtract (fromSC x) (fromSC y) crCycloInitMap
x * y = MakeSC $ crMult (fromSC x) (fromSC y)
negate x = MakeSC $ crNegate $ fromSC x
abs x = MakeSC $ crAbs $ fromSC x
signum x = MakeSC $ crSignum $ fromSC x
scToInteger, scToI :: SimpleCanon -> Integer
scToI c = crToI $ fromSC c
scToInteger = scToI
scGCD, scLCM :: SimpleCanon -> SimpleCanon -> SimpleCanon
scGCD x y = MakeSC $ crGCD (fromSC x) (fromSC y)
scLCM x y = MakeSC $ crLCM (fromSC x) (fromSC y)
scNegative, scPositive :: SimpleCanon -> Bool
scNegative c = crNegative $ fromSC c
scPositive c = crPositive $ fromSC c
scLog :: SimpleCanon -> Rational
scLog x = crLog $ fromSC x
scLogDouble :: SimpleCanon -> Double
scLogDouble x = crLogDouble $ fromSC x
newtype RationalSimpleCanon = MakeRC CR_ deriving (Eq)
toRationalSimpleCanonViaUserFunc :: CR_ -> (Integer -> Bool) -> RationalSimpleCanon
toRationalSimpleCanonViaUserFunc c f | crValidRationalViaUserFunc c f == False = error $ invalidError
| otherwise = MakeRC c
where invalidError =
"toRationalSimpleCanonViaUserFunc: Invalid rational canonical rep passed to constructor: "
++ (show c) ++ " (user predicate supplied)"
fromRationalSimpleCanon, fromRC :: RationalSimpleCanon -> CR_
fromRC (MakeRC i) = i
fromRationalSimpleCanon = fromRC
type RC = RationalSimpleCanon
instance Show RationalSimpleCanon where
show rc = crShowRational $ fromRC rc
instance Enum RationalSimpleCanon where
toEnum n = toRC $ fst $ crFromI $ fromIntegral n
fromEnum c = fromIntegral $ toInteger c
instance Integral RationalSimpleCanon where
toInteger rc = crToI $ fromRC rc
quotRem n m | crIntegral $ fromRC n = (MakeRC n', MakeRC m')
| otherwise = error "Can't perform 'quotRem' on non-integral RationalSimpleCanon"
where (n', m') = fst $ crQuotRem (fromRC n) (fromRC m) crCycloInitMap
mod n m | crIntegral $ fromRC n = MakeRC $ fst $ crMod (fromRC n) (fromRC m)
| otherwise = error "Can't perform 'mod' on non-integral RationalSimpleCanon"
instance Fractional RationalSimpleCanon where
fromRational (n :% d) = MakeRC $ crDivRational (fst $ crFromI n) (fst $ crFromI d)
(/) x y = MakeRC $ crDivRational (fromRC x) (fromRC y)
instance Ord RationalSimpleCanon where
compare x y = crCmp (fromRC x) (fromRC y)
instance Real RationalSimpleCanon where
toRational rc = crToRational $ fromRC rc
instance Num RationalSimpleCanon where
fromInteger n = MakeRC $ fst $ crFromI n
x + y = MakeRC $ fst $ crAddR (fromRC x) (fromRC y) crCycloInitMap
x - y = MakeRC $ fst $ crSubtractR (fromRC x) (fromRC y) crCycloInitMap
x * y = MakeRC $ crMult (fromRC x) (fromRC y)
negate x = MakeRC $ crNegate $ fromRC x
abs x = MakeRC $ crAbs $ fromRC x
signum x = MakeRC $ crSignum $ fromRC x
rcLog :: RationalSimpleCanon -> Rational
rcLog c = crLog $ fromRC c
rcLogDouble :: RationalSimpleCanon -> Double
rcLogDouble c = crLogDouble $ fromRC c
getNumerAsRC :: RationalSimpleCanon -> RationalSimpleCanon
getNumerAsRC c = MakeRC $ crNumer $ fromRC c
getDenomAsRC :: RationalSimpleCanon -> RationalSimpleCanon
getDenomAsRC c = MakeRC $ crDenom $ fromRC c
getNumer, getDenom :: RationalSimpleCanon -> SimpleCanon
getNumer c = MakeSC $ crNumer $ fromRC c
getDenom c = MakeSC $ crDenom $ fromRC c
getNumerDenom :: RationalSimpleCanon -> (SimpleCanon, SimpleCanon)
getNumerDenom c = (MakeSC n, MakeSC d)
where (n, d) = crSplit $ fromRC c
getNumerDenomAsRCs :: RationalSimpleCanon -> (RationalSimpleCanon, RationalSimpleCanon)
getNumerDenomAsRCs c = (MakeRC n, MakeRC d)
where (n, d) = crSplit $ fromRC c
rcNegative, rcPositive :: RationalSimpleCanon -> Bool
rcNegative x = crNegative $ fromRC x
rcPositive x = crPositive $ fromRC x
infixl 7 %
(%) :: (Integral a) => a -> a -> a
n % m = mod n m
infixr 9 <^
class SimpleCanonExpnt a b c | a b -> c where
(<^) :: a -> b -> c
instance SimpleCanonExpnt Integer Integer SimpleCanon where
p <^ e = MakeSC $ crExp (fst $ crFromI p) e False
instance SimpleCanonExpnt SimpleCanon Integer SimpleCanon where
p <^ e = MakeSC $ crExp (fromSC p) e False
instance SimpleCanonExpnt RationalSimpleCanon Integer RationalSimpleCanon where
p <^ e = MakeRC $ crExp (fromRC p) e True
instance SimpleCanonExpnt RationalSimpleCanon SimpleCanon RationalSimpleCanon where
p <^ e = MakeRC $ crExp (fromRC p) (crToI $ fromSC e) True
infixr 9 >^
class SimpleCanonRoot a b c | a b -> c where
(>^) :: a -> b -> c
instance SimpleCanonRoot SimpleCanon SimpleCanon SimpleCanon where
r >^ n = MakeSC $ crRoot (fromSC n) (toInteger r)
instance SimpleCanonRoot Integer Integer SimpleCanon where
r >^ n = MakeSC $ crRoot (fst $ crFromI n) r
instance SimpleCanonRoot Integer SimpleCanon SimpleCanon where
r >^ n = MakeSC $ crRoot (fromSC n) r
instance SimpleCanonRoot SimpleCanon Integer SimpleCanon where
r >^ n = MakeSC $ crRoot (fst $ crFromI n) (toInteger r)
instance SimpleCanonRoot Integer RationalSimpleCanon RationalSimpleCanon where
r >^ n = MakeRC $ crRoot (fromRC n) r
toSimpleCanon :: (CanonConv a) => a -> SimpleCanon
toSimpleCanon = toSC
toRationalSimpleCanon :: (CanonConv a) => a -> RationalSimpleCanon
toRationalSimpleCanon = toRC
class CanonConv c where
toSC :: c -> SimpleCanon
toRC :: c -> RationalSimpleCanon
instance CanonConv SimpleCanon where
toSC c = c
toRC c = MakeRC $ fromSC c
instance CanonConv CR_ where
toSC cr | crValidIntegral cr = MakeSC cr
| otherwise = error invalidError
where invalidError = "Invalid integral canonical rep passed to constructor: " ++ (show cr)
toRC cr | crValidRational cr = MakeRC cr
| otherwise = error invalidRepRatioError
where invalidRepRatioError = "toRC: Invalid canonical rep passed to constructor: " ++ (show cr)
instance CanonConv RationalSimpleCanon where
toSC rc | crValidIntegral frc = MakeSC frc
| otherwise = error invalidError
where frc = fromRC rc
invalidError = "Invalid integral canonical rep passed to constructor: " ++ (show rc)
toRC rc = rc