AERN-RnToRm-0.5: polynomial function enclosures (PFEs) approximating exact real functions

Portabilityportable
Stabilityexperimental
Maintainermik@konecny.aow.cz

Data.Number.ER.RnToRm.UnitDom.Base

Description

Classes abstracting function arithmetic with directed rounding. Instances are used to describe a boundary for an approximation to a real function on the interval [-1,1]^n.

To be imported qualified, usually with the synonym UFB.

Documentation

class (ERRealBase b, ERIntApprox ra, Ord ufb, DomainBox boxb varid b, DomainIntBox boxra varid ra) => ERUnitFnBase boxb boxra varid b ra ufb | ufb -> boxb boxra varid b ra whereSource

Methods

initialiseBaseArithmetic :: ufb -> IO ()Source

This should be evaluated before using any of the following operations.

raEndpointsSource

Arguments

:: ufb

this parameter is not used except for type checking

-> ra 
-> (b, b) 

Convert from the associated interval type to the base type. (The types are determined by the given example function.)

raFromEndpointsSource

Arguments

:: ufb

this parameter is not used except for type checking

-> (b, b) 
-> ra 

Convert from the base type to the associated interval type. (The types are determined by the given example function.)

compareApprox :: ufb -> ufb -> OrderingSource

A linear ordering on basic functions, which can be syntactic and rather arbitrary.

showDiGrCmpSource

Arguments

:: Int

number of decimal digits to show

-> Bool

whether to show granularity

-> Bool

whether to show internal structure

-> ufb 
-> String 

isValid :: ufb -> BoolSource

Check internal consistency of the basic function, typically absence of NaN.

checkSource

Arguments

:: String

indentification of caller location for easier debugging

-> ufb 
-> ufb 

Check internal consistency of the basic function and report problem if any.

getGranularity :: ufb -> GranularitySource

Get the granularity of the coefficients inside this basic function.

setMinGranularity :: Granularity -> ufb -> ufbSource

setGranularity :: Granularity -> ufb -> ufbSource

getDegree :: ufb -> IntSource

Get the degree of this basic function.

If the function is a polynomial, this function should return its degree.

reduceDegreeUp :: Int -> ufb -> ufbSource

Decrease the degree of a basic function, rounding pointwise upwards.

getSize :: ufb -> IntSource

Get the term size of this basic function.

If the function is a polynomial, this function should return the number of terms in the polynomial.

reduceSizeUp :: Int -> ufb -> ufbSource

Decrease the size of this basic function, rounding pointwise upwards.

getVariables :: ufb -> [varid]Source

Get a list of all variables featured in this basic function.

const :: b -> ufbSource

Construct a constant basic function.

affineSource

Arguments

:: b

value at 0

-> Map varid b

ascent of each base vector

-> ufb 

Construct an affine basic function.

bounds :: EffortIndex -> ufb -> (b, b)Source

Find an upper bound of a basic function over [-1,1]^n.

upperBound :: EffortIndex -> ufb -> bSource

Find an upper bound of a basic function over [-1,1]^n.

upperBoundPrecise :: EffortIndex -> ufb -> bSource

Find an upper bound of a basic function over [-1,1]^n.

maxUpSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb
f1
-> ufb
f2
-> ufb 

Approximate the function max(f1,f2) from above.

minUpSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb
f1
-> ufb
f2
-> ufb 

Approximate the function min(f1,f2) from above.

maxDownSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb
f1
-> ufb
f2
-> ufb 

Approximate the function max(f1,f2) from below.

minDownSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb
f1
-> ufb
f2
-> ufb 

Approximate the function min(f1,f2) from below.

neg :: ufb -> ufbSource

Pointwise exact negation of a basic function

addConstUp :: b -> ufb -> ufbSource

Add a scalar to a basic function, rounding upwards.

scaleUp :: b -> ufb -> ufbSource

Multiply a basic function by a scalar, rounding upwards.

scaleApproxUpSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> ra 
-> ufb 
-> ufb 

Multiply a basic function by an approximation of a scalar, rounding upwards.

