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

AERN2.MP.Ball

Description

Arbitrary precision ball arithmetic

Synopsis

Auxiliary types

module AERN2.Norm

data ErrorBound Source #

A non-negative Double value to serve as an error bound. Arithmetic is rounded towards +infinity.

Instances

Instances details
Arbitrary ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

HasAccuracy ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Generic ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type Rep ErrorBound :: Type -> Type #

Show ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

NFData ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Methods

rnf :: ErrorBound -> () #

Eq ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Ord ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Convertible MPBall ErrorBound Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Convertible MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Convertible Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Convertible Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Convertible Int ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

CanAddAsymmetric ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type AddType ErrorBound ErrorBound #

CanAddAsymmetric ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type AddType ErrorBound MPFloat #

CanAddAsymmetric MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type AddType MPFloat ErrorBound #

CanDiv ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type DivType ErrorBound Integer #

HasEqAsymmetric ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type EqCompareType ErrorBound Rational #

HasEqAsymmetric ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type EqCompareType ErrorBound Integer #

HasEqAsymmetric ErrorBound Int Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type EqCompareType ErrorBound Int #

HasEqAsymmetric Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type EqCompareType Rational ErrorBound #

HasEqAsymmetric Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type EqCompareType Integer ErrorBound #

HasEqAsymmetric Int ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type EqCompareType Int ErrorBound #

ConvertibleExactly ErrorBound MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleExactly ErrorBound Dyadic Source # 
Instance details

Defined in AERN2.MP.ErrorBound

ConvertibleExactly ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

ConvertibleExactly ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

ConvertibleExactly ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

CanMinMaxAsymmetric ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MinMaxType ErrorBound ErrorBound #

CanMulAsymmetric ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType ErrorBound ErrorBound #

CanMulAsymmetric ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType ErrorBound MPFloat #

CanMulAsymmetric ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType ErrorBound Rational #

CanMulAsymmetric ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType ErrorBound Integer #

CanMulAsymmetric MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType MPFloat ErrorBound #

CanMulAsymmetric Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType Rational ErrorBound #

CanMulAsymmetric Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type MulType Integer ErrorBound #

HasOrderAsymmetric ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

HasOrderAsymmetric ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType ErrorBound MPFloat #

HasOrderAsymmetric ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType ErrorBound Rational #

HasOrderAsymmetric ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType ErrorBound Integer #

HasOrderAsymmetric ErrorBound Int Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType ErrorBound Int #

HasOrderAsymmetric MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType MPFloat ErrorBound #

HasOrderAsymmetric Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType Rational ErrorBound #

HasOrderAsymmetric Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType Integer ErrorBound #

HasOrderAsymmetric Int ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

Associated Types

type OrderCompareType Int ErrorBound #

