HERA-0.2

Data.Number.Ball

Synopsis

Documentation

data Ball Source

Ball represents a closed interval [center-radius, center+radius]

Constructors

Ball 

Fields

center :: !Dyadic

center of the ball

radius :: !Dyadic

radius of the ball

Instances

makeASource

Arguments

:: Precision

desired precision of the center

-> Dyadic

left endpoint

-> Dyadic

right endpoint

-> Ball 

Make a ball from endpoints

makeSource

Arguments

:: Dyadic

left endpoint

-> Dyadic

right endpoint

-> Ball 

Make a ball from endpoints so that no precision is lost.

normalizeBall :: Precision -> Ball -> BallSource

Normalize the given ball's center to the specified precision. Resulting ball might be larger.

lower :: Precision -> Ball -> DyadicSource

Lower endpoint of the ball rounded down to specified precision.

upper :: Precision -> Ball -> DyadicSource

Upper endpoint of the ball rounded up to specified precision.

lower_ :: Ball -> DyadicSource

Lower endpoint with precision of the center

upper_ :: Ball -> DyadicSource

Upper endpoint with precision of the center

sgnLower :: Ball -> IntSource

Sign of lower endpoint of the ball. This should be faster than using signum (center b - radius b)

sgnUpper :: Ball -> IntSource

Analogous to sgnLower.

width :: Ball -> DyadicSource

Upper bound on the width of the ball. 2 * radius b rounded up.

compareB :: Ball -> Ball -> POrderingSource

Compare two balls.

  • if upper a < lower b then Less
  • if upper b < lower a then Greater
  • otherwise balls are incomparable.

below :: Ball -> Ball -> BoolSource

Check if second ball is included in the first

contains :: Ball -> Dyadic -> BoolSource

Check if dyadic is element of the ball.

intersectASource

Arguments

:: Monad m 
=> Precision

precision of the resulting ball's center

-> Ball 
-> Ball 
-> m Ball 

Returns an intersection of two balls. If balls are disjoint then computation fails with fail.

intersect :: Monad m => Ball -> Ball -> m BallSource

Intersection of two balls exactly (no precision is lost).

add :: Precision -> Ball -> Ball -> BallSource

Addition of two balls.

  •  center = center a + center b
  •  radius = radius a + radius b

Rounding errors are added to the radius.

sub :: Precision -> Ball -> Ball -> BallSource

Subtraction of two balls.

  •  center = center a - center b
  •  radius = radius a + radius b

Rounding errors are added to the radius.

neg :: Precision -> Ball -> BallSource

Negation of the ball.

  • center = - center b rounded to specified precision.
  • radius is only modified for the rounding error.

mul :: Precision -> Ball -> Ball -> BallSource

Multiplication of two balls. (centers of both balls are assumed positive)

  • If none of the balls contains 0 then
 center = center a * center b + radius a * radius b
 radius = center a * radius b + radius a * center b
  • If one of the operands (left) contains 0
 center = center a * upper b
 radius = radius a * upper b
  • If both of the balls contain 0
 lower =  min ((lower a) * (upper b)) ((lower b) * (upper a))
 upper =  max ((lower a) * (lower b)) ((upper b) * (upper a))

Rounding errors are added to the radius.

div :: Monad m => Precision -> Ball -> Ball -> m BallSource

Division of two balls

  • If radius is "large" then divide endpoints and makeA a ball from them.
  • If radius is "small" then division can be optimized
  •  center = center a / center b
  • (radius = radius a * center b + center a * radius b) / (center b * center b) + 2 * 2 ^ (e1 - e2 - p) where p is precision of the result, e1 = getExp c1, e2 = getExp c2 . This way the resulting interval is guaranteed to be correct.

Rounding errors are added to the radius.

If divisor ball contains zero compuatation fails with fail.

sqrt :: Monad m => Precision -> Ball -> m BallSource

Square root of a ball. If interval contains 0 then computation fails.

exp :: Precision -> Ball -> BallSource

 e ^ b

log :: Monad m => Precision -> Ball -> m BallSource

Natural logarithm of a ball. If interval contains 0 then computation fails.

maxB :: Precision -> Ball -> Ball -> BallSource

Maximum of two balls, meaning:

  • lower = max (lower a) (lower b) rounded down
  • upper = max (upper a) (upper b) rounded up

minB :: Precision -> Ball -> Ball -> BallSource

Analogous to maxB.

fromDyadic :: Precision -> Dyadic -> BallSource

MakeA a ball from dyadic. Radius is 0 if desired precision is not smaller than precision of dyadic.

fromString :: Precision -> String -> BallSource

Similar to fromDyadic.

fromInt :: Precision -> Int -> BallSource

Similar to fromDyadic.

fromWord :: Precision -> Word -> BallSource

Similar to fromInt.