data-interval-1.3.0: Interval datatype, interval arithmetic and interval-based containers

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

Data.IntegerInterval

Contents

Description

Interval datatype and interval arithmetic over integers.

Since 1.2.0

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 IntegerInterval Source #

The intervals (i.e. connected and convex subsets) over integers (Z).

Instances

Eq IntegerInterval Source # 
Data IntegerInterval Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntegerInterval -> c IntegerInterval #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntegerInterval #

toConstr :: IntegerInterval -> Constr #

dataTypeOf :: IntegerInterval -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IntegerInterval) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntegerInterval) #

gmapT :: (forall b. Data b => b -> b) -> IntegerInterval -> IntegerInterval #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntegerInterval -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntegerInterval -> r #

gmapQ :: (forall d. Data d => d -> u) -> IntegerInterval -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntegerInterval -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntegerInterval -> m IntegerInterval #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntegerInterval -> m IntegerInterval #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntegerInterval -> m IntegerInterval #

Num IntegerInterval Source # 
Read IntegerInterval Source # 
Show IntegerInterval Source # 
NFData IntegerInterval Source # 

Methods

rnf :: IntegerInterval -> () #

Hashable IntegerInterval Source # 
JoinSemiLattice IntegerInterval Source # 
MeetSemiLattice IntegerInterval Source # 
Lattice IntegerInterval Source # 
BoundedJoinSemiLattice IntegerInterval Source # 
BoundedMeetSemiLattice IntegerInterval Source # 
BoundedLattice IntegerInterval Source # 

Construction

interval Source #

Arguments

:: (Extended Integer, Bool)

lower bound and whether it is included

-> (Extended Integer, Bool)

upper bound and whether it is included

-> IntegerInterval 

smart constructor for IntegerInterval

(<=..<=) infix 5 Source #

Arguments

:: Extended Integer

lower bound l

-> Extended Integer

upper bound u

-> IntegerInterval 

closed interval [l,u]

(<..<=) infix 5 Source #

Arguments

:: Extended Integer

lower bound l

-> Extended Integer

upper bound u

-> IntegerInterval 

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

(<=..<) infix 5 Source #

Arguments

:: Extended Integer

lower bound l

-> Extended Integer

upper bound u

-> IntegerInterval 

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

(<..<) infix 5 Source #

Arguments

:: Extended Integer

lower bound l

-> Extended Integer

upper bound u

-> IntegerInterval 

open interval (l, u)

whole :: IntegerInterval Source #

whole real number line (-∞, ∞)

empty :: IntegerInterval Source #

empty (contradicting) interval

singleton :: Integer -> IntegerInterval Source #

singleton set \[x,x\]

Query

null :: IntegerInterval -> Bool Source #

Is the interval empty?

member :: Integer -> IntegerInterval -> Bool Source #

Is the element in the interval?

notMember :: Integer -> IntegerInterval -> Bool Source #

Is the element not in the interval?

isSubsetOf :: IntegerInterval -> IntegerInterval -> Bool Source #

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

isProperSubsetOf :: IntegerInterval -> IntegerInterval -> Bool Source #

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

lowerBound :: IntegerInterval -> Extended Integer Source #

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

upperBound :: IntegerInterval -> Extended Integer Source #

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

lowerBound' :: IntegerInterval -> (Extended Integer, 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' :: IntegerInterval -> (Extended Integer, 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 :: IntegerInterval -> Integer Source #

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

Universal comparison operators

(<!) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(<=!) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(==!) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(>=!) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(>!) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(/=!) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

Existential comparison operators

(<?) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(<=?) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(==?) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(>=?) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(>?) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

(/=?) :: IntegerInterval -> IntegerInterval -> Bool infix 4 Source #

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

Existential comparison operators that produce witnesses (experimental)

(<??) :: IntegerInterval -> IntegerInterval -> Maybe (Integer, Integer) infix 4 Source #

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

(<=??) :: IntegerInterval -> IntegerInterval -> Maybe (Integer, Integer) infix 4 Source #

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

(==??) :: IntegerInterval -> IntegerInterval -> Maybe (Integer, Integer) infix 4 Source #

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

(>=??) :: IntegerInterval -> IntegerInterval -> Maybe (Integer, Integer) infix 4 Source #

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

(>??) :: IntegerInterval -> IntegerInterval -> Maybe (Integer, Integer) infix 4 Source #

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

(/=??) :: IntegerInterval -> IntegerInterval -> Maybe (Integer, Integer) infix 4 Source #

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

Combine

intersection :: IntegerInterval -> IntegerInterval -> IntegerInterval Source #

intersection of two intervals

intersections :: [IntegerInterval] -> IntegerInterval Source #

intersection of a list of intervals.

hull :: IntegerInterval -> IntegerInterval -> IntegerInterval Source #

convex hull of two intervals

hulls :: [IntegerInterval] -> IntegerInterval Source #

convex hull of a list of intervals.

Map

mapMonotonic :: (Integer -> Integer) -> IntegerInterval -> IntegerInterval Source #

mapMonotonic f i is the image of i under f, where f must be a strict monotone function.

Operations

pickup :: IntegerInterval -> Maybe Integer Source #

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

simplestIntegerWithin :: IntegerInterval -> Maybe Integer Source #

simplestIntegerWithin returns the simplest rational number within the interval.

An integer y is said to be simpler than another y' if

(see also approxRational and simplestRationalWithin)

Conversion

toInterval :: Real r => IntegerInterval -> Interval r Source #

Convert the interval to Interval data type.

fromInterval :: Interval Integer -> IntegerInterval Source #

Conversion from Interval data type.

fromIntervalOver :: RealFrac r => Interval r -> IntegerInterval Source #

Given a Interval I over R, compute the smallest IntegerInterval J such that I ⊆ J.

fromIntervalUnder :: RealFrac r => Interval r -> IntegerInterval Source #

Given a Interval I over R, compute the largest IntegerInterval J such that J ⊆ I.