{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE CPP #-}
module AERN2.MP.Ball.PreludeOps
(
)
where
import MixedTypesNumPrelude
import qualified Prelude as P
import AERN2.Kleenean
import AERN2.MP.Dyadic (dyadic)
import AERN2.MP.Ball.Type
import AERN2.MP.Ball.Conversions ()
import AERN2.MP.Ball.Comparisons ()
import AERN2.MP.Ball.Field ()
import AERN2.MP.Ball.Elementary ()
instance P.Eq MPBall where
MPBall
a == :: MPBall -> MPBall -> Bool
== MPBall
b =
case MPBall
a MPBall -> MPBall -> EqCompareType MPBall MPBall
forall a b. HasEqAsymmetric a b => a -> b -> EqCompareType a b
== MPBall
b of
EqCompareType MPBall MPBall
CertainTrue -> Bool
True
EqCompareType MPBall MPBall
CertainFalse -> Bool
False
EqCompareType MPBall MPBall
_ ->
[Char] -> Bool
forall a. HasCallStack => [Char] -> a
error [Char]
"Failed to decide equality of MPBalls. If you switch to MixedTypesNumPrelude instead of Prelude, comparison of MPBalls returns Kleenean instead of Bool."
instance P.Ord MPBall where
compare :: MPBall -> MPBall -> Ordering
compare MPBall
a MPBall
b =
case (MPBall
a MPBall -> MPBall -> OrderCompareType MPBall MPBall
forall a b.
HasOrderAsymmetric a b =>
a -> b -> OrderCompareType a b
< MPBall
b, MPBall
a MPBall -> MPBall -> EqCompareType MPBall MPBall
forall a b. HasEqAsymmetric a b => a -> b -> EqCompareType a b
== MPBall
b, MPBall
a MPBall -> MPBall -> OrderCompareType MPBall MPBall
forall a b.
HasOrderAsymmetric a b =>
a -> b -> OrderCompareType a b
> MPBall
b) of
(Kleenean
CertainTrue, Kleenean
_, Kleenean
_) -> Ordering
P.LT
(Kleenean
_, Kleenean
CertainTrue, Kleenean
_) -> Ordering
P.EQ
(Kleenean
_, Kleenean
_, Kleenean
CertainTrue) -> Ordering
P.GT
(Kleenean, Kleenean, Kleenean)
_ ->
[Char] -> Ordering
forall a. HasCallStack => [Char] -> a
error [Char]
"Failed to decide order of MPBalls. If you switch to MixedTypesNumPrelude instead of Prelude, comparison of MPBalls returns Kleenean instead of Bool."
instance P.Num MPBall where
fromInteger :: Integer -> MPBall
fromInteger = Integer -> MPBall
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> t2
convertExactly
negate :: MPBall -> MPBall
negate = MPBall -> MPBall
forall t. CanNeg t => t -> NegType t
negate
+ :: MPBall -> MPBall -> MPBall
(+) = MPBall -> MPBall -> MPBall
forall t1 t2. CanAddAsymmetric t1 t2 => t1 -> t2 -> AddType t1 t2
(+)
* :: MPBall -> MPBall -> MPBall
(*) = MPBall -> MPBall -> MPBall
forall t1 t2. CanMulAsymmetric t1 t2 => t1 -> t2 -> MulType t1 t2
(*)
abs :: MPBall -> MPBall
abs = MPBall -> MPBall
forall t. CanAbs t => t -> AbsType t
abs
signum :: MPBall -> MPBall
signum = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"Prelude.signum not implemented for MPBall"
instance P.Fractional MPBall where
fromRational :: Rational -> MPBall
fromRational = Dyadic -> MPBall
forall t1 t2. ConvertibleExactly t1 t2 => t1 -> t2
convertExactly (Dyadic -> MPBall) -> (Rational -> Dyadic) -> Rational -> MPBall
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Dyadic
forall t. CanBeDyadic t => t -> Dyadic
dyadic
recip :: MPBall -> MPBall
recip = MPBall -> MPBall
forall t. CanRecip t => t -> DivType Integer t
recip
/ :: MPBall -> MPBall -> MPBall
(/) = MPBall -> MPBall -> MPBall
forall t1 t2. CanDiv t1 t2 => t1 -> t2 -> DivType t1 t2
(/)
instance P.Floating MPBall where
pi :: MPBall
pi = [Char] -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"There is no pi :: MPBall, use pi :: Real instead"
sqrt :: MPBall -> MPBall
sqrt = MPBall -> MPBall
forall t. CanSqrt t => t -> SqrtType t
sqrt
exp :: MPBall -> MPBall
exp = MPBall -> MPBall
forall t. CanExp t => t -> ExpType t
exp
sin :: MPBall -> MPBall
sin = MPBall -> MPBall
forall t. CanSinCos t => t -> SinCosType t
sin
cos :: MPBall -> MPBall
cos = MPBall -> MPBall
forall t. CanSinCos t => t -> SinCosType t
cos
log :: MPBall -> MPBall
log = MPBall -> MPBall
forall t. CanLog t => t -> LogType t
log
atan :: MPBall -> MPBall
atan = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: atan not implemented yet"
atanh :: MPBall -> MPBall
atanh = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: atanh not implemented yet"
asin :: MPBall -> MPBall
asin = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: asin not implemented yet"
acos :: MPBall -> MPBall
acos = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: acos not implemented yet"
sinh :: MPBall -> MPBall
sinh = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: sinh not implemented yet"
cosh :: MPBall -> MPBall
cosh = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: cosh not implemented yet"
asinh :: MPBall -> MPBall
asinh = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: asinh not implemented yet"
acosh :: MPBall -> MPBall
acosh = [Char] -> MPBall -> MPBall
forall a. HasCallStack => [Char] -> a
error [Char]
"MPBall: acosh not implemented yet"