data-interval-0.2.0: Interval Arithmetic

Portabilitynon-portable (ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable)
Stabilityprovisional
Maintainermasahiro.sakai@gmail.com
Safe HaskellSafe-Inferred

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.

Synopsis

Interval type

data Interval r Source

Interval

Instances

Typeable1 Interval 
Eq r => Eq (Interval r) 
(Real r, Fractional r) => Fractional (Interval r) 
(Num r, Ord r) => Num (Interval r) 
(Num r, Ord r, Read r) => Read (Interval r) 
(Num r, Ord r, Show r) => Show (Interval r) 
NFData r => NFData (Interval r) 
(Num r, Ord r) => JoinSemiLattice (Interval r) 
(Num r, Ord r) => MeetSemiLattice (Interval r) 
(Num r, Ord r) => Lattice (Interval r) 
(Num r, Ord r) => BoundedJoinSemiLattice (Interval r) 
(Num r, Ord r) => BoundedMeetSemiLattice (Interval r) 
(Num r, Ord r) => BoundedLattice (Interval r) 

data EndPoint r Source

Endpoints of intervals

Constructors

NegInf

negative infinity (-∞)

Finite !r

finite value

PosInf

positive infinity (+∞)

Instances

Construction

intervalSource

Arguments

:: (Ord r, Num 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, Num r) 
=> EndPoint r

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

closed interval [l,u]

(<..<=)Source

Arguments

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

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

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

(<=..<)Source

Arguments

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

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

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

(<..<)Source

Arguments

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

lower bound l

-> EndPoint r

upper bound u

-> Interval r 

open interval (l, u)

whole :: (Num r, Ord r) => Interval rSource

whole real number line (-∞, ∞)

empty :: Num r => Interval rSource

empty (contradicting) interval

singleton :: (Num r, Ord r) => r -> Interval rSource

singleton set [x,x]

Query

null :: Ord r => Interval r -> BoolSource

Is the interval empty?

member :: Ord r => r -> Interval r -> BoolSource

Is the element in the interval?

notMember :: Ord r => r -> Interval r -> BoolSource

Is the element not in the interval?

isSubsetOf :: Ord r => Interval r -> Interval r -> BoolSource

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

isProperSubsetOf :: Ord r => Interval r -> Interval r -> BoolSource

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

lowerBound :: Num r => Interval r -> EndPoint rSource

Lower bound of the interval

upperBound :: Num r => Interval r -> EndPoint rSource

Upper bound of the interval

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

Lower bound of the interval and whether it is included in the interval

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

Upper bound of the interval and whether it is included in the interval

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

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

Comparison

(<!) :: Real r => Interval r -> Interval r -> BoolSource

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

(<=!) :: Real r => Interval r -> Interval r -> BoolSource

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

(==!) :: Real r => Interval r -> Interval r -> BoolSource

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

(>=!) :: Real r => Interval r -> Interval r -> BoolSource

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

(>!) :: Real r => Interval r -> Interval r -> BoolSource

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

(<?) :: Real r => Interval r -> Interval r -> BoolSource

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

(<=?) :: Real r => Interval r -> Interval r -> BoolSource

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

(==?) :: Real r => Interval r -> Interval r -> BoolSource

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

(>=?) :: Real r => Interval r -> Interval r -> BoolSource

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

(>?) :: Real r => Interval r -> Interval r -> BoolSource

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

Combine

intersection :: forall r. (Ord r, Num r) => Interval r -> Interval r -> Interval rSource

intersection (greatest lower bounds) of two intervals

hull :: forall r. (Ord r, Num r) => Interval r -> Interval r -> Interval rSource

convex hull of two intervals

Operations

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

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