(+^) :: ufb -> ufb -> ufbSource

Pointwise upwards rounded addition

(-^) :: ufb -> ufb -> ufbSource

Pointwise upwards rounded subtraction

(*^) :: ufb -> ufb -> ufbSource

Pointwise upwards rounded multiplication

recipUp :: Int -> Int -> EffortIndex -> ufb -> ufbSource

Approximate the function 1/f from above, assuming f does not hit zero in the unit domain.

evalUp :: boxb -> ufb -> bSource

Evaluate a basic function at a point rounding upwards using a basic number for both the point and the result.

evalApprox :: boxra -> ufb -> raSource

Evaluate a basic function at a point rounding downwards using a basic number for both the point and the result.

Safely evaluate a basic function at a point using a real number approximation for both the point and the result.

partialEvalApproxUp :: boxra -> ufb -> ufbSource

Partially evaluate a basic function at a lower-dimensional point given using a real number approximation. Approximate the resulting function from above.

composeUpSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> varid

variable v to substitute in f

-> ufb

function f_v to substitute for v that maps [-1,1] into [-1,1]

-> ufb

pointwise upper bound of f[v |-> f_v]

Compose two basic functions, rounding upwards, assuming f_v ranges within the domain [-1,1].

composeManyUpSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> Map varid ufb

variables to substitute and for each variable v, function f_v to substitute for v that maps [-1,1] into [-1,1]

-> ufb

pointwise upper bound of f[v |-> f_v]

Substitute several variables in a basic function with other basic functions, rounding upwards, assuming each f_v ranges within the domain [-1,1].

composeDownSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> varid

variable v to substitute in f

-> ufb

function f_v to substitute for v that maps [-1,1] into [-1,1]

-> ufb

pointwise lower bound of f[v |-> f_v]

Compose two basic functions, rounding downwards, assuming f_v ranges within the domain [-1,1].

composeManyDownSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> Map varid ufb

variables to substitute and for each variable v, function f_v to substitute for v that maps [-1,1] into [-1,1]

-> ufb

pointwise lower bound of f[v |-> f_v]

Substitute several variables in a basic function with other basic functions, rounding downwards, assuming each f_v ranges within the domain [-1,1].

integrateSource

Arguments

:: varid

variable to integrate by

-> ufb
f
-> (ufb, ufb) 

Approximate the primitive function of f from below and from above.

differentiateSource

Arguments

:: varid

variable to differentiate by

-> ufb
f
-> (ufb, ufb) 

Approximate the derivative of f from below and from above.

volumeAboveZeroUpSource

Arguments

:: [varid]

dimensions to include in the measuring domain; have to include all those present in f

-> ufb
f
-> b 

Measure the volume between a function and the zero hyperplane on the domain [-1,1]^n.

Instances

(ERRealBase rb, RealFrac rb, DomainBox box varid Int, Ord box, Show varid, DomainBoxMappable boxb boxras varid rb [ERInterval rb], DomainBoxMappable boxra boxras varid (ERInterval rb) [ERInterval rb], DomainIntBox boxra varid (ERInterval rb)) => ERUnitFnBase boxb boxra varid rb (ERInterval rb) (ERChebPoly box rb) 

class ERUnitFnBase boxb boxra varid b ra ufb => ERUnitFnBaseEncl boxb boxra varid b ra ufb | ufb -> boxb boxra varid b ra whereSource

Methods

boundsEncl :: EffortIndex -> (ufb, ufb) -> (b, b)Source

constEncl :: (b, b) -> (ufb, ufb)Source

Construct a constant basic enclosure (negated lower bound fn, upper bound fn) from bounds given as coeffients (lower bound, upper bound).

evalEncl :: boxra -> (ufb, ufb) -> raSource

evalEnclInner :: boxra -> (ufb, ufb) -> raSource

addConstEnclSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> b 
-> (ufb, ufb) 
-> (ufb, ufb) 

Enclosure and base constant addition

IMPORTANT: enclosure = (NEGATED lower bound, upper bound)

scaleEnclSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> b 
-> (ufb, ufb) 
-> (ufb, ufb) 

Enclosure scaling by a base constant

IMPORTANT: enclosure = (NEGATED lower bound, upper bound)

addEnclSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> (ufb, ufb) 
-> (ufb, ufb) 
-> (ufb, ufb) 

Enclosure addition

IMPORTANT: enclosure = (NEGATED lower bound, upper bound)

multiplyEnclSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> (ufb, ufb) 
-> (ufb, ufb) 
-> (ufb, ufb) 

Enclosure multiplication

IMPORTANT: enclosure = (NEGATED lower bound, upper bound)

recipEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex 
-> (ufb, ufb)

enclosure of f

-> (ufb, ufb) 

Approximate the reciprocal of an enclosure, assuming f does not hit zero in the unit domain.

IMPORTANT: enclosure = (negated lower bound, upper bound)

composeEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> varid

variable v to substitute in f

-> (ufb, ufb)

enclosure of a function f_v to substitute for v that maps [-1,1] into [-1,1]

-> (ufb, ufb)

enclosure of f[v |-> f_v]

Compose two basic functions, rounding downwards and upwards, assuming f_v ranges within the domain [-1,1].

composeManyEnclsSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> Map varid (ufb, ufb)

variables to substitute and for each variable v, enclosure of a function f_v to substitute for v that maps [-1,1] into [-1,1]

-> (ufb, ufb)

enclosure of f[v |-> f_v]

Substitute several variables in a basic function with other basic functions, rounding downwards and upwards, assuming each f_v ranges within the domain [-1,1].

Instances

(ERRealBase rb, RealFrac rb, DomainBox box varid Int, Ord box, Show varid, DomainBoxMappable boxb boxras varid rb [ERInterval rb], DomainBoxMappable boxra boxras varid (ERInterval rb) [ERInterval rb], DomainIntBox boxra varid (ERInterval rb)) => ERUnitFnBaseEncl boxb boxra varid rb (ERInterval rb) (ERChebPoly box rb) 

class ERUnitFnBaseEncl boxb boxra varid b ra ufb => ERUnitFnBaseElementary boxb boxra varid b ra ufb | ufb -> boxb boxra varid b ra whereSource

Methods

sqrtEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating exp as a polynomial

-> (ufb, ufb)
f
-> (ufb, ufb) 

Approximate sqrt(f) for enclosures.

expEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating exp as a polynomial

-> (ufb, ufb)
f
-> (ufb, ufb) 

Approximate exp(f) for enclosures.

logEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating log as a polynomial

-> (ufb, ufb)
f
-> (ufb, ufb) 

Approximate log(f) for enclosures.

sinEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating sin as a polynomial

-> (ufb, ufb)
f
-> (ufb, ufb) 

Approximate sin(f) for enclosures, assuming the range of f is within [-pi2,pi2].

cosEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating cos as a polynomial

-> (ufb, ufb)
f
-> (ufb, ufb) 

Approximate cos(f) for enclosures, assuming the range of f is within [-pi2,pi2].

atanEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating cos as a polynomial

-> (ufb, ufb)
f
-> (ufb, ufb) 

Approximate atan(f) for enclosures.

Instances

(ERRealBase rb, RealFrac rb, DomainBox box varid Int, Ord box, Show varid, DomainBoxMappable boxb boxras varid rb [ERInterval rb], DomainBoxMappable boxra boxras varid (ERInterval rb) [ERInterval rb], DomainIntBox boxra varid (ERInterval rb)) => ERUnitFnBaseElementary boxb boxra varid rb (ERInterval rb) (ERChebPoly box rb) 

class ERUnitFnBase boxb boxra varid b ra ufb => ERUnitFnBaseIEncl boxb boxra varid b ra ufb | ufb -> boxb boxra varid b ra whereSource

Methods

constIEncl :: (b, b) -> ((ufb, ufb), Bool)Source

Construct a constant basic inner enclosure (negated lower bound fn, upper bound fn, is enclosure definitely anticonsistent?) from bounds given as coeffients (lower bound, upper bound). An inner enclosure (lnI,hI) is anticonsistent iff hI + lnI <= 0, ie upper bound is never above lower bound.

