Copyright | (c) Masahiro Sakai 2011-2013 |
---|---|
License | BSD-style |
Maintainer | masahiro.sakai@gmail.com |
Stability | provisional |
Portability | non-portable (ScopedTypeVariables, DeriveDataTypeable) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- module Data.ExtendedReal
- type EndPoint r = Extended r
- interval :: Ord r => (Extended r, Bool) -> (Extended r, Bool) -> Interval r
- (<=..<=) :: Ord r => Extended r -> Extended r -> Interval r
- (<..<=) :: Ord r => Extended r -> Extended r -> Interval r
- (<=..<) :: Ord r => Extended r -> Extended r -> Interval r
- (<..<) :: Ord r => Extended r -> Extended r -> Interval r
- whole :: Ord r => Interval r
- empty :: Ord r => Interval r
- singleton :: 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 :: Interval r -> Extended r
- upperBound :: Interval r -> Extended r
- lowerBound' :: Interval r -> (Extended r, Bool)
- upperBound' :: Interval r -> (Extended r, Bool)
- width :: (Num r, Ord r) => Interval r -> r
- (<!) :: Ord r => Interval r -> Interval r -> Bool
- (<=!) :: Ord r => Interval r -> Interval r -> Bool
- (==!) :: Ord r => Interval r -> Interval r -> Bool
- (>=!) :: Ord r => Interval r -> Interval r -> Bool
- (>!) :: Ord r => Interval r -> Interval r -> Bool
- (/=!) :: Ord r => Interval r -> Interval r -> Bool
- (<?) :: Ord r => Interval r -> Interval r -> Bool
- (<=?) :: Ord r => Interval r -> Interval r -> Bool
- (==?) :: Ord r => Interval r -> Interval r -> Bool
- (>=?) :: Ord r => Interval r -> Interval r -> Bool
- (>?) :: Ord r => Interval r -> Interval r -> Bool
- (/=?) :: Ord r => Interval r -> Interval r -> Bool
- (<??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r)
- (<=??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r)
- (==??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r)
- (>=??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r)
- (>??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r)
- (/=??) :: (Real r, Fractional r) => Interval r -> Interval r -> Maybe (r, r)
- intersection :: forall r. Ord r => Interval r -> Interval r -> Interval r
- intersections :: Ord r => [Interval r] -> Interval r
- hull :: forall r. Ord r => Interval r -> Interval r -> Interval r
- hulls :: Ord r => [Interval r] -> Interval r
- pickup :: (Real r, Fractional r) => Interval r -> Maybe r
- simplestRationalWithin :: RealFrac r => Interval r -> Maybe Rational
Interval type
The intervals (i.e. connected and convex subsets) over real numbers R.
Eq r => Eq (Interval r) | |
(Real r, Fractional r) => Fractional (Interval r) | |
(Ord r, Data r) => Data (Interval r) | |
(Num r, Ord r) => Num (Interval r) | |
(Ord r, Read r) => Read (Interval r) | |
(Ord r, Show r) => Show (Interval r) | |
NFData r => NFData (Interval r) | |
Hashable r => Hashable (Interval r) | |
Ord r => JoinSemiLattice (Interval r) | |
Ord r => MeetSemiLattice (Interval r) | |
Ord r => Lattice (Interval r) | |
Ord r => BoundedJoinSemiLattice (Interval r) | |
Ord r => BoundedMeetSemiLattice (Interval r) | |
Ord r => BoundedLattice (Interval r) | |
Typeable (* -> *) Interval |
module Data.ExtendedReal
type EndPoint r = Extended r Source
Deprecated: EndPoint is deprecated. Please use Extended instead.
Endpoints of intervals
Construction
:: Ord r | |
=> (Extended r, Bool) | lower bound and whether it is included |
-> (Extended 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 -> Bool Source
Is this a subset?
(i1 `
tells whether isSubsetOf
` i2)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 -> Extended r Source
Lower endpoint (i.e. greatest lower bound) of the interval.
lowerBound
of the empty interval isPosInf
.lowerBound
of a left unbounded interval isNegInf
.lowerBound
of an interval may or may not be a member of the interval.
upperBound :: Interval r -> Extended r Source
Upper endpoint (i.e. least upper bound) of the interval.
upperBound
of the empty interval isNegInf
.upperBound
of a right unbounded interval isPosInf
.upperBound
of an interval may or may not be a member of the interval.
lowerBound' :: Interval r -> (Extended 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 -> (Extended 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 infix 4 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 infix 4 Source
Does there exist an x
in X
, y
in Y
such that x
?<
y
(<=?) :: Ord r => Interval r -> Interval r -> Bool infix 4 Source
Does there exist an x
in X
, y
in Y
such that x
?<=
y
(==?) :: Ord r => Interval r -> Interval r -> Bool infix 4 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 infix 4 Source
Does there exist an x
in X
, y
in Y
such that x
?>=
y
(>?) :: Ord r => Interval r -> Interval r -> Bool infix 4 Source
Does there exist an x
in X
, y
in Y
such that x
?>
y
(/=?) :: Ord r => Interval r -> Interval r -> Bool infix 4 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) infix 4 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) infix 4 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) infix 4 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) infix 4 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) infix 4 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) infix 4 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
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
, andabs
(numerator
y) <=abs
(numerator
y')
.denominator
y <=denominator
y'
(see also approxRational
)
Since 0.4.0