Portability | portable |
---|---|
Stability | experimental |
Maintainer | mik@konecny.aow.cz |
Definitions of classes that describe what is required from arbitrary precision approximations of exact real numbers.
We introduce two levels of abstraction for these approximations:
-
ERApprox
= a *set* of approximated numbers whose size is measured using some fixed measure -
ERIntApprox
= an *interval* of real numbers with finitely representable endpoints
To be imported qualified, usually with the synonym RA.
- class Fractional ra => ERApprox ra where
- getPrecision :: ra -> Precision
- getGranularity :: ra -> Granularity
- setGranularity :: Granularity -> ra -> ra
- setMinGranularity :: Granularity -> ra -> ra
- isEmpty :: ra -> Bool
- isBottom :: ra -> Bool
- isExact :: ra -> Bool
- isDisjoint :: ra -> ra -> Bool
- isInteriorDisjoint :: ra -> ra -> Bool
- isBounded :: ra -> Bool
- bottomApprox :: ra
- emptyApprox :: ra
- refines :: ra -> ra -> Bool
- (/\) :: ra -> ra -> ra
- intersectMeasureImprovement :: EffortIndex -> ra -> ra -> (ra, ra)
- equalReals :: ra -> ra -> Maybe Bool
- compareReals :: ra -> ra -> Maybe Ordering
- leqReals :: ra -> ra -> Maybe Bool
- equalApprox :: ra -> ra -> Bool
- compareApprox :: ra -> ra -> Ordering
- double2ra :: Double -> ra
- showApprox :: Int -> Bool -> Bool -> ra -> String
- class ERApprox ira => ERIntApprox ira where
- doubleBounds :: ira -> (Double, Double)
- floatBounds :: ira -> (Float, Float)
- integerBounds :: ira -> (ExtendedInteger, ExtendedInteger)
- bisectDomain :: Maybe ira -> ira -> (ira, ira)
- defaultBisectPt :: ira -> ira
- bounds :: ira -> (ira, ira)
- (\/) :: ira -> ira -> ira
- bounds2ira :: ERIntApprox ira => (ira, ira) -> ira
- effIx2ra :: ERApprox ra => EffortIndex -> ra
- splitIRA :: ERIntApprox ira => ira -> [ira] -> [ira]
- eqSingletons :: ERApprox ra => ra -> ra -> Bool
- leqSingletons :: ERApprox ra => ra -> ra -> Bool
- ltSingletons :: ERApprox ra => ra -> ra -> Bool
- equalIntervals :: ERIntApprox ira => ira -> ira -> Bool
- exactMiddle :: ERIntApprox ira => ira -> (ira, ira, ira, Granularity)
- maxExtensionR2R :: ERIntApprox ira => (EffortIndex -> ira -> [ira]) -> (EffortIndex -> ira -> ira) -> EffortIndex -> ira -> ira
Documentation
class Fractional ra => ERApprox ra whereSource
A type whose elements represent sets that can be used to approximate a single extended real number with arbitrary precision.
getPrecision :: ra -> PrecisionSource
Precision is a measure of the set size.
The default interpretation:
- If the diameter of the set is d, then the precision should be near floor(- log_2 d).
getGranularity :: ra -> GranularitySource
the lower the granularity the bigger the rounding errors
setGranularity :: Granularity -> ra -> raSource
increase or safely decrease granularity
setMinGranularity :: Granularity -> ra -> raSource
ensure granularity is not below the first arg
true if this represents a computational error
true if this holds no information
true if this is a singleton
isDisjoint :: ra -> ra -> BoolSource
isInteriorDisjoint :: ra -> ra -> BoolSource
true if the approximation excludes infinity
bottomApprox :: raSource
the bottom element - any number
emptyApprox :: raSource
the top element - error
refines :: ra -> ra -> BoolSource
first arg is a subset of the second arg
join; combining two approximations of the same number
intersectMeasureImprovement :: EffortIndex -> ra -> ra -> (ra, ra)Source
Like intersection but the second component:
- measures improvement of the intersection relative to the first of the two approximations
- is a positive number: 1 means no improvement, 2 means doubled precision, etc.
equalReals :: ra -> ra -> Maybe BoolSource
nothing if overlapping and not singletons
compareReals :: ra -> ra -> Maybe OrderingSource
nothing if overlapping and not singletons
leqReals :: ra -> ra -> Maybe BoolSource
nothing if overlapping on interior or by a wrong endpoint
equalApprox :: ra -> ra -> BoolSource
syntactic comparison
compareApprox :: ra -> ra -> OrderingSource
syntactic linear ordering
(ERRealBase b, RealFrac b) => ERApprox (ERInterval b) |
class ERApprox ira => ERIntApprox ira whereSource
A type whose elements represent sets that can be used to approximate a recursive set of closed extended real number intervals with arbitrary precision.
A type whose elements represent real *intervals* that can be used to approximate a single extended real number with arbitrary precision.
Sometimes, these types can be used to approximate a closed extended real number interval with arbitrary precision. Nevetheless, this is not guaranteed.
doubleBounds :: ira -> (Double, Double)Source
floatBounds :: ira -> (Float, Float)Source
integerBounds :: ira -> (ExtendedInteger, ExtendedInteger)Source
:: Maybe ira | point to split at |
-> ira | interval to split |
-> (ira, ira) | left and right, overlapping on a singleton |
defaultBisectPt :: ira -> iraSource
bounds :: ira -> (ira, ira)Source
returns thin approximations of endpoints, in natural order
(\/) :: ira -> ira -> iraSource
meet, usually constructing interval from approximations of its endpoints
This does not need to be the meet of the real intervals but it has to be a maximal element in the set of all ira elements that are below the two parameters.
(ERRealBase b, RealFrac b) => ERIntApprox (ERInterval b) |
bounds2ira :: ERIntApprox ira => (ira, ira) -> iraSource
Inverse of bounds
.
effIx2ra :: ERApprox ra => EffortIndex -> raSource
This function converts an effort index to a real number approximation.
Useful when an effort index is used in a formula mixed with real approximations.
:: ERIntApprox ira | |
=> ira | an interval to be split |
-> [ira] | approximations of the cut points in increasing order |
-> [ira] |
Split an interval to a sequence of intervals whose union is the original interval using a given sequence of cut points. The cut points are expected to be in increasing order and contained in the given interval. Violations of this rule are tolerated.
eqSingletons :: ERApprox ra => ra -> ra -> BoolSource
Assuming the arguments are singletons, equality is decidable.
leqSingletons :: ERApprox ra => ra -> ra -> BoolSource
Assuming the arguments are singletons, <=
is decidable.
ltSingletons :: ERApprox ra => ra -> ra -> BoolSource
Assuming the arguments are singletons, <
is decidable.
equalIntervals :: ERIntApprox ira => ira -> ira -> BoolSource
Return true if and only if the two intervals have equal endpoints.
exactMiddle :: ERIntApprox ira => ira -> (ira, ira, ira, Granularity)Source
- Return the endpoints of the interval as well as the exact midpoint.
- To be able to do this, there may be a need to increase granularity.
- All three singleton intervals are set to the same new granularity.
:: ERIntApprox ira | |
=> (EffortIndex -> ira -> [ira]) | returns a safe approximation of all extrema within the interval |
-> (EffortIndex -> ira -> ira) | a function behaving well on sequences that intersect to a point |
-> EffortIndex -> ira -> ira | a function behaving well on sequences that intersect to a non-empty interval |
This produces a function that computes the maximal extension of the
given function. A maximal extension function has the property:
f(I) = { f(x) | x in I }. Here we get this property only for the
limit function for its EffortIndex
tending to infinity.