evalIEncl :: boxra -> ((ufb, ufb), Bool) -> raSource

addIEnclSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> ((ufb, ufb), Bool) 
-> ((ufb, ufb), Bool) 
-> ((ufb, ufb), Bool) 

Inner enclosure addition.

multiplyIEnclSource

Arguments

:: Int

maximum polynomial degree

-> Int

maximum term count

-> ((ufb, ufb), Bool) 
-> ((ufb, ufb), Bool) 
-> ((ufb, ufb), Bool) 

Inner enclosure multiplication.

recipIEnclPositiveSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex 
-> ((ufb, ufb), Bool) 
-> ((ufb, ufb), Bool) 

Approximate the reciprocal of an inner enclosure, assuming f is positive in the unit domain.

composeIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> varid

variable v to substitute in f

-> ((ufb, ufb), Bool)

inverse enclosure of a function f_v to substitute for v that maps [-1,1] into [-1,1]

-> ((ufb, ufb), Bool)

inverse enclosure of f[v |-> f_v]

Compose two basic functions, rounding downwards and upwards, assuming f_v ranges within the domain [-1,1].

composeManyIEnclsSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> ufb

function f

-> Map varid ((ufb, ufb), Bool)

variables to substitute and for each variable v inverse enclosure of a function f_v to substitute for v that maps [-1,1] into [-1,1]

-> ((ufb, ufb), Bool)

inverse enclosure of f[v |-> f_v]

Substitute several variables in a basic function with other basic functions, rounding downwards and upwards, assuming each f_v ranges within the domain [-1,1].

Instances

(ERRealBase rb, RealFrac rb, DomainBox box varid Int, Ord box, Show varid, DomainBoxMappable boxb boxras varid rb [ERInterval rb], DomainBoxMappable boxra boxras varid (ERInterval rb) [ERInterval rb], DomainIntBox boxra varid (ERInterval rb)) => ERUnitFnBaseIEncl boxb boxra varid rb (ERInterval rb) (ERChebPoly box rb) 

class ERUnitFnBaseIEncl boxb boxra varid b ra ufb => ERUnitFnBaseIElementary boxb boxra varid b ra ufb | ufb -> boxb boxra varid b ra whereSource

Methods

sqrtIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating exp as a polynomial

-> ((ufb, ufb), Bool)
f
-> ((ufb, ufb), Bool) 

Approximate sqrt(f) for enclosures.

expIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating exp as a polynomial

-> ((ufb, ufb), Bool)
f
-> ((ufb, ufb), Bool) 

Approximate exp(f) for enclosures.

logIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating log as a polynomial

-> ((ufb, ufb), Bool)
f
-> ((ufb, ufb), Bool) 

Approximate log(f) for enclosures.

sinIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating sin as a polynomial

-> ((ufb, ufb), Bool)
f
-> ((ufb, ufb), Bool) 

Approximate sin(f) for enclosures, assuming the range of f is within [-pi2,pi2].

cosIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating cos as a polynomial

-> ((ufb, ufb), Bool)
f
-> ((ufb, ufb), Bool) 

Approximate cos(f) for enclosures, assuming the range of f is within [-pi2,pi2].

atanIEnclSource

Arguments

:: Int

max degree for result

-> Int

max approx size for result

-> EffortIndex

how hard to try when approximating cos as a polynomial

-> ((ufb, ufb), Bool)
f
-> ((ufb, ufb), Bool) 

Approximate atan(f) for enclosures.

Instances

(ERRealBase rb, RealFrac rb, DomainBox box varid Int, Ord box, Show varid, DomainBoxMappable boxb boxras varid rb [ERInterval rb], DomainBoxMappable boxra boxras varid (ERInterval rb) [ERInterval rb], DomainIntBox boxra varid (ERInterval rb)) => ERUnitFnBaseIElementary boxb boxra varid rb (ERInterval rb) (ERChebPoly box rb)