aern2-mp-0.2.8.0: Multi-precision ball (interval) arithmetic
Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

AERN2.MP.WithCurrentPrec

Description

Type wrapper setting default precision.

Borrowed some tricks from https://github.com/ekmett/rounded/blob/master/src/Numeric/Rounded/Precision.hs

Synopsis

Documentation

newtype WithCurrentPrec p t Source #

Constructors

WithCurrentPrec 

Fields

Instances

Instances details
(HasLimits ix (CN MPBall -> CN MPBall), LimitType ix (CN MPBall -> CN MPBall) ~ (CN MPBall -> CN MPBall), KnownNat p) => HasLimits ix (CN (WithCurrentPrec p (CN MPBall))) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Limit

Associated Types

type LimitType ix (CN (WithCurrentPrec p (CN MPBall))) Source #

Methods

limit :: (ix -> CN (WithCurrentPrec p (CN MPBall))) -> LimitType ix (CN (WithCurrentPrec p (CN MPBall))) Source #

CanTakeErrors NumErrors t => CanTakeErrors NumErrors (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Type

CanDiv Int a => CanDiv Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Int (WithCurrentPrec p a) #

CanDiv Integer a => CanDiv Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Integer (WithCurrentPrec p a) #

CanDiv Rational a => CanDiv Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Rational (WithCurrentPrec p a) #

CanDiv Dyadic a => CanDiv Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Dyadic (WithCurrentPrec p a) #

(CanPow Int e, HasOrderCertainly e Integer, CanTestInteger e) => CanPow Int (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType Int (WithCurrentPrec p e) #

type PPowType Int (WithCurrentPrec p e) #

(CanPow Integer e, HasOrderCertainly e Integer, CanTestInteger e) => CanPow Integer (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType Integer (WithCurrentPrec p e) #

type PPowType Integer (WithCurrentPrec p e) #

(CanPow Rational e, HasOrderCertainly e Integer, CanTestInteger e) => CanPow Rational (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType Rational (WithCurrentPrec p e) #

type PPowType Rational (WithCurrentPrec p e) #

CanMulAsymmetric Int a => CanMulAsymmetric Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Int (WithCurrentPrec p a) #

Methods

mul :: Int -> WithCurrentPrec p a -> MulType Int (WithCurrentPrec p a) #

CanMulAsymmetric Integer a => CanMulAsymmetric Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Integer (WithCurrentPrec p a) #

CanMulAsymmetric Rational a => CanMulAsymmetric Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Rational (WithCurrentPrec p a) #

CanMulAsymmetric Dyadic a => CanMulAsymmetric Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Dyadic (WithCurrentPrec p a) #

CanAddAsymmetric Int a => CanAddAsymmetric Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Int (WithCurrentPrec p a) #

Methods

add :: Int -> WithCurrentPrec p a -> AddType Int (WithCurrentPrec p a) #

CanAddAsymmetric Integer a => CanAddAsymmetric Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Integer (WithCurrentPrec p a) #

CanAddAsymmetric Rational a => CanAddAsymmetric Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Rational (WithCurrentPrec p a) #

CanAddAsymmetric Dyadic a => CanAddAsymmetric Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Dyadic (WithCurrentPrec p a) #

CanSub Int a => CanSub Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Int (WithCurrentPrec p a) #

Methods

sub :: Int -> WithCurrentPrec p a -> SubType Int (WithCurrentPrec p a) #

CanSub Integer a => CanSub Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Integer (WithCurrentPrec p a) #

CanSub Rational a => CanSub Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Rational (WithCurrentPrec p a) #

CanSub Dyadic a => CanSub Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Dyadic (WithCurrentPrec p a) #

CanMinMaxAsymmetric Int a => CanMinMaxAsymmetric Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Int (WithCurrentPrec p a) #

CanMinMaxAsymmetric Integer a => CanMinMaxAsymmetric Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Integer (WithCurrentPrec p a) #

CanMinMaxAsymmetric Rational a => CanMinMaxAsymmetric Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Rational (WithCurrentPrec p a) #

CanMinMaxAsymmetric Dyadic a => CanMinMaxAsymmetric Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Dyadic (WithCurrentPrec p a) #

HasEqAsymmetric Int a => HasEqAsymmetric Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Int (WithCurrentPrec p a) #

HasEqAsymmetric Integer a => HasEqAsymmetric Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Integer (WithCurrentPrec p a) #

HasEqAsymmetric Rational a => HasEqAsymmetric Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Rational (WithCurrentPrec p a) #

HasEqAsymmetric Dyadic a => HasEqAsymmetric Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Dyadic (WithCurrentPrec p a) #

HasOrderAsymmetric Int a => HasOrderAsymmetric Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Int (WithCurrentPrec p a) #

HasOrderAsymmetric Integer a => HasOrderAsymmetric Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Integer (WithCurrentPrec p a) #

HasOrderAsymmetric Rational a => HasOrderAsymmetric Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Rational (WithCurrentPrec p a) #

HasOrderAsymmetric Dyadic a => HasOrderAsymmetric Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Dyadic (WithCurrentPrec p a) #

(ConvertibleWithPrecision t1 t2, KnownNat p) => ConvertibleExactly t1 (WithCurrentPrec p t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Type

(HasLimits ix (CN MPBall -> CN MPBall), LimitType ix (CN MPBall -> CN MPBall) ~ (CN MPBall -> CN MPBall), KnownNat p) => HasLimits ix (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Limit

Associated Types

type LimitType ix (WithCurrentPrec p (CN MPBall)) Source #

CanDiv (CN Int) a => CanDiv (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (CN Int) (WithCurrentPrec p a) #

Methods

divide :: CN Int -> WithCurrentPrec p a -> DivType (CN Int) (WithCurrentPrec p a) #

CanDiv (CN Integer) a => CanDiv (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (CN Integer) (WithCurrentPrec p a) #

CanDiv (CN Rational) a => CanDiv (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (CN Rational) (WithCurrentPrec p a) #

CanDiv (CN Dyadic) a => CanDiv (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (CN Dyadic) (WithCurrentPrec p a) #

CanMulAsymmetric (CN Int) a => CanMulAsymmetric (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (CN Int) (WithCurrentPrec p a) #

Methods

mul :: CN Int -> WithCurrentPrec p a -> MulType (CN Int) (WithCurrentPrec p a) #

CanMulAsymmetric (CN Integer) a => CanMulAsymmetric (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (CN Integer) (WithCurrentPrec p a) #

CanMulAsymmetric (CN Rational) a => CanMulAsymmetric (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (CN Rational) (WithCurrentPrec p a) #

CanMulAsymmetric (CN Dyadic) a => CanMulAsymmetric (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (CN Dyadic) (WithCurrentPrec p a) #

CanAddAsymmetric (CN Int) a => CanAddAsymmetric (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (CN Int) (WithCurrentPrec p a) #

Methods

add :: CN Int -> WithCurrentPrec p a -> AddType (CN Int) (WithCurrentPrec p a) #

CanAddAsymmetric (CN Integer) a => CanAddAsymmetric (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (CN Integer) (WithCurrentPrec p a) #

CanAddAsymmetric (CN Rational) a => CanAddAsymmetric (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (CN Rational) (WithCurrentPrec p a) #

CanAddAsymmetric (CN Dyadic) a => CanAddAsymmetric (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (CN Dyadic) (WithCurrentPrec p a) #

CanSub (CN Int) a => CanSub (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (CN Int) (WithCurrentPrec p a) #

Methods

sub :: CN Int -> WithCurrentPrec p a -> SubType (CN Int) (WithCurrentPrec p a) #

CanSub (CN Integer) a => CanSub (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (CN Integer) (WithCurrentPrec p a) #

CanSub (CN Rational) a => CanSub (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (CN Rational) (WithCurrentPrec p a) #

CanSub (CN Dyadic) a => CanSub (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (CN Dyadic) (WithCurrentPrec p a) #

CanMinMaxAsymmetric (CN Int) a => CanMinMaxAsymmetric (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (CN Int) (WithCurrentPrec p a) #

CanMinMaxAsymmetric (CN Integer) a => CanMinMaxAsymmetric (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (CN Integer) (WithCurrentPrec p a) #

CanMinMaxAsymmetric (CN Rational) a => CanMinMaxAsymmetric (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (CN Rational) (WithCurrentPrec p a) #

CanMinMaxAsymmetric (CN Dyadic) a => CanMinMaxAsymmetric (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (CN Dyadic) (WithCurrentPrec p a) #

HasEqAsymmetric (CN Int) a => HasEqAsymmetric (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (CN Int) (WithCurrentPrec p a) #

HasEqAsymmetric (CN Integer) a => HasEqAsymmetric (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (CN Integer) (WithCurrentPrec p a) #

HasEqAsymmetric (CN Rational) a => HasEqAsymmetric (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (CN Rational) (WithCurrentPrec p a) #

HasEqAsymmetric (CN Dyadic) a => HasEqAsymmetric (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (CN Dyadic) (WithCurrentPrec p a) #

HasOrderAsymmetric (CN Int) a => HasOrderAsymmetric (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (CN Int) (WithCurrentPrec p a) #

HasOrderAsymmetric (CN Integer) a => HasOrderAsymmetric (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (CN Integer) (WithCurrentPrec p a) #

HasOrderAsymmetric (CN Rational) a => HasOrderAsymmetric (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (CN Rational) (WithCurrentPrec p a) #

HasOrderAsymmetric (CN Dyadic) a => HasOrderAsymmetric (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (CN Dyadic) (WithCurrentPrec p a) #

Eq t => Eq (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

KnownNat p => Floating (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

Methods

pi :: WithCurrentPrec p (CN MPBall) #

exp :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

log :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

sqrt :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

(**) :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

logBase :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

sin :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

cos :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

tan :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

asin :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

acos :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

atan :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

sinh :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

cosh :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

tanh :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

asinh :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

acosh :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

atanh :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

log1p :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

expm1 :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

log1pexp :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

log1mexp :: WithCurrentPrec p (CN MPBall) -> WithCurrentPrec p (CN MPBall) #

(KnownNat p, Fractional t, ConvertibleWithPrecision Integer t, ConvertibleWithPrecision Rational t) => Fractional (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

(KnownNat p, Num t, ConvertibleWithPrecision Integer t) => Num (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

Ord t => Ord (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

Show t => Show (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Type

CanSqrt t => CanSqrt (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type SqrtType (WithCurrentPrec p t) #

CanExp t => CanExp (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type ExpType (WithCurrentPrec p t) #

CanLog t => CanLog (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type LogType (WithCurrentPrec p t) #

CanSinCos t => CanSinCos (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type SinCosType (WithCurrentPrec p t) #

KnownNat p => Field (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

KnownNat p => OrderedField (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

CanTestIsIntegerType t => CanTestIsIntegerType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Type

KnownNat p => Ring (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

KnownNat p => OrderedRing (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

CanAbs t => CanAbs (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type AbsType (WithCurrentPrec p t) #

CanNeg t => CanNeg (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type NegType (WithCurrentPrec p t) #

CanDiv a Dyadic => CanDiv (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) Dyadic #

CanDiv a Rational => CanDiv (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) Rational #

CanDiv a Int => CanDiv (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) Int #

CanDiv a Integer => CanDiv (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) Integer #

CanPow b Rational => CanPow (WithCurrentPrec p b) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec p b) Rational #

type PPowType (WithCurrentPrec p b) Rational #

CanPow b Int => CanPow (WithCurrentPrec p b) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec p b) Int #

type PPowType (WithCurrentPrec p b) Int #

CanPow b Integer => CanPow (WithCurrentPrec p b) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec p b) Integer #

type PPowType (WithCurrentPrec p b) Integer #

CanMulAsymmetric a Dyadic => CanMulAsymmetric (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) Dyadic #

CanMulAsymmetric a Rational => CanMulAsymmetric (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) Rational #

CanMulAsymmetric a Int => CanMulAsymmetric (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) Int #

Methods

mul :: WithCurrentPrec p a -> Int -> MulType (WithCurrentPrec p a) Int #

CanMulAsymmetric a Integer => CanMulAsymmetric (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) Integer #

CanAddAsymmetric a Dyadic => CanAddAsymmetric (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) Dyadic #

CanAddAsymmetric a Rational => CanAddAsymmetric (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) Rational #

CanAddAsymmetric a Int => CanAddAsymmetric (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) Int #

Methods

add :: WithCurrentPrec p a -> Int -> AddType (WithCurrentPrec p a) Int #

CanAddAsymmetric a Integer => CanAddAsymmetric (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) Integer #

CanSub a Dyadic => CanSub (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) Dyadic #

CanSub a Rational => CanSub (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) Rational #

CanSub a Int => CanSub (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) Int #

Methods

sub :: WithCurrentPrec p a -> Int -> SubType (WithCurrentPrec p a) Int #

CanSub a Integer => CanSub (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) Integer #

CanMinMaxAsymmetric a Dyadic => CanMinMaxAsymmetric (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) Dyadic #

CanMinMaxAsymmetric a Rational => CanMinMaxAsymmetric (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) Rational #

CanMinMaxAsymmetric a Int => CanMinMaxAsymmetric (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) Int #

CanMinMaxAsymmetric a Integer => CanMinMaxAsymmetric (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) Integer #

HasEqAsymmetric a Dyadic => HasEqAsymmetric (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) Dyadic #

HasEqAsymmetric a Rational => HasEqAsymmetric (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) Rational #

HasEqAsymmetric a Int => HasEqAsymmetric (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) Int #

HasEqAsymmetric a Integer => HasEqAsymmetric (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) Integer #

HasOrderAsymmetric a Dyadic => HasOrderAsymmetric (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) Dyadic #

HasOrderAsymmetric a Rational => HasOrderAsymmetric (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) Rational #

HasOrderAsymmetric a Int => HasOrderAsymmetric (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) Int #

HasOrderAsymmetric a Integer => HasOrderAsymmetric (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) Integer #

CanDiv a (CN Dyadic) => CanDiv (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) (CN Dyadic) #

CanDiv a (CN Rational) => CanDiv (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) (CN Rational) #

CanDiv a (CN Int) => CanDiv (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) (CN Int) #

Methods

divide :: WithCurrentPrec p a -> CN Int -> DivType (WithCurrentPrec p a) (CN Int) #

CanDiv a (CN Integer) => CanDiv (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p a) (CN Integer) #

CanMulAsymmetric a (CN Dyadic) => CanMulAsymmetric (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) (CN Dyadic) #

CanMulAsymmetric a (CN Rational) => CanMulAsymmetric (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) (CN Rational) #

CanMulAsymmetric a (CN Int) => CanMulAsymmetric (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) (CN Int) #

Methods

mul :: WithCurrentPrec p a -> CN Int -> MulType (WithCurrentPrec p a) (CN Int) #

CanMulAsymmetric a (CN Integer) => CanMulAsymmetric (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p a) (CN Integer) #

CanAddAsymmetric a (CN Dyadic) => CanAddAsymmetric (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) (CN Dyadic) #

CanAddAsymmetric a (CN Rational) => CanAddAsymmetric (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) (CN Rational) #

CanAddAsymmetric a (CN Int) => CanAddAsymmetric (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) (CN Int) #

Methods

add :: WithCurrentPrec p a -> CN Int -> AddType (WithCurrentPrec p a) (CN Int) #

CanAddAsymmetric a (CN Integer) => CanAddAsymmetric (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p a) (CN Integer) #

CanSub a (CN Dyadic) => CanSub (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) (CN Dyadic) #

CanSub a (CN Rational) => CanSub (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) (CN Rational) #

CanSub a (CN Int) => CanSub (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) (CN Int) #

Methods

sub :: WithCurrentPrec p a -> CN Int -> SubType (WithCurrentPrec p a) (CN Int) #

CanSub a (CN Integer) => CanSub (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p a) (CN Integer) #

CanMinMaxAsymmetric a (CN Dyadic) => CanMinMaxAsymmetric (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) (CN Dyadic) #

CanMinMaxAsymmetric a (CN Rational) => CanMinMaxAsymmetric (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) (CN Rational) #

CanMinMaxAsymmetric a (CN Int) => CanMinMaxAsymmetric (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) (CN Int) #

CanMinMaxAsymmetric a (CN Integer) => CanMinMaxAsymmetric (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p a) (CN Integer) #

HasEqAsymmetric a (CN Dyadic) => HasEqAsymmetric (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) (CN Dyadic) #

HasEqAsymmetric a (CN Rational) => HasEqAsymmetric (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) (CN Rational) #

HasEqAsymmetric a (CN Int) => HasEqAsymmetric (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) (CN Int) #

HasEqAsymmetric a (CN Integer) => HasEqAsymmetric (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p a) (CN Integer) #

HasOrderAsymmetric a (CN Dyadic) => HasOrderAsymmetric (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) (CN Dyadic) #

HasOrderAsymmetric a (CN Rational) => HasOrderAsymmetric (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) (CN Rational) #

HasOrderAsymmetric a (CN Int) => HasOrderAsymmetric (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) (CN Int) #

HasOrderAsymmetric a (CN Integer) => HasOrderAsymmetric (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p a) (CN Integer) #

(CanDiv t1 t2, p1 ~ p2) => CanDiv (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

Methods

divide :: WithCurrentPrec p1 t1 -> WithCurrentPrec p2 t2 -> DivType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(CanPow t1 t2, p1 ~ p2) => CanPow (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

type PPowType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(CanMulAsymmetric t1 t2, p1 ~ p2) => CanMulAsymmetric (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

Methods

mul :: WithCurrentPrec p1 t1 -> WithCurrentPrec p2 t2 -> MulType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(CanAddAsymmetric t1 t2, p1 ~ p2) => CanAddAsymmetric (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

Methods

add :: WithCurrentPrec p1 t1 -> WithCurrentPrec p2 t2 -> AddType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(CanSub t1 t2, p1 ~ p2) => CanSub (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

Methods

sub :: WithCurrentPrec p1 t1 -> WithCurrentPrec p2 t2 -> SubType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(CanMinMaxAsymmetric t1 t2, p1 ~ p2) => CanMinMaxAsymmetric (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(HasEqAsymmetric t1 t2, p1 ~ p2) => HasEqAsymmetric (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

(HasOrderAsymmetric t1 t2, p1 ~ p2) => HasOrderAsymmetric (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) #

type LimitType ix (CN (WithCurrentPrec p (CN MPBall))) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Limit

type DivType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type PPowType Int (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PPowType Integer (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PPowType Rational (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType Int (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType Integer (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType Rational (WithCurrentPrec p e) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type MulType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MinMaxType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType Int (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType Integer (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType Rational (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType Dyadic (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type LimitType ix (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Limit

type DivType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MinMaxType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (CN Int) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (CN Integer) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (CN Rational) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (CN Dyadic) (WithCurrentPrec p a) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type SqrtType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type ExpType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type LogType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type SinCosType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type AbsType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type NegType (WithCurrentPrec p t) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type PPowType (WithCurrentPrec p b) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PPowType (WithCurrentPrec p b) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PPowType (WithCurrentPrec p b) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType (WithCurrentPrec p b) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType (WithCurrentPrec p b) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType (WithCurrentPrec p b) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type MulType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MinMaxType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) Dyadic Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) Rational Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) Int Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) Integer Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type DivType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type DivType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MulType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MinMaxType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type MinMaxType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) (CN Dyadic) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) (CN Rational) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) (CN Int) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p a) (CN Integer) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type DivType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type PPowType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type PowType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type MulType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type AddType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type SubType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Field

type MinMaxType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type EqCompareType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type OrderCompareType (WithCurrentPrec p1 t1) (WithCurrentPrec p2 t2) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

runWithPrec :: Precision -> (forall p. KnownNat p => WithCurrentPrec p t) -> t Source #

Run a WithCurrentPrec computation with a specific precision.

newtype WithAnyPrec t Source #

An existential type wrapper for convenient conversions, eg using aern2-real:

_x :: KnownNat p => WithCurrentPrec (CN MPBall) p
_x = undefined

_r_x :: CReal
_r_x = creal $ WithAnyPrec _x

Constructors

WithAnyPrec (forall p. KnownNat p => WithCurrentPrec p t) 

Orphan instances

KnownNat p => Field (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

KnownNat p => OrderedField (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

KnownNat p => Ring (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

KnownNat p => OrderedRing (WithCurrentPrec p (CN MPBall)) Source # 
Instance details