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

AERN2.MP.Enclosure

Description

Enclosure classes and operations.

Synopsis

Documentation

class IsBall t where Source #

Minimal complete definition

centre, centreAsBallAndRadius, updateRadius

Associated Types

type CentreType t Source #

Methods

centre :: t -> CentreType t Source #

centreAsBallAndRadius :: t -> (t, ErrorBound) Source #

centreAsBall :: t -> t Source #

radius :: t -> ErrorBound Source #

updateRadius :: (ErrorBound -> ErrorBound) -> t -> t Source #

makeExactCentre :: t -> t Source #

When the radius of the ball is implicitly contributed to by imprecision in the centre (eg if the centre is a polynomial with inexact coefficients), move all that imprecision to the explicit radius, making the centre exact. This may lose some information, but as a ball is equivalent to the original. For MPBall this function is pointless because it is equivalent to the identity.

ballFunctionUsingLipschitz Source #

Arguments

:: (IsBall t, HasEqCertainly t t) 
=> (t -> t)

fThin: a version of f that works well on thin balls

-> (t -> ErrorBound)

fLip: a Lipschitz function of f over large balls

-> t -> t

f on *large* balls

Computes a ball function f on the centre and updating the error bound using a Lipschitz constant.

intervalFunctionByEndpoints Source #

Arguments

:: (IsInterval t, CanMinMaxSameType (IntervalEndpoint t), HasEqCertainly t t) 
=> (t -> t)

fThin: a version of f that works well on thin intervals

-> t -> t

f on *large* intervals

Computes a *monotone* ball function f on intervals using the interval endpoints.

intervalFunctionByEndpointsUpDown Source #

Arguments

:: IsInterval t 
=> (IntervalEndpoint t -> IntervalEndpoint t)

fDown: a version of f working on endpoints, rounded down

-> (IntervalEndpoint t -> IntervalEndpoint t)

fUp: a version of f working on endpoints, rounded up

-> t -> t

f on intervals rounding *outwards*

Computes a *monotone* ball function f on intervals using the interval endpoints.

class CanPlusMinus t1 t2 where Source #

Associated Types

type PlusMinusType t1 t2 Source #

type PlusMinusType t1 t2 = t1

Methods

plusMinus :: t1 -> t2 -> PlusMinusType t1 t2 Source #

Operator for constructing or enlarging enclosures such as balls or intervals

Instances

Instances details
CanBeErrorBound t => CanPlusMinus Int t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType Int t Source #

Methods

plusMinus :: Int -> t -> PlusMinusType Int t Source #

CanBeErrorBound t => CanPlusMinus Integer t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType Integer t Source #

CanBeErrorBound t => CanPlusMinus Rational t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType Rational t Source #

CanBeErrorBound t => CanPlusMinus MPFloat t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType MPFloat t Source #

CanBeErrorBound t => CanPlusMinus Dyadic t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType Dyadic t Source #

CanBeErrorBound t => CanPlusMinus MPBall t Source # 
Instance details

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType MPBall t Source #

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

Defined in AERN2.MP.Ball.Conversions

Associated Types

type PlusMinusType (CN MPBall) t Source #

(+-) :: CanPlusMinus t1 t2 => t1 -> t2 -> PlusMinusType t1 t2 infixl 6 Source #

Operator for constructing or enlarging enclosures such as balls or intervals

class CanTestContains dom e where Source #

Methods

contains Source #

Arguments

:: dom
dom
-> e
e
-> Bool 

Test if e is inside dom.

Instances

Instances details
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 #

class CanMapInside dom e where Source #

Methods

mapInside Source #

Arguments

:: dom
dom
-> e
e
-> e 

Return some value contained in dom. The returned value does not have to equal the given e even if e is already inside dom. All elements of dom should be covered with roughly the same probability when calling this function for evenly distributed e's.

This function is intended mainly for generating values inside dom for randomised tests.

class CanIntersectAsymmetric e1 e2 where Source #

A set intersection (usually partial)

Associated Types

type IntersectionType e1 e2 Source #

type IntersectionType e1 e2 = CN e1

Methods

intersect :: e1 -> e2 -> IntersectionType e1 e2 Source #

Instances

Instances details
CanIntersectAsymmetric Bool Bool Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type IntersectionType Bool Bool Source #

CanIntersectAsymmetric Kleenean Kleenean Source # 
Instance details

Defined in AERN2.MP.Enclosure

CanIntersectAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

type IntersectionType MPBall MPBall Source #

CanIntersectAsymmetric (CN Bool) (CN b) => CanIntersectAsymmetric Bool (CN b) Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type IntersectionType Bool (CN b) Source #

CanIntersectAsymmetric (CN Kleenean) (CN b) => CanIntersectAsymmetric Kleenean (CN b) Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type IntersectionType Kleenean (CN 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 #

CanIntersectAsymmetric (CN a) (CN Kleenean) => CanIntersectAsymmetric (CN a) Kleenean Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type IntersectionType (CN a) Kleenean Source #

CanIntersectAsymmetric (CN a) (CN Bool) => CanIntersectAsymmetric (CN a) Bool Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type IntersectionType (CN a) Bool Source #

(CanIntersectAsymmetric a b, IntersectionType a b ~ CN c) => CanIntersectAsymmetric (CN a) (CN b) Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type IntersectionType (CN a) (CN b) Source #

Methods

intersect :: CN a -> CN b -> IntersectionType (CN a) (CN b) 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 #

type CanIntersectBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ e1) Source #

type CanIntersectCNBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ CN e1) Source #

class CanUnionAsymmetric e1 e2 where Source #

A set union (usually partial)

Associated Types

type UnionType e1 e2 Source #

type UnionType e1 e2 = CN e1

Methods

union :: e1 -> e2 -> UnionType e1 e2 Source #

Instances

Instances details
CanUnionAsymmetric MPBall MPBall Source # 
Instance details

Defined in AERN2.MP.Ball.Comparisons

Associated Types

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

(CanUnionAsymmetric a b, UnionType a b ~ CN c) => CanUnionAsymmetric (CN a) (CN b) Source # 
Instance details

Defined in AERN2.MP.Enclosure

Associated Types

type UnionType (CN a) (CN b) Source #

Methods

union :: CN a -> CN b -> UnionType (CN a) (CN b) 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 #

type CanUnion e1 e2 = (CanUnionAsymmetric e1 e2, CanUnionAsymmetric e1 e2, UnionType e1 e2 ~ UnionType e2 e1) Source #

type CanUnionBy e1 e2 = (CanUnion e1 e2, UnionType e1 e2 ~ e1) Source #

type CanUnionCNBy e1 e2 = (CanUnion e1 e2, UnionType e1 e2 ~ CN e1) Source #

Orphan instances

(CanUnionSameType t, CanTakeCNErrors t) => HasIfThenElse Kleenean t Source # 
Instance details

Associated Types

type IfThenElseType Kleenean t #

Methods

ifThenElse :: Kleenean -> t -> t -> IfThenElseType Kleenean t #