Copyright | (c) Michal Konecny |
---|---|
License | BSD3 |
Maintainer | mikkonecny@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Enclosure classes and operations.
Synopsis
- class IsBall t where
- type CentreType t
- centre :: t -> CentreType t
- centreAsBallAndRadius :: t -> (t, ErrorBound)
- centreAsBall :: t -> t
- radius :: t -> ErrorBound
- updateRadius :: (ErrorBound -> ErrorBound) -> t -> t
- makeExactCentre :: t -> t
- ballFunctionUsingLipschitz :: (IsBall t, HasEqCertainly t t) => (t -> t) -> (t -> ErrorBound) -> t -> t
- class IsInterval i where
- type IntervalEndpoint i
- endpoints :: i -> (IntervalEndpoint i, IntervalEndpoint i)
- fromEndpoints :: IntervalEndpoint i -> IntervalEndpoint i -> i
- endpointL :: IsInterval i => i -> IntervalEndpoint i
- endpointR :: IsInterval i => i -> IntervalEndpoint i
- fromEndpointsAsIntervals :: (IsInterval i, CanMinMaxSameType (IntervalEndpoint i)) => i -> i -> i
- endpointsAsIntervals :: IsInterval i => i -> (i, i)
- endpointLAsInterval :: IsInterval i => i -> i
- endpointRAsInterval :: IsInterval i => i -> i
- intervalFunctionByEndpoints :: (IsInterval t, CanMinMaxSameType (IntervalEndpoint t), HasEqCertainly t t) => (t -> t) -> t -> t
- intervalFunctionByEndpointsUpDown :: IsInterval t => (IntervalEndpoint t -> IntervalEndpoint t) -> (IntervalEndpoint t -> IntervalEndpoint t) -> t -> t
- class CanPlusMinus t1 t2 where
- type PlusMinusType t1 t2
- plusMinus :: t1 -> t2 -> PlusMinusType t1 t2
- (+-) :: CanPlusMinus t1 t2 => t1 -> t2 -> PlusMinusType t1 t2
- class CanTestContains dom e where
- class CanMapInside dom e where
- mapInside :: dom -> e -> e
- 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
- intersect :: e1 -> e2 -> IntersectionType e1 e2
- type CanIntersect e1 e2 = (CanIntersectAsymmetric e1 e2, CanIntersectAsymmetric e1 e2, IntersectionType e1 e2 ~ IntersectionType e2 e1)
- type CanIntersectBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ e1)
- type CanIntersectSameType e1 = CanIntersectBy e1 e1
- type CanIntersectCNBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ CN e1)
- type CanIntersectCNSameType e1 = CanIntersectCNBy e1 e1
- class CanUnionAsymmetric e1 e2 where
- type CanUnion e1 e2 = (CanUnionAsymmetric e1 e2, CanUnionAsymmetric e1 e2, UnionType e1 e2 ~ UnionType e2 e1)
- type CanUnionBy e1 e2 = (CanUnion e1 e2, UnionType e1 e2 ~ e1)
- type CanUnionSameType e1 = CanUnionBy e1 e1
- type CanUnionCNBy e1 e2 = (CanUnion e1 e2, UnionType e1 e2 ~ CN e1)
- type CanUnionCNSameType e1 = CanUnionCNBy e1 e1
Documentation
type CentreType t Source #
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.
Instances
IsBall MPBall Source # | |
Defined in AERN2.MP.Ball.Type type CentreType MPBall Source # centre :: MPBall -> CentreType MPBall Source # centreAsBallAndRadius :: MPBall -> (MPBall, ErrorBound) Source # centreAsBall :: MPBall -> MPBall Source # radius :: MPBall -> ErrorBound Source # updateRadius :: (ErrorBound -> ErrorBound) -> MPBall -> MPBall Source # makeExactCentre :: MPBall -> MPBall Source # | |
IsBall t => IsBall (CN t) Source # | |
Defined in AERN2.MP.Enclosure type CentreType (CN t) Source # centre :: CN t -> CentreType (CN t) Source # centreAsBallAndRadius :: CN t -> (CN t, ErrorBound) Source # centreAsBall :: CN t -> CN t Source # radius :: CN t -> ErrorBound Source # updateRadius :: (ErrorBound -> ErrorBound) -> CN t -> CN t Source # makeExactCentre :: CN t -> CN t Source # |
ballFunctionUsingLipschitz Source #
:: (IsBall t, HasEqCertainly t t) | |
=> (t -> t) |
|
-> (t -> ErrorBound) |
|
-> t -> t |
|
Computes a ball function f
on the centre and updating the error bound using a Lipschitz constant.
class IsInterval i where Source #
type IntervalEndpoint i Source #
endpoints :: i -> (IntervalEndpoint i, IntervalEndpoint i) Source #
fromEndpoints :: IntervalEndpoint i -> IntervalEndpoint i -> i Source #
Instances
IsInterval MPBall Source # | |
Defined in AERN2.MP.Ball.Type type IntervalEndpoint MPBall Source # | |
IsInterval t => IsInterval (CN t) Source # | |
Defined in AERN2.MP.Enclosure type IntervalEndpoint (CN t) Source # endpoints :: CN t -> (IntervalEndpoint (CN t), IntervalEndpoint (CN t)) Source # fromEndpoints :: IntervalEndpoint (CN t) -> IntervalEndpoint (CN t) -> CN t Source # |
endpointL :: IsInterval i => i -> IntervalEndpoint i Source #
endpointR :: IsInterval i => i -> IntervalEndpoint i Source #
fromEndpointsAsIntervals :: (IsInterval i, CanMinMaxSameType (IntervalEndpoint i)) => i -> i -> i Source #
endpointsAsIntervals :: IsInterval i => i -> (i, i) Source #
endpointLAsInterval :: IsInterval i => i -> i Source #
endpointRAsInterval :: IsInterval i => i -> i Source #
intervalFunctionByEndpoints Source #
:: (IsInterval t, CanMinMaxSameType (IntervalEndpoint t), HasEqCertainly t t) | |
=> (t -> t) |
|
-> t -> t |
|
Computes a *monotone* ball function f
on intervals using the interval endpoints.
intervalFunctionByEndpointsUpDown Source #
:: IsInterval t | |
=> (IntervalEndpoint t -> IntervalEndpoint t) |
|
-> (IntervalEndpoint t -> IntervalEndpoint t) |
|
-> t -> t |
|
Computes a *monotone* ball function f
on intervals using the interval endpoints.
class CanPlusMinus t1 t2 where Source #
type PlusMinusType t1 t2 Source #
type PlusMinusType t1 t2 = t1
plusMinus :: t1 -> t2 -> PlusMinusType t1 t2 Source #
Operator for constructing or enlarging enclosures such as balls or intervals
Instances
CanBeErrorBound t => CanPlusMinus Int t Source # | |
Defined in AERN2.MP.Ball.Conversions type PlusMinusType Int t Source # | |
CanBeErrorBound t => CanPlusMinus Integer t Source # | |
Defined in AERN2.MP.Ball.Conversions type PlusMinusType Integer t Source # | |
CanBeErrorBound t => CanPlusMinus Rational t Source # | |
Defined in AERN2.MP.Ball.Conversions type PlusMinusType Rational t Source # | |
CanBeErrorBound t => CanPlusMinus MPFloat t Source # | |
Defined in AERN2.MP.Ball.Conversions type PlusMinusType MPFloat t Source # | |
CanBeErrorBound t => CanPlusMinus Dyadic t Source # | |
Defined in AERN2.MP.Ball.Conversions type PlusMinusType Dyadic t Source # | |
CanBeErrorBound t => CanPlusMinus MPBall t Source # | |
Defined in AERN2.MP.Ball.Conversions type PlusMinusType MPBall t Source # | |
CanBeErrorBound t => CanPlusMinus (CN MPBall) t Source # | |
Defined in AERN2.MP.Ball.Conversions 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 #
class CanMapInside dom e where Source #
:: 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.
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 #
A set intersection (usually partial)
type IntersectionType e1 e2 Source #
type IntersectionType e1 e2 = CN e1
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 CanIntersectBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ e1) Source #
type CanIntersectSameType e1 = CanIntersectBy e1 e1 Source #
type CanIntersectCNBy e1 e2 = (CanIntersect e1 e2, IntersectionType e1 e2 ~ CN e1) Source #
type CanIntersectCNSameType e1 = CanIntersectCNBy e1 e1 Source #
class CanUnionAsymmetric e1 e2 where Source #
A set union (usually partial)
Instances
CanUnionAsymmetric MPBall MPBall Source # | |
(CanUnionAsymmetric MPBall b, CanBeErrors es) => CanUnionAsymmetric MPBall (CollectErrors es b) Source # | |
Defined in AERN2.MP.Ball.Comparisons type UnionType MPBall (CollectErrors es b) Source # union :: MPBall -> CollectErrors es b -> UnionType MPBall (CollectErrors es b) Source # | |
(CanUnionAsymmetric a b, UnionType a b ~ CN c) => CanUnionAsymmetric (CN a) (CN b) Source # | |
(CanUnionAsymmetric a MPBall, CanBeErrors es) => CanUnionAsymmetric (CollectErrors es a) MPBall Source # | |
Defined in AERN2.MP.Ball.Comparisons type UnionType (CollectErrors es a) MPBall Source # union :: CollectErrors es a -> MPBall -> 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 CanUnionSameType e1 = CanUnionBy e1 e1 Source #
type CanUnionCNSameType e1 = CanUnionCNBy e1 e1 Source #
Orphan instances
(CanUnionSameType t, CanTakeCNErrors t) => HasIfThenElse Kleenean t Source # | |
type IfThenElseType Kleenean t # ifThenElse :: Kleenean -> t -> t -> IfThenElseType Kleenean t # |