aern2-mp-0.2.5.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 t p Source #

Constructors

WithCurrentPrec 

Fields

Instances

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

Defined in AERN2.MP.WithCurrentPrec.Type

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType Int (WithCurrentPrec e p) #

Methods

pow :: Int -> WithCurrentPrec e p -> PowType Int (WithCurrentPrec e p) #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType Integer (WithCurrentPrec e p) #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType Rational (WithCurrentPrec e p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Int (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Int (WithCurrentPrec a p) #

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Int (WithCurrentPrec a p) #

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Int (WithCurrentPrec a p) #

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Int (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Int (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Int (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Integer (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Rational (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType Dyadic (WithCurrentPrec a p) #

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

Defined in AERN2.MP.WithCurrentPrec.Limit

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

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

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

Methods

pi :: WithCurrentPrec (CN MPBall) p #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

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

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

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

Defined in AERN2.MP.WithCurrentPrec.PreludeInstances

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

Defined in AERN2.MP.WithCurrentPrec.Type

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type SqrtType (WithCurrentPrec t p) #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type ExpType (WithCurrentPrec t p) #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type LogType (WithCurrentPrec t p) #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type SinCosType (WithCurrentPrec t p) #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type AbsType (WithCurrentPrec t p) #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec b p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec b p) Int #

Methods

pow :: WithCurrentPrec b p -> Int -> PowType (WithCurrentPrec b p) Int #

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

type PowType (WithCurrentPrec b p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec a p) Int #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type DivType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec a p) Int #

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type MulType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec a p) Int #

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type AddType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec a p) Int #

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

type SubType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec a p) Int #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type MinMaxType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec a p) Int #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type EqCompareType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec a p) Dyadic #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec a p) Rational #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec a p) Int #

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

type OrderCompareType (WithCurrentPrec a p) Integer #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

Associated Types

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

Methods

pow :: WithCurrentPrec t1 p1 -> WithCurrentPrec t2 p2 -> PowType (WithCurrentPrec t1 p1) (WithCurrentPrec t2 p2) #

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Field

Associated Types

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

Methods

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

Associated Types

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

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Limit

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

type SqrtType (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type ExpType (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type LogType (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type SinCosType (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Elementary

type AbsType (WithCurrentPrec t p) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Elementary

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Field

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Comparisons

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

class HasCurrentPrecision p where Source #

Methods

getCurrentPrecision :: proxy p -> Precision Source #

Instances

Instances details
KnownNat n => HasCurrentPrecision (n :: Nat) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Type

Methods

getCurrentPrecision :: proxy n -> Precision Source #

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 t p)