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

AERN2.MP.Ball.Type

Description

Arbitrary precision dyadic balls

Synopsis

Auxiliary types

The Ball type

data MPBall Source #

Constructors

MPBall 

Instances

Instances details
Eq MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Methods

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

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

Floating MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Fractional MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Num MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Ord MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.PreludeOps

Show MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

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 #

Arbitrary MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Tests

NFData MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

rnf :: MPBall -> () #

CanSqrt MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type SqrtType MPBall #

Methods

sqrt :: MPBall -> SqrtType 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 #

CanTestIsIntegerType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

isIntegerType :: MPBall -> Bool #

Ring MPBall Source # 
Instance details

Defined in AERN2.MP.Ball

OrderedRing MPBall Source # 
Instance details

Defined in AERN2.MP.Ball

OrderedCertainlyRing MPBall Source # 
Instance details

Defined in AERN2.MP.Ball

HasIntegerBounds MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

CanAbs MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type AbsType MPBall #

Methods

abs :: MPBall -> AbsType MPBall #

CanGiveUpIfVeryInaccurate MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestNaN MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

isNaN :: MPBall -> Bool #

CanTestFinite MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestInteger MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

CanTestZero MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

CanTestPosNeg MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

CanNeg MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type NegType MPBall #

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

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

HasAccuracy MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

IsInterval MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type IntervalEndpoint MPBall Source #

IsBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Associated Types

type CentreType MPBall Source #

CanNormalize MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

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 #

CanDiv Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Integer MPBall #

CanDiv Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Rational MPBall #

CanDiv Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType Dyadic MPBall #

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 MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Integer #

CanDiv MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Rational #

CanDiv MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall Dyadic #

CanDiv MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivType MPBall MPBall #

CanPow Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType Int MPBall #

type PPowType Int MPBall #

CanPow Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType Integer MPBall #

type PPowType Integer MPBall #

CanPow Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType Rational MPBall #

type PPowType Rational MPBall #

CanPow MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type PowType MPBall Int #

type PPowType MPBall Int #

CanPow MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type PowType MPBall Integer #

type PPowType MPBall Integer #

CanPow MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType MPBall Rational #

type PPowType MPBall Rational #

CanPow MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType MPBall Dyadic #

type PPowType MPBall Dyadic #

CanPow MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

Associated Types

type PowType MPBall MPBall #

type PPowType MPBall MPBall #

CanDivIMod MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type DivIType MPBall MPBall #

type ModType MPBall 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 #

CanMulAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Integer MPBall #

CanMulAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Rational MPBall #

CanMulAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType Dyadic MPBall #

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 MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Integer #

CanMulAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Rational #

CanMulAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall Dyadic #

CanMulAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type MulType MPBall 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 #

CanAddAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Integer MPBall #

CanAddAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Rational MPBall #

CanAddAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType Dyadic MPBall #

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 MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Integer #

CanAddAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Rational #

CanAddAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall Dyadic #

CanAddAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type AddType MPBall 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 #

CanSub Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Integer MPBall #

CanSub Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Rational MPBall #

CanSub Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType Dyadic MPBall #

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 MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Integer #

CanSub MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Rational #

CanSub MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall Dyadic #

CanSub MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

Associated Types

type SubType MPBall MPBall #

CanMinMaxAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Int MPBall #

CanMinMaxAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Integer MPBall #

CanMinMaxAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Rational MPBall #

CanMinMaxAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType Dyadic MPBall #

CanMinMaxAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Int #

CanMinMaxAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Integer #

CanMinMaxAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Rational #

CanMinMaxAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall Dyadic #

CanMinMaxAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type MinMaxType MPBall MPBall #

HasEqAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Int MPBall #

HasEqAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Integer MPBall #

HasEqAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Rational MPBall #

HasEqAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType Dyadic MPBall #

HasEqAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Int #

HasEqAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Integer #

HasEqAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Rational #

HasEqAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall Dyadic #

HasEqAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type EqCompareType MPBall MPBall #

HasOrderAsymmetric Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Int MPBall #

HasOrderAsymmetric Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Integer MPBall #

HasOrderAsymmetric Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Rational MPBall #

HasOrderAsymmetric Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType Dyadic MPBall #

HasOrderAsymmetric MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Int #

HasOrderAsymmetric MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Integer #

HasOrderAsymmetric MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Rational #

HasOrderAsymmetric MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall Dyadic #

HasOrderAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type OrderCompareType MPBall MPBall #

ConvertibleExactly Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleExactly Integer 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 MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Convertible MPBall ErrorBound Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Int MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Integer MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

ConvertibleWithPrecision Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

CanUnionAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type UnionType MPBall MPBall Source #

CanIntersectAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type IntersectionType MPBall MPBall Source #

CanTestContains MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

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

CanTestContains MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestContains MPBall Rational Source # 
Instance details

Defined in AERN2.MP.Ball.Type

CanTestContains MPBall Dyadic Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

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

CanTestContains MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

Methods

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

CanBeErrorBound t => CanPlusMinus MPBall t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType MPBall t Source #

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

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

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

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

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

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

(HasEqAsymmetric MPBall b, IsBool (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) #

(HasOrderAsymmetric MPBall b, IsBool (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 Int (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

Associated Types

type LimitType Int (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 Rational (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

Associated Types

type LimitType Rational (CN MPBall -> CN MPBall) 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 #

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

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

Ring (CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball

OrderedRing (CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball

OrderedCertainlyRing (CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball

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 #

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 #

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 #

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 #

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

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType (CN MPBall) t Source #

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

(HasEqAsymmetric a MPBall, IsBool (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 #

(HasOrderAsymmetric a MPBall, IsBool (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 #

(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

ConvertibleWithPrecision (Rational, Rational) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

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

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

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 => Ring (WithCurrentPrec p (CN MPBall)) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec

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

Defined in AERN2.MP.WithCurrentPrec

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.8.0-7EdW5MADRpY8tQ5ayaur95" '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 SqrtType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

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 AbsType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type NegType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type Approximate MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type IntervalEndpoint MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type CentreType MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Type

type DivType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PPowType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PPowType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PPowType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PPowType MPBall Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type PowType MPBall Int Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType MPBall Integer Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type PowType MPBall Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Elementary

type ModType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivIType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type AddType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type SubType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MinMaxType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type MinMaxType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type EqCompareType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType Int 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 Rational MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType Dyadic MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type OrderCompareType MPBall Int 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 Rational 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 MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type UnionType MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

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 DivType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType MPBall (CN b) = CN (DivType 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 MulType MPBall (CN b) Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType MPBall (CN b) = CN (MulType MPBall b)
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 LimitType ix (CN (WithCurrentPrec p (CN MPBall))) Source # 
Instance details

Defined in AERN2.MP.WithCurrentPrec.Limit

type MinMaxType 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 OrderCompareType MPBall (CollectErrors es b) Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

type LimitType Int (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 Rational (CN MPBall -> CN MPBall) Source # 
Instance details

Defined in AERN2.MP.Ball.Limit

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

Defined in AERN2.MP.Ball.Comparisons

type IntersectionType 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 DivType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type DivType (CN a) MPBall = CN (DivType 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 MulType (CN a) MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Field

type MulType (CN a) MPBall = CN (MulType a MPBall)
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 PlusMinusType (CN MPBall) t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

type MinMaxType (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 OrderCompareType (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 IntersectionType (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.

Ball construction/extraction functions