| Copyright | (c) Masahiro Sakai 2011-2013 |
|---|---|
| License | BSD-style |
| Maintainer | masahiro.sakai@gmail.com |
| Stability | provisional |
| Portability | non-portable (CPP, ScopedTypeVariables, DeriveDataTypeable) |
| Safe Haskell | Safe |
| Language | Haskell2010 |
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
- 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
- isConnected :: 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
- mapMonotonic :: (Ord a, Ord b) => (a -> b) -> Interval a -> Interval b
- 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.
Instances
| Eq r => Eq (Interval r) Source # | |
| (Real r, Fractional r) => Fractional (Interval r) Source # | |
| (Ord r, Data r) => Data (Interval r) Source # | |
Defined in Data.Interval.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Interval r -> c (Interval r) # gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (Interval r) # toConstr :: Interval r -> Constr # dataTypeOf :: Interval r -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Interval r)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Interval r)) # gmapT :: (forall b. Data b => b -> b) -> Interval r -> Interval r # gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> Interval r -> r0 # gmapQr :: (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> Interval r -> r0 # gmapQ :: (forall d. Data d => d -> u) -> Interval r -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Interval r -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Interval r -> m (Interval r) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval r -> m (Interval r) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval r -> m (Interval r) # | |
| (Num r, Ord r) => Num (Interval r) Source # | |
Defined in Data.Interval | |
| (Ord r, Read r) => Read (Interval r) Source # | |
| (Ord r, Show r) => Show (Interval r) Source # | |
| NFData r => NFData (Interval r) Source # | |
Defined in Data.Interval.Internal | |
| Hashable r => Hashable (Interval r) Source # | |
Defined in Data.Interval.Internal | |
| Ord r => Lattice (Interval r) Source # | |
| Ord r => BoundedJoinSemiLattice (Interval r) Source # | |
Defined in Data.Interval | |
| Ord r => BoundedMeetSemiLattice (Interval r) Source # | |
Defined in Data.Interval | |
module Data.ExtendedReal
type EndPoint r = Extended r Source #
Deprecated: EndPoint is deprecated. Please use Extended instead.
Endpoints of intervals
Construction
Arguments
| :: 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).
isConnected :: Ord r => Interval r -> Interval r -> Bool Source #
Does the union of two range form a connected set?
Since 1.3.0
lowerBound :: Interval r -> Extended r Source #
Lower endpoint (i.e. greatest lower bound) of the interval.
lowerBoundof the empty interval isPosInf.lowerBoundof a left unbounded interval isNegInf.lowerBoundof 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.
upperBoundof the empty interval isNegInf.upperBoundof a right unbounded interval isPosInf.upperBoundof 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
Map
mapMonotonic :: (Ord a, Ord b) => (a -> b) -> Interval a -> Interval b Source #
mapMonotonic f i is the image of i under f, where f must be a strict monotone function.
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(numeratory) <=abs(numeratory').denominatory <=denominatory'
(see also approxRational)
Since 0.4.0
Orphan instances
| (Real r, Fractional r) => Fractional (Interval r) Source # | |
| (Num r, Ord r) => Num (Interval r) Source # | |
| (Ord r, Read r) => Read (Interval r) Source # | |
| (Ord r, Show r) => Show (Interval r) Source # | |
| Ord r => Lattice (Interval r) Source # | |
| Ord r => BoundedJoinSemiLattice (Interval r) Source # | |
| Ord r => BoundedMeetSemiLattice (Interval r) Source # | |