{-# LANGUAGE NoImplicitPrelude #-}
module Number.Positional.Check where
import qualified Number.Positional as Pos
import qualified Number.Complex as Complex
import qualified Algebra.RealTranscendental as RealTrans
import qualified Algebra.Transcendental as Trans
import qualified Algebra.Algebraic as Algebraic
import qualified Algebra.RealField as RealField
import qualified Algebra.Field as Field
import qualified Algebra.RealRing as RealRing
import qualified Algebra.Absolute as Absolute
import qualified Algebra.Ring as Ring
import qualified Algebra.Additive as Additive
import qualified Algebra.ZeroTestable as ZeroTestable
import qualified Algebra.EqualityDecision as EqDec
import qualified Algebra.OrderDecision as OrdDec
import qualified Prelude as P98
import NumericPrelude.Base as P
import NumericPrelude.Numeric as NP
data T = Cons {base :: Pos.Basis, exponent :: Int, mantissa :: Pos.Mantissa}
deriving (Show)
compress :: T -> T
compress = lift1 Pos.compress
carry :: T -> T
carry (Cons b ex xs) =
let ys = scanr (\x (c,_) -> divMod (x+c) b) (0,undefined) xs
digits = map snd (init ys)
in prependDigit (fst (head ys)) (Cons b ex digits)
prependDigit :: Pos.Digit -> T -> T
prependDigit 0 x = x
prependDigit x (Cons b ex xs) =
Cons b (ex+1) (x:xs)
lift0 :: (Pos.Basis -> Pos.T) -> T
lift0 op =
uncurry (Cons defltBase) (op defltBase)
lift1 :: (Pos.Basis -> Pos.T -> Pos.T) -> T -> T
lift1 op (Cons xb xe xm) =
uncurry (Cons xb) (op xb (xe, xm))
lift2 :: (Pos.Basis -> Pos.T -> Pos.T -> Pos.T) -> T -> T -> T
lift2 op (Cons xb xe xm) (Cons yb ye ym) =
let b = commonBasis xb yb
in uncurry (Cons b) (op b (xe, xm) (ye, ym))
commonBasis :: Pos.Basis -> Pos.Basis -> Pos.Basis
commonBasis xb yb =
if xb == yb
then xb
else error "Number.Positional: bases differ"
fromBaseInteger :: Pos.Basis -> Integer -> T
fromBaseInteger b n =
uncurry (Cons b) (Pos.fromBaseInteger b n)
fromBaseRational :: Pos.Basis -> Rational -> T
fromBaseRational b r =
uncurry (Cons b) (Pos.fromBaseRational b r)
defltBaseRoot :: Pos.Basis
defltBaseRoot = 10
defltBaseExp :: Pos.Exponent
defltBaseExp = 3
defltBase :: Pos.Basis
defltBase = ringPower defltBaseExp defltBaseRoot
defltShow :: T -> String
defltShow (Cons xb xe xm) =
if xb == defltBase
then Pos.showBasis defltBaseRoot defltBaseExp (xe,xm)
else error "defltShow: wrong base"
instance Additive.C T where
zero = fromBaseInteger defltBase 0
(+) = lift2 Pos.add
(-) = lift2 Pos.sub
negate = lift1 Pos.neg
instance Ring.C T where
one = fromBaseInteger defltBase 1
fromInteger n = fromBaseInteger defltBase n
(*) = lift2 Pos.mul
instance Field.C T where
(/) = lift2 Pos.divide
recip = lift1 Pos.reciprocal
instance Algebraic.C T where
sqrt = lift1 Pos.sqrtNewton
root n = lift1 (flip Pos.root n)
x ^/ y = lift1 (flip Pos.power y) x
instance Trans.C T where
pi = lift0 Pos.piConst
exp = lift1 Pos.exp
log = lift1 Pos.ln
sin = lift1 (\b -> snd . Pos.cosSin b)
cos = lift1 (\b -> fst . Pos.cosSin b)
tan = lift1 Pos.tan
atan = lift1 Pos.arctan
instance EqDec.C T where
x==?y = lift2 (\b -> Pos.ifLazy b (x==y))
instance OrdDec.C T where
x<=?y = lift2 (\b -> Pos.ifLazy b (x<=y))
instance ZeroTestable.C T where
isZero (Cons xb xe xm) =
Pos.cmp xb (xe,xm) Pos.zero == EQ
instance Eq T where
(Cons xb xe xm) == (Cons yb ye ym) =
Pos.cmp (commonBasis xb yb) (xe,xm) (ye,ym) == EQ
instance Ord T where
compare (Cons xb xe xm) (Cons yb ye ym) =
Pos.cmp (commonBasis xb yb) (xe,xm) (ye,ym)
instance Absolute.C T where
abs = lift1 (const Pos.absolute)
signum = Absolute.signumOrd
instance RealRing.C T where
splitFraction (Cons xb xe xm) =
let (int, frac) = Pos.toFixedPoint xb (xe,xm)
in (fromInteger int, Cons xb (-1) frac)
instance RealField.C T where
instance RealTrans.C T where
atan2 = lift2 (curry . Pos.angle)
instance Complex.Power T where
power = Complex.defltPow
instance P98.Num T where
fromInteger = fromBaseInteger defltBase
negate = negate
(+) = (+)
(*) = (*)
abs = abs
signum = signum
instance P98.Fractional T where
fromRational = fromBaseRational defltBase . fromRational
(/) = (/)