type Rep ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type Rep ErrorBound = D1 ('MetaData "ErrorBound" "AERN2.MP.ErrorBound" "aern2-mp-0.2.15.1-6xeEefByTke3KEoNxGQRX3" 'True) (C1 ('MetaCons "ErrorBound" 'PrefixI 'True) (S1 ('MetaSel ('Just "er2mp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPFloat)))
type AddType ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type AddType ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type AddType MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type DivType ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type EqCompareType ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type EqCompareType ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type EqCompareType ErrorBound Int Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type EqCompareType Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type EqCompareType Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type EqCompareType Int ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MinMaxType ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type MulType Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType ErrorBound ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType ErrorBound MPFloat Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType ErrorBound Rational Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType ErrorBound Integer Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType ErrorBound Int Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType MPFloat ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType Rational ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType Integer ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

type OrderCompareType Int ErrorBound Source # 
Instance details

Defined in AERN2.MP.ErrorBound

The Ball type

data MPBall Source #

Constructors

MPBall 

Instances

Instances details
Arbitrary MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Tests

HasAccuracy MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

HasApproximate MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type Approximate MPBall Source #

ShowWithAccuracy MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

IsBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type CentreType MPBall Source #

IsInterval MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type IntervalEndpoint MPBall Source #

CanSetPrecision MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

HasPrecision MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

HasNorm MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanNormalize MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Floating MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Generic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type Rep MPBall :: Type -> Type #

Methods

from :: MPBall -> Rep MPBall x #

to :: Rep MPBall x -> MPBall #

Num MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Fractional MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Show MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

NFData MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

rnf :: MPBall -> () #

Eq MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Methods

(==) :: MPBall -> MPBall -> Bool #

(/=) :: MPBall -> MPBall -> Bool #

Ord MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

CanNeg MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type NegType MPBall #

CanExp MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type ExpType MPBall #

Methods

exp :: MPBall -> ExpType MPBall #

CanLog MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type LogType MPBall #

Methods

log :: MPBall -> LogType MPBall #

CanSinCos MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type SinCosType MPBall #

CanSqrt MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type SqrtType MPBall #

Methods

sqrt :: MPBall -> SqrtType MPBall #

CanTestFinite MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestInteger MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

CanTestNaN MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

isNaN :: MPBall -> Bool #

CanTestValid MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

isValid :: MPBall -> Bool #

CanTestZero MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

CanAbs MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type AbsType MPBall #

Methods

abs :: MPBall -> AbsType MPBall #

CanTestPosNeg MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

CanTestIsIntegerType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

isIntegerType :: MPBall -> Bool #

CanGiveUpIfVeryInaccurate MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

OrderedCertainlyRing MPBall Source # 
Instance details

Defined in AERN2.MP.Ball

OrderedRing MPBall Source # 
Instance details

Defined in AERN2.MP.Ball

Ring MPBall Source # 
Instance details

Defined in AERN2.MP.Ball

HasIntegerBounds MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

CanIntersectAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type IntersectionType MPBall MPBall Source #

CanBeErrorBound t => CanPlusMinus MPBall t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType MPBall t Source #

CanTestContains MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

contains :: MPBall -> MPBall -> Bool Source #

CanTestContains MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

contains :: MPBall -> Dyadic -> Bool Source #

CanTestContains MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestContains MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestContains MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

contains :: MPBall -> Int -> Bool Source #

CanUnionAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type UnionType MPBall MPBall Source #

ConvertibleWithPrecision Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Convertible MPBall ErrorBound Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

CanAddAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall MPBall #

CanAddAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Dyadic #

CanAddAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Rational #

CanAddAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Integer #

CanAddAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Int #

Methods

add :: MPBall -> Int -> AddType MPBall Int #

CanAddAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Dyadic MPBall #

CanAddAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Rational MPBall #

CanAddAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Integer MPBall #

CanAddAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Int MPBall #

Methods

add :: Int -> MPBall -> AddType Int MPBall #

CanSub MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall MPBall #

CanSub MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Dyadic #

CanSub MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Rational #

CanSub MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Integer #

CanSub MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Int #

Methods

sub :: MPBall -> Int -> SubType MPBall Int #

CanSub Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Dyadic MPBall #

CanSub Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Rational MPBall #

CanSub Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Integer MPBall #

CanSub Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Int MPBall #

Methods

sub :: Int -> MPBall -> SubType Int MPBall #

CanDiv MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall MPBall #

CanDiv MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Dyadic #

CanDiv MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Rational #

CanDiv MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Integer #

CanDiv MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Int #

Methods

divide :: MPBall -> Int -> DivType MPBall Int #

CanDiv Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Dyadic MPBall #

CanDiv Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Rational MPBall #

CanDiv Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Integer MPBall #

CanDiv Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Int MPBall #

Methods

divide :: Int -> MPBall -> DivType Int MPBall #

HasEqAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall MPBall #

HasEqAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Dyadic #

HasEqAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Rational #

HasEqAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Integer #

HasEqAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Int #

HasEqAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Dyadic MPBall #

HasEqAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Rational MPBall #

HasEqAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Integer MPBall #

HasEqAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Int MPBall #

ConvertibleExactly MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleExactly Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleExactly ErrorBound MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleExactly Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleExactly Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

CanMinMaxAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall MPBall #

CanMinMaxAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Dyadic #

CanMinMaxAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Rational #

CanMinMaxAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Integer #

CanMinMaxAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Int #

CanMinMaxAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Dyadic MPBall #

CanMinMaxAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Rational MPBall #

CanMinMaxAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Integer MPBall #

CanMinMaxAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Int MPBall #

CanMulAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall MPBall #

CanMulAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Dyadic #

CanMulAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Rational #

CanMulAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Integer #

CanMulAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Int #

Methods

mul :: MPBall -> Int -> MulType MPBall Int #

CanMulAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Dyadic MPBall #

CanMulAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Rational MPBall #

CanMulAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Integer MPBall #

CanMulAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Int MPBall #

Methods

mul :: Int -> MPBall -> MulType Int MPBall #

HasOrderAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall MPBall #

HasOrderAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Dyadic #

HasOrderAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Rational #

HasOrderAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Integer #

HasOrderAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Int #

HasOrderAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Dyadic MPBall #

HasOrderAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Rational MPBall #

HasOrderAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Integer MPBall #

HasOrderAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Int MPBall #

CanPow MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType MPBall MPBall #

type PPowType MPBall MPBall #

CanPow MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType MPBall Dyadic #

type PPowType MPBall Dyadic #

CanPow MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType MPBall Rational #

type PPowType MPBall Rational #

CanPow MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type PowType MPBall Integer #

type PPowType MPBall Integer #

CanPow MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type PowType MPBall Int #

type PPowType MPBall Int #

CanPow Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType Rational MPBall #

type PPowType Rational MPBall #

CanPow Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType Integer MPBall #

type PPowType Integer MPBall #

CanPow Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType Int MPBall #

type PPowType Int MPBall #

CanDivIMod MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivIType MPBall MPBall #

type ModType MPBall MPBall #

(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 #

CanAddAsymmetric MPBall b => CanAddAsymmetric MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall (CN b) #

Methods

add :: MPBall -> CN b -> AddType MPBall (CN b) #

CanSub MPBall b => CanSub MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall (CN b) #

Methods

sub :: MPBall -> CN b -> SubType MPBall (CN b) #

(CanDiv MPBall b, CanTestZero b) => CanDiv MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall (CN b) #

Methods

divide :: MPBall -> CN b -> DivType MPBall (CN b) #

CanMulAsymmetric MPBall b => CanMulAsymmetric MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall (CN b) #

Methods

mul :: MPBall -> CN b -> MulType MPBall (CN b) #

CanPow MPBall b => CanPow MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type PowType MPBall (CN b) #

type PPowType MPBall (CN b) #

Methods

pow :: MPBall -> CN b -> PowType MPBall (CN b) #

ppow :: MPBall -> CN b -> PPowType MPBall (CN b) #

HasLimits Rational (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

Associated Types

type LimitType Rational (CN MPBall -> CN MPBall) Source #

HasLimits Integer (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

Associated Types

type LimitType Integer (CN MPBall -> CN MPBall) Source #

HasLimits Int (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

Associated Types

type LimitType Int (CN MPBall -> CN MPBall) Source #

(CanIntersectAsymmetric MPBall b, CanBeErrors es) => CanIntersectAsymmetric MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type IntersectionType MPBall (CollectErrors es b) Source #

(CanUnionAsymmetric MPBall b, CanBeErrors es) => CanUnionAsymmetric MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type UnionType MPBall (CollectErrors es b) Source #

(HasEqAsymmetric MPBall b, IsBool (EqCompareType MPBall b), CanTestCertainly (EqCompareType MPBall b), CanBeErrors es) => HasEqAsymmetric MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall (CollectErrors es b) #

(CanMinMaxAsymmetric MPBall b, CanBeErrors es) => CanMinMaxAsymmetric MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall (CollectErrors es b) #

(HasOrderAsymmetric MPBall b, IsBool (OrderCompareType MPBall b), CanTestCertainly (OrderCompareType MPBall b), CanBeErrors es) => HasOrderAsymmetric MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall (CollectErrors es b) #

(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 #

OrderedCertainlyRing (CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball

OrderedRing (CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball

Ring (CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball

CanBeErrorBound t => CanPlusMinus (CN MPBall) t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType (CN MPBall) t Source #

CanAddAsymmetric a MPBall => CanAddAsymmetric (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType (CN a) MPBall #

Methods

add :: CN a -> MPBall -> AddType (CN a) MPBall #

CanSub a MPBall => CanSub (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType (CN a) MPBall #

Methods

sub :: CN a -> MPBall -> SubType (CN a) MPBall #

CanDiv a MPBall => CanDiv (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType (CN a) MPBall #

Methods

divide :: CN a -> MPBall -> DivType (CN a) MPBall #

CanMulAsymmetric a MPBall => CanMulAsymmetric (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType (CN a) MPBall #

Methods

mul :: CN a -> MPBall -> MulType (CN a) MPBall #

CanPow a MPBall => CanPow (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type PowType (CN a) MPBall #

type PPowType (CN a) MPBall #

Methods

pow :: CN a -> MPBall -> PowType (CN a) MPBall #

ppow :: CN a -> MPBall -> PPowType (CN a) MPBall #

(CanIntersectAsymmetric a MPBall, CanBeErrors es) => CanIntersectAsymmetric (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type IntersectionType (CollectErrors es a) MPBall Source #

(CanUnionAsymmetric a MPBall, CanBeErrors es) => CanUnionAsymmetric (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type UnionType (CollectErrors es a) MPBall Source #

ConvertibleWithPrecision (Rational, Rational) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

(HasEqAsymmetric a MPBall, IsBool (EqCompareType a MPBall), CanTestCertainly (EqCompareType a MPBall), CanBeErrors es) => HasEqAsymmetric (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType (CollectErrors es a) MPBall #

(ConvertibleExactly c Dyadic, ConvertibleExactly e Dyadic, Show c, Show e, Typeable c, Typeable e) => ConvertibleExactly (c, e) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

(CanMinMaxAsymmetric a MPBall, CanBeErrors es) => CanMinMaxAsymmetric (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType (CollectErrors es a) MPBall #

(HasOrderAsymmetric a MPBall, IsBool (OrderCompareType a MPBall), CanTestCertainly (OrderCompareType a MPBall), CanBeErrors es) => HasOrderAsymmetric (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType (CollectErrors es a) MPBall #

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 => 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

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

Defined in AERN2.MP.WithCurrentPrec

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

Defined in AERN2.MP.WithCurrentPrec

type Approximate MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type CentreType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type IntervalEndpoint MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type Rep MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type Rep MPBall = D1 ('MetaData "MPBall" "AERN2.MP.Ball.Type" "aern2-mp-0.2.15.1-6xeEefByTke3KEoNxGQRX3" 'False) (C1 ('MetaCons "MPBall" 'PrefixI 'True) (S1 ('MetaSel ('Just "ball_value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPFloat) :*: S1 ('MetaSel ('Just "ball_error") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrorBound)))
type NegType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type ExpType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type LogType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type SinCosType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type SqrtType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type AbsType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type IntersectionType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type PlusMinusType MPBall t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

type UnionType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type AddType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type EqCompareType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MulType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type OrderCompareType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type PPowType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PPowType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PPowType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PPowType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PPowType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PPowType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PPowType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PPowType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type DivIType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type ModType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

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

Defined in AERN2.MP.WithCurrentPrec.Limit

type AddType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType MPBall (CN b) = CN (AddType MPBall b)
type SubType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall (CN b) = CN (SubType MPBall b)
type DivType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall (CN b) = CN (DivType MPBall b)
type MulType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall (CN b) = CN (MulType MPBall b)
type PPowType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType MPBall (CN b) = CN (PowType MPBall b)
type LimitType Rational (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

type LimitType Integer (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

type LimitType Int (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

type IntersectionType MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type UnionType MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

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

Defined in AERN2.MP.WithCurrentPrec.Limit

type PlusMinusType (CN MPBall) t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

type AddType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType (CN a) MPBall = CN (AddType a MPBall)
type SubType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType (CN a) MPBall = CN (SubType a MPBall)
type DivType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType (CN a) MPBall = CN (DivType a MPBall)
type MulType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType (CN a) MPBall = CN (MulType a MPBall)
type PPowType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType (CN a) MPBall = CN (PowType a MPBall)
type IntersectionType (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type UnionType (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType (CollectErrors es a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

reducePrecionIfInaccurate :: MPBall -> MPBall Source #

Reduce the precision of the ball centre if the accuracy of the ball is poor.

More precisely, reduce the precision of the centre so that the ulp is approximately (radius / 1024), unless the ulp is already lower than this.

giveUpIfVeryInaccurate :: CanGiveUpIfVeryInaccurate t => CN t -> CN t #

If the value contains so little information that it is seen as useless, drop the value and add an error indicating what happened.

Ball operations (see also instances)

Helpers for constructing ball functions

byEndpointsMP :: (MPFloat -> MPFloat -> MPFloat) -> MPBall -> MPBall -> MPBall Source #

Compute an MPBall function from *exact* MPFloat operations on interval endpoints. This works only for *non-decreasing* operations, eg addition, min, max.

fromApproxWithLipschitz Source #

Arguments

:: (MPFloat -> BoundsCEDU MPFloat)

fCEDU: a version of f on MPFloat returning rigorous bounds

-> MPFloat

lip a Lipschitz constant for f, lip > 0

-> MPBall -> MPBall

f on MPBall rounding *outwards*

Computes a real function f from correctly rounded MPFR-approximations and a number lip which is a Lipschitz constant for f, i.e. |f(x) - f(y)| <= lip * |x - y| for all x,y.

Orphan instances

OrderedCertainlyRing MPBall Source # 
Instance details

OrderedRing MPBall Source # 
Instance details

Ring MPBall Source # 
Instance details

OrderedCertainlyRing (CN MPBall) Source # 
Instance details

OrderedRing (CN MPBall) Source # 
Instance details

Ring (CN MPBall) Source # 
Instance details