data-interval-1.1.1: Interval arithmetic for both open and closed intervals

Copyright(c) Masahiro Sakai 2011-2013
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityprovisional
Portabilitynon-portable (ScopedTypeVariables, DeriveDataTypeable)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Interval

Contents

Description

Interval datatype and interval arithmetic.

Unlike the intervals package (http://hackage.haskell.org/package/intervals), this module provides both open and closed intervals and is intended to be used with Rational.

For the purpose of abstract interpretation, it might be convenient to use Lattice instance. See also lattices package (http://hackage.haskell.org/package/lattices).

Synopsis

Interval type

data Interval r Source

The intervals (i.e. connected and convex subsets) over real numbers R.

Instances

data Extended r :: * -> *

Extended r is an extension of r with positive/negative infinity (±∞).

Constructors

NegInf

negative infinity (-∞)

Finite !r

finite value

PosInf

positive infinity (+∞)

Instances

Functor Extended 
Bounded (Extended r) 
Eq r => Eq (Extended r) 
(Fractional r, Ord r) => Fractional (Extended r)

Note that Extended r is not a field, nor a ring.

Data r => Data (Extended r) 
(Num r, Ord r) => Num (Extended r)

Note that Extended r is not a field, nor a ring.

PosInf + NegInf is left undefined as usual, but we define 0 * PosInf = 0 * NegInf = 0 by following the convention of probability or measure theory.

Ord r => Ord (Extended r) 
Read r => Read (Extended r) 
Show r => Show (Extended r) 
NFData r => NFData (Extended r) 
Hashable r => Hashable (Extended r) 
Typeable (* -> *) Extended 

type EndPoint r = Extended r Source

Endpoints of intervals

Construction

interval Source

Arguments

:: Ord r 
=> (EndPoint r, Bool)

lower bound and whether it is included

-> (EndPoint r, Bool)

upper bound and whether it is included

-> Interval r 

smart constructor for Interval

(<=..<=) Source

Arguments

:: Ord r 
=> EndPoint r

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

closed interval [l,u]

(<..<=) Source

Arguments

:: Ord r 
=> EndPoint r

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

left-open right-closed interval (l,u]

(<=..<) Source

Arguments

:: Ord r 
=> EndPoint r

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

left-closed right-open interval [l, u)

(<..<) Source

Arguments

:: Ord r 
=> EndPoint r

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

open interval (l, u)

whole :: Ord r => Interval r Source

whole real number line (-∞, ∞)

empty :: Ord r => Interval r Source

empty (contradicting) interval

singleton :: Ord r => r -> Interval r Source

singleton set [x,x]

Query

null :: Ord r => Interval r -> Bool Source

Is the interval empty?

member :: Ord r => r -> Interval r -> Bool Source

Is the element in the interval?

notMember :: Ord r => r -> Interval r -> Bool Source

Is the element not in the interval?

isSubsetOf :: Ord r => Interval r -> Interval r -> Bool Source

Is this a subset? (i1 `isSubsetOf` i2) tells whether i1 is a subset of i2.

isProperSubsetOf :: Ord r => Interval r -> Interval r -> Bool Source

Is this a proper subset? (i.e. a subset but not equal).

lowerBound :: Interval r -> EndPoint r Source

Lower endpoint (i.e. greatest lower bound) of the interval.

upperBound :: Interval r -> EndPoint r Source

Upper endpoint (i.e. least upper bound) of the interval.

lowerBound' :: Interval r -> (EndPoint r, Bool) Source

lowerBound of the interval and whether it is included in the interval. The result is convenient to use as an argument for interval.

upperBound' :: Interval r -> (EndPoint r, Bool) Source

upperBound of the interval and whether it is included in the interval. The result is convenient to use as an argument for interval.

width :: (Num r, Ord r) => Interval r -> r Source

Width of a interval. Width of an unbounded interval is undefined.

Universal comparison operators

(<!) :: Ord r => Interval r -> Interval r -> Bool Source

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

(<=!) :: Ord r => Interval r -> Interval r -> Bool Source

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

(==!) :: Ord r => Interval r -> Interval r -> Bool Source

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

(>=!) :: Ord r => Interval r -> Interval r -> Bool Source

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

(>!) :: Ord r => Interval r -> Interval r -> Bool Source

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

(/=!) :: Ord r => Interval r -> Interval r -> Bool Source

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

Since 1.0.1

Existential comparison operators

(<?) :: Ord r => Interval r -> Interval r -> Bool Source

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

(<=?) :: Ord r => Interval r -> Interval r -> Bool Source

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

(==?) :: Ord r => Interval r -> Interval r -> Bool Source

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

Since 1.0.0

(>=?) :: Ord r => Interval r -> Interval r -> Bool Source

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

(>?) :: Ord r => Interval r -> Interval r -> Bool Source

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

(/=?) :: Ord r => Interval r -> Interval r -> Bool Source

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

Since 1.0.1

Existential comparison operators that produce witnesses (experimental)

(<??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r) Source

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

Since 1.0.0

(<=??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r) Source

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

Since 1.0.0

(==??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r) Source

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

Since 1.0.0

(>=??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r) Source

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

Since 1.0.0

(>??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r) Source

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

Since 1.0.0

(/=??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r) Source

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

Since 1.0.1

Combine

intersection :: forall r. Ord r => Interval r -> Interval r -> Interval r Source

intersection of two intervals

intersections :: Ord r => [Interval r] -> Interval r Source

intersection of a list of intervals.

Since 0.6.0

hull :: forall r. Ord r => Interval r -> Interval r -> Interval r Source

convex hull of two intervals

hulls :: Ord r => [Interval r] -> Interval r Source

convex hull of a list of intervals.

Since 0.6.0

Operations

pickup :: (Real r, Fractional r) => Interval r -> Maybe r Source

pick up an element from the interval if the interval is not empty.

simplestRationalWithin :: RealFrac r => Interval r -> Maybe Rational Source

simplestRationalWithin returns the simplest rational number within the interval.

A rational number y is said to be simpler than another y' if

(see also approxRational)

Since 0.4.0