rounded-0.1.0.1: Correctly-rounded arbitrary-precision floating-point arithmetic

Safe HaskellNone
LanguageHaskell2010

Numeric.Rounded.Interval

Synopsis

Documentation

data Interval p Source #

Constructors

I (Rounded TowardNegInf p) (Rounded TowardInf p) 
Empty 
Instances
Eq (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Methods

(==) :: Interval p -> Interval p -> Bool #

(/=) :: Interval p -> Interval p -> Bool #

Precision p => Floating (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Precision p => Fractional (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Precision p => Num (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Precision p => Ord (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Methods

compare :: Interval p -> Interval p -> Ordering #

(<) :: Interval p -> Interval p -> Bool #

(<=) :: Interval p -> Interval p -> Bool #

(>) :: Interval p -> Interval p -> Bool #

(>=) :: Interval p -> Interval p -> Bool #

max :: Interval p -> Interval p -> Interval p #

min :: Interval p -> Interval p -> Interval p #

Precision p => Real (Interval p) Source #

realToFrac will use the midpoint

Instance details

Defined in Numeric.Rounded.Interval

Methods

toRational :: Interval p -> Rational #

Precision p => RealFrac (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Methods

properFraction :: Integral b => Interval p -> (b, Interval p) #

truncate :: Integral b => Interval p -> b #

round :: Integral b => Interval p -> b #

ceiling :: Integral b => Interval p -> b #

floor :: Integral b => Interval p -> b #

Precision p => Show (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Methods

showsPrec :: Int -> Interval p -> ShowS #

show :: Interval p -> String #

showList :: [Interval p] -> ShowS #

Generic (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

Associated Types

type Rep (Interval p) :: Type -> Type #

Methods

from :: Interval p -> Rep (Interval p) x #

to :: Rep (Interval p) x -> Interval p #

type Rep (Interval p) Source # 
Instance details

Defined in Numeric.Rounded.Interval

fmod :: RealFrac a => a -> a -> a Source #

increasing :: (forall r. Rounding r => Rounded r a -> Rounded r b) -> Interval a -> Interval b Source #

lift a monotone increasing function over a given interval

decreasing :: (forall r. Rounding r => Rounded r a -> Rounded r b) -> Interval a -> Interval b Source #

(+/-) :: Rounded r p -> Rounded r' p -> Interval p infixl 6 Source #

interval :: Rounded TowardNegInf p -> Rounded TowardInf p -> Maybe (Interval p) Source #

create a non-empty interval or fail

whole :: Precision p => Interval p Source #

The whole real number line

>>> whole
-Infinity ... Infinity

empty :: Interval p Source #

An empty interval

>>> empty
Empty

null :: Interval p -> Bool Source #

Check if an interval is empty

>>> null (1 ... 5)
False
>>> null (1 ... 1)
False
>>> null empty
True

inf :: Interval p -> Rounded TowardNegInf p Source #

The infimum (lower bound) of an interval

>>> inf (1.0 ... 20.0)
1.0
>>> inf empty
*** Exception: empty interval

sup :: Interval p -> Rounded TowardInf p Source #

The supremum (upper bound) of an interval

>>> sup (1.0 ... 20.0)
20.0
>>> sup empty
*** Exception: empty interval

singular :: Interval p -> Bool Source #

Is the interval a singleton point? N.B. This is fairly fragile and likely will not hold after even a few operations that only involve singletons

>>> singular (singleton 1)
True
>>> singular (1.0 ... 20.0)
False

width :: Precision p => Interval p -> Rounded TowardInf p Source #

Calculate the width of an interval.

>>> width (1 ... 20)
19 ... 19
>>> width (singleton 1)
0 ... 0
>>> width empty
0 ... 0

magnitude :: Precision p => Interval p -> Rounded TowardInf p Source #

Magnitude

>>> magnitude (1 ... 20)
20
>>> magnitude (-20 ... 10)
20
>>> magnitude (singleton 5)
5

throws EmptyInterval if the interval is empty.

>>> magnitude empty
*** Exception: empty interval

mignitude :: Precision p => Interval p -> Rounded TowardNegInf p Source #

"mignitude"

>>> mignitude (1 ... 20)
1
>>> mignitude (-20 ... 10)
0
>>> mignitude (singleton 5)
5

throws EmptyInterval if the interval is empty.

>>> mignitude empty
*** Exception: empty interval

symmetric :: Rounded TowardInf p -> Interval p Source #

Construct a symmetric interval.

>>> symmetric 3
-3 ... 3

distance :: Precision p => Interval p -> Interval p -> Rounded TowardNegInf p Source #

Hausdorff distance between intervals.

>>> distance (1 ... 7) (6 ... 10)
0
>>> distance (1 ... 7) (15 ... 24)
8
>>> distance (1 ... 7) (-10 ... -2)
3
>>> distance Empty (1 ... 1)
*** Exception: empty interval

inflate :: Precision p => Rounded TowardInf p -> Interval p -> Interval p Source #

Inflate an interval by enlarging it at both ends.

>>> inflate 3 (-1 ... 7)
-4 ... 10
>>> inflate (-2) (0 ... 4)
-2 ... 6
>>> inflate 1 empty
Empty

(<!) :: Precision p => Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x < y

>>> (5 ... 10 :: Interval Double) <! (20 ... 30 :: Interval Double)
True
>>> (5 ... 10 :: Interval Double) <! (10 ... 30 :: Interval Double)
False
>>> (20 ... 30 :: Interval Double) <! (5 ... 10 :: Interval Double)
False

(<=!) :: Precision p => Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x <= y

>>> (5 ... 10 :: Interval Double) <=! (20 ... 30 :: Interval Double)
True
>>> (5 ... 10 :: Interval Double) <=! (10 ... 30 :: Interval Double)
True
>>> (20 ... 30 :: Interval Double) <=! (5 ... 10 :: Interval Double)
False

(==!) :: Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x == y

Only singleton intervals or empty intervals can return true

>>> (singleton 5 :: Interval Double) ==! (singleton 5 :: Interval Double)
True
>>> (5 ... 10 :: Interval Double) ==! (5 ... 10 :: Interval Double)
False

(/=!) :: Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x /= y

>>> (5 ... 15 :: Interval Double) /=! (20 ... 40 :: Interval Double)
True
>>> (5 ... 15 :: Interval Double) /=! (15 ... 40 :: Interval Double)
False

(>!) :: Precision p => Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x > y

>>> (20 ... 40 :: Interval Double) >! (10 ... 19 :: Interval Double)
True
>>> (5 ... 20 :: Interval Double) >! (15 ... 40 :: Interval Double)
False

(>=!) :: Precision p => Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x >= y

>>> (20 ... 40 :: Interval Double) >=! (10 ... 20 :: Interval Double)
True
>>> (5 ... 20 :: Interval Double) >=! (15 ... 40 :: Interval Double)
False

elem :: Rounded TowardZero p -> Interval p -> Bool Source #

Determine if a point is in the interval.

>>> elem 3.2 (1 ... 5)
True
>>> elem 5 (1 ... 5)
True
>>> elem 1 (1 ... 5)
True
>>> elem 8 (1 ... 5)
False
>>> elem 5 empty
False

notElem :: Rounded TowardZero p -> Interval p -> Bool Source #

Determine if a point is not included in the interval

>>> notElem 8 (1.0 ... 5.0)
True
>>> notElem 1.4 (1.0 ... 5.0)
False

And of course, nothing is a member of the empty interval.

>>> notElem 5 empty
True

certainly :: Precision p => (forall b. Ord b => b -> b -> Bool) -> Interval p -> Interval p -> Bool Source #

For all x in X, y in Y. x op y

(<?) :: Precision p => Interval p -> Interval p -> Bool Source #

Does there exist an x in X, y in Y such that x < y?

(<=?) :: Precision p => Interval p -> Interval p -> Bool Source #

Does there exist an x in X, y in Y such that x <= y?

(==?) :: Interval a -> Interval a -> Bool Source #

Does there exist an x in X, y in Y such that x == y?

(/=?) :: Interval a -> Interval a -> Bool Source #

Does there exist an x in X, y in Y such that x /= y?

(>?) :: Precision p => Interval p -> Interval p -> Bool Source #

Does there exist an x in X, y in Y such that x > y?

(>=?) :: Precision p => Interval p -> Interval p -> Bool Source #

Does there exist an x in X, y in Y such that x >= y?

possibly :: Precision p => (forall b. Ord b => b -> b -> Bool) -> Interval p -> Interval p -> Bool Source #

Does there exist an x in X, y in Y such that x op y?

contains :: Precision p => Interval p -> Interval p -> Bool Source #

Check if interval X totally contains interval Y

>>> (20 ... 40 :: Interval Double) `contains` (25 ... 35 :: Interval Double)
True
>>> (20 ... 40 :: Interval Double) `contains` (15 ... 35 :: Interval Double)
False

isSubsetOf :: Precision p => Interval p -> Interval p -> Bool Source #

Flipped version of contains. Check if interval X a subset of interval Y

>>> (25 ... 35 :: Interval Double) `isSubsetOf` (20 ... 40 :: Interval Double)
True
>>> (20 ... 40 :: Interval Double) `isSubsetOf` (15 ... 35 :: Interval Double)
False

intersection :: Precision p => Interval p -> Interval p -> Interval p Source #

Calculate the intersection of two intervals.

>>> intersection (1 ... 10 :: Interval Double) (5 ... 15 :: Interval Double)
5.0 ... 10.0

hull :: Precision p => Interval p -> Interval p -> Interval p Source #

Calculate the convex hull of two intervals

>>> hull (0 ... 10 :: Interval Double) (5 ... 15 :: Interval Double)
0.0 ... 15.0
>>> hull (15 ... 85 :: Interval Double) (0 ... 10 :: Interval Double)
0.0 ... 85.0

bisect :: Precision p => Interval p -> (Interval p, Interval p) Source #

Bisect an interval at its midpoint.

>>> bisect (10.0 ... 20.0)
(10.0 ... 15.0,15.0 ... 20.0)
>>> bisect (singleton 5.0)
(5.0 ... 5.0,5.0 ... 5.0)
>>> bisect Empty
(Empty,Empty)