aern2-mp-0.1.0.0: Multi-precision floats via MPFR

Copyright(c) Michal Konecny
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

AERN2.MP.Enclosure

Contents

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 :: 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)

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 e 
=> (e -> e)

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

-> (e -> e)

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 CanMapInside dom e where Source #

Minimal complete definition

mapInside

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.

class CanIntersectAsymmetric e1 e2 where Source #

Minimal complete definition

intersect

Associated Types

type IntersectionType e1 e2 Source #

Methods

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

Instances

CanIntersectAsymmetric Bool Bool Source # 
(CanIntersectAsymmetric Bool b, CanEnsureCE es b, CanEnsureCE es (IntersectionType Bool b), SuitableForCE es) => CanIntersectAsymmetric Bool (CollectErrors es b) Source # 

Associated Types

type IntersectionType Bool (CollectErrors es b) :: * Source #

(CanIntersectAsymmetric a b, CanEnsureCN a, (~) * (IntersectionType a b) (EnsureCN a), CanEnsureCN (EnsureCN a), CanEnsureCN b, (~) * (EnsureCN b) (EnsureCN a)) => CanIntersectAsymmetric (Maybe a) (Maybe b) Source # 

Associated Types

type IntersectionType (Maybe a) (Maybe b) :: * Source #

Methods

intersect :: Maybe a -> Maybe b -> IntersectionType (Maybe a) (Maybe b) Source #

(CanIntersectAsymmetric (Maybe a) b, CanEnsureCE es b, CanEnsureCE es (IntersectionType (Maybe a) b), SuitableForCE es) => CanIntersectAsymmetric (Maybe a) (CollectErrors es b) Source # 

Associated Types

type IntersectionType (Maybe a) (CollectErrors es b) :: * Source #

(CanIntersectAsymmetric a Bool, CanEnsureCE es a, CanEnsureCE es (IntersectionType a Bool), SuitableForCE es) => CanIntersectAsymmetric (CollectErrors es a) Bool Source # 

Associated Types

type IntersectionType (CollectErrors es a) Bool :: * Source #

(CanIntersectAsymmetric a (Maybe b), CanEnsureCE es a, CanEnsureCE es (IntersectionType a (Maybe b)), SuitableForCE es) => CanIntersectAsymmetric (CollectErrors es a) (Maybe b) Source # 

Associated Types

type IntersectionType (CollectErrors es a) (Maybe b) :: * Source #

(CanIntersectAsymmetric e1 e2, SuitableForCE es, CanEnsureCE es e1, CanEnsureCE es e2, CanEnsureCE es (IntersectionType e1 e2)) => CanIntersectAsymmetric (CollectErrors es e1) (CollectErrors es e2) Source # 

Associated Types

type IntersectionType (CollectErrors es e1) (CollectErrors es e2) :: * Source #

class CanUnionAsymmetric e1 e2 where Source #

Minimal complete definition

union

Associated Types

type UnionType e1 e2 Source #

Methods

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

Instances

(CanUnionAsymmetric e1 e2, CanEnsureCN e1, CanEnsureCN e2, CanEnsureCN (UnionType e1 e2)) => CanUnionAsymmetric (CN e1) (CN e2) Source # 

Associated Types

type UnionType (CN e1) (CN e2) :: * Source #

Methods

union :: CN e1 -> CN e2 -> UnionType (CN e1) (CN e2) Source #

(Arrow to, CanUnionAsymmetric e1 e2) => CanUnionAsymmetric (to Accuracy e1) (to Accuracy e2) Source # 

Associated Types

type UnionType (to Accuracy e1) (to Accuracy e2) :: * Source #

Methods

union :: to Accuracy e1 -> to Accuracy e2 -> UnionType (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 #

Orphan instances

(CanUnionCNSameType t, CanEnsureCN t) => HasIfThenElse (Maybe Bool) t Source # 

Associated Types

type IfThenElseType (Maybe Bool) t :: * #

Methods

ifThenElse :: Maybe Bool -> t -> t -> IfThenElseType (Maybe Bool) t #