| Copyright | (c) Michal Konecny |
|---|---|
| License | BSD3 |
| Maintainer | mikkonecny@gmail.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell98 |
AERN2.MP.Enclosure
Contents
Description
Enclosure classes and operations.
- class IsBall t where
- type CentreType t
- class IsInterval i e where
- intervalFunctionByEndpoints :: (IsInterval t t, HasEqCertainly t t) => (t -> t) -> t -> t
- intervalFunctionByEndpointsUpDown :: IsInterval t e => (e -> e) -> (e -> e) -> t -> t
- class CanTestContains dom e where
- class CanMapInside dom e where
- specCanMapInside :: (CanMapInside d e, CanTestContains d e, Arbitrary d, Arbitrary e, Show d, Show e) => T d -> T e -> Spec
- class CanIntersectAsymmetric e1 e2 where
- type IntersectionType e1 e2
- type CanIntersect e1 e2 = (CanIntersectAsymmetric e1 e2, CanIntersectAsymmetric e1 e2, IntersectionType e1 e2 ~ IntersectionType e2 e1)
- type CanIntersectCNBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ EnsureCN e1, CanIntersect (EnsureCN e1) e2, IntersectionType (EnsureCN e1) e2 ~ EnsureCN e1)
- type CanIntersectCNSameType e1 = (CanIntersectCNBy e1 e1, CanIntersect (EnsureCN e1) (EnsureCN e1), IntersectionType (EnsureCN e1) (EnsureCN e1) ~ EnsureCN e1)
- class CanUnionAsymmetric e1 e2 where
- type UnionType e1 e2
- type CanUnion e1 e2 = (CanUnionAsymmetric e1 e2, CanUnionAsymmetric e1 e2, UnionType e1 e2 ~ UnionType e2 e1)
- type CanUnionCNBy e1 e2 = (CanUnion e1 e2, UnionType e1 e2 ~ EnsureCN e1, CanUnion (EnsureCN e1) e2, UnionType (EnsureCN e1) e2 ~ EnsureCN e1)
- type CanUnionCNSameType e1 = (CanUnionCNBy e1 e1, CanUnion (EnsureCN e1) (EnsureCN e1), UnionType (EnsureCN e1) (EnsureCN e1) ~ EnsureCN e1)
Documentation
Minimal complete definition
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 :: IsBall t => 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.
intervalFunctionByEndpoints Source #
Arguments
| :: (IsInterval t t, HasEqCertainly t t) | |
| => (t -> t) |
|
| -> t -> t |
|
Computes a *monotone* ball function f on intervals using the interval endpoints.
intervalFunctionByEndpointsUpDown Source #
Arguments
| :: IsInterval t e | |
| => (e -> e) |
|
| -> (e -> e) |
|
| -> t -> t |
|
Computes a *monotone* ball function f on intervals using the interval endpoints.
class CanTestContains dom e where Source #
Minimal complete definition
class CanMapInside dom e where Source #
Minimal complete definition
Methods
mapInside :: dom -> e -> e Source #
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.
specCanMapInside :: (CanMapInside d e, CanTestContains d e, Arbitrary d, Arbitrary e, Show d, Show e) => T d -> T e -> Spec Source #
class CanIntersectAsymmetric e1 e2 where Source #
Minimal complete definition
Associated Types
type IntersectionType e1 e2 Source #
Methods
intersect :: e1 -> e2 -> IntersectionType e1 e2 Source #
Instances
type CanIntersect e1 e2 = (CanIntersectAsymmetric e1 e2, CanIntersectAsymmetric e1 e2, IntersectionType e1 e2 ~ IntersectionType e2 e1) Source #
type CanIntersectCNBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ EnsureCN e1, CanIntersect (EnsureCN e1) e2, IntersectionType (EnsureCN e1) e2 ~ EnsureCN e1) Source #
type CanIntersectCNSameType e1 = (CanIntersectCNBy e1 e1, CanIntersect (EnsureCN e1) (EnsureCN e1), IntersectionType (EnsureCN e1) (EnsureCN e1) ~ EnsureCN e1) Source #
class CanUnionAsymmetric e1 e2 where Source #
Minimal complete definition
Instances
| (CanUnionAsymmetric e1 e2, CanEnsureCN e1, CanEnsureCN e2, CanEnsureCN (UnionType e1 e2)) => CanUnionAsymmetric (CN e1) (CN e2) Source # | |
| (Arrow to, CanUnionAsymmetric e1 e2) => CanUnionAsymmetric (to Accuracy e1) (to Accuracy e2) Source # | |
type CanUnion e1 e2 = (CanUnionAsymmetric e1 e2, CanUnionAsymmetric e1 e2, UnionType e1 e2 ~ UnionType e2 e1) Source #
type CanUnionCNBy e1 e2 = (CanUnion e1 e2, UnionType e1 e2 ~ EnsureCN e1, CanUnion (EnsureCN e1) e2, UnionType (EnsureCN e1) e2 ~ EnsureCN e1) Source #
type CanUnionCNSameType e1 = (CanUnionCNBy e1 e1, CanUnion (EnsureCN e1) (EnsureCN e1), UnionType (EnsureCN e1) (EnsureCN e1) ~ EnsureCN e1) Source #
Orphan instances
| (CanUnionCNSameType t, CanEnsureCN t) => HasIfThenElse (Maybe Bool) t Source # | |