Portability | non-portable (ScopedTypeVariables, DeriveDataTypeable) |
---|---|
Stability | provisional |
Maintainer | masahiro.sakai@gmail.com |
Safe Haskell | Safe-Inferred |
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).
- data Interval r
- data EndPoint r
- interval :: (Ord r, Num r) => (EndPoint r, Bool) -> (EndPoint r, Bool) -> Interval r
- (<=..<=) :: (Ord r, Num r) => EndPoint r -> EndPoint r -> Interval r
- (<..<=) :: (Ord r, Num r) => EndPoint r -> EndPoint r -> Interval r
- (<=..<) :: (Ord r, Num r) => EndPoint r -> EndPoint r -> Interval r
- (<..<) :: (Ord r, Num r) => EndPoint r -> EndPoint r -> Interval r
- whole :: (Num r, Ord r) => Interval r
- empty :: Num r => Interval r
- singleton :: (Num r, Ord r) => r -> Interval r
- null :: Ord r => Interval r -> Bool
- member :: Ord r => r -> Interval r -> Bool
- notMember :: Ord r => r -> Interval r -> Bool
- isSubsetOf :: Ord r => Interval r -> Interval r -> Bool
- isProperSubsetOf :: Ord r => Interval r -> Interval r -> Bool
- lowerBound :: Num r => Interval r -> EndPoint r
- upperBound :: Num r => Interval r -> EndPoint r
- lowerBound' :: Num r => Interval r -> (EndPoint r, Bool)
- upperBound' :: Num r => Interval r -> (EndPoint r, Bool)
- width :: (Num r, Ord r) => Interval r -> r
- (<!) :: Real r => Interval r -> Interval r -> Bool
- (<=!) :: Real r => Interval r -> Interval r -> Bool
- (==!) :: Real r => Interval r -> Interval r -> Bool
- (>=!) :: Real r => Interval r -> Interval r -> Bool
- (>!) :: Real r => Interval r -> Interval r -> Bool
- (<?) :: Real r => Interval r -> Interval r -> Bool
- (<=?) :: Real r => Interval r -> Interval r -> Bool
- (==?) :: Real r => Interval r -> Interval r -> Bool
- (>=?) :: Real r => Interval r -> Interval r -> Bool
- (>?) :: Real r => Interval r -> Interval r -> Bool
- intersection :: forall r. (Ord r, Num r) => Interval r -> Interval r -> Interval r
- intersections :: (Ord r, Num r) => [Interval r] -> Interval r
- hull :: forall r. (Ord r, Num r) => Interval r -> Interval r -> Interval r
- hulls :: (Ord r, Num r) => [Interval r] -> Interval r
- pickup :: (Real r, Fractional r) => Interval r -> Maybe r
- simplestRationalWithin :: RealFrac r => Interval r -> Maybe Rational
Interval type
Interval
Typeable1 Interval | |
Eq r => Eq (Interval r) | |
(Real r, Fractional r) => Fractional (Interval r) | |
(Num r, Ord r, Data r) => Data (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) | |
Hashable r => Hashable (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) |
Endpoints of intervals
Construction
:: (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
closed interval [l
,u
]
left-open right-closed interval (l
,u
]
left-closed right-open interval [l
, u
)
open interval (l
, u
)
Query
isSubsetOf :: Ord r => Interval r -> Interval r -> BoolSource
Is this a subset?
(i1
tells whether isSubsetOf
i2)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.
The result is convenient to use as an argument for interval
.
upperBound' :: Num r => Interval r -> (EndPoint r, Bool)Source
Upper bound 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 -> rSource
Width of a interval. Width of an unbounded interval is undefined
.
Comparison
(<?) :: 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 of two intervals
intersections :: (Ord r, Num r) => [Interval r] -> Interval rSource
intersection of a list of 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.
simplestRationalWithin :: RealFrac r => Interval r -> Maybe RationalSource
simplestRationalWithin
returns the simplest rational number within the interval.
A rational number y
is said to be simpler than another y'
if
-
, andabs
(numerator
y) <=abs
(numerator
y') -
.denominator
y <=denominator
y'
(see also approxRational
)