| Copyright | (c) Masahiro Sakai 2011-2013 Andrew Lelechenko 2020 |
|---|---|
| License | BSD-style |
| Maintainer | masahiro.sakai@gmail.com |
| Stability | provisional |
| Portability | non-portable (CPP, ScopedTypeVariables, DeriveDataTypeable) |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Data.Interval
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
- data Boundary
- interval :: Ord r => (Extended r, Boundary) -> (Extended r, Boundary) -> 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
- isSingleton :: Ord r => Interval r -> Bool
- extractSingleton :: Ord r => Interval r -> Maybe r
- 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, Boundary)
- upperBound' :: Interval r -> (Extended r, Boundary)
- 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 :: Ord r => Interval r -> Interval r -> Interval r
- intersections :: Ord r => [Interval r] -> Interval r
- hull :: 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
- relate :: Ord r => Interval r -> Interval r -> Relation
Interval type
The intervals (i.e. connected and convex subsets) over a type r.
Instances
| (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 :: forall r0 r'. (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) # | |
| (Storable r, Ord r) => Storable (Interval r) Source # | |
Defined in Data.Interval.Internal Methods alignment :: Interval r -> Int # peekElemOff :: Ptr (Interval r) -> Int -> IO (Interval r) # pokeElemOff :: Ptr (Interval r) -> Int -> Interval r -> IO () # peekByteOff :: Ptr b -> Int -> IO (Interval r) # pokeByteOff :: Ptr b -> Int -> Interval r -> IO () # | |
| (RealFrac r, Floating r) => Floating (Interval r) Source # | When results of |
Defined in Data.Interval Methods exp :: Interval r -> Interval r # log :: Interval r -> Interval r # sqrt :: Interval r -> Interval r # (**) :: Interval r -> Interval r -> Interval r # logBase :: Interval r -> Interval r -> Interval r # sin :: Interval r -> Interval r # cos :: Interval r -> Interval r # tan :: Interval r -> Interval r # asin :: Interval r -> Interval r # acos :: Interval r -> Interval r # atan :: Interval r -> Interval r # sinh :: Interval r -> Interval r # cosh :: Interval r -> Interval r # tanh :: Interval r -> Interval r # asinh :: Interval r -> Interval r # acosh :: Interval r -> Interval r # atanh :: Interval r -> Interval r # log1p :: Interval r -> Interval r # expm1 :: Interval r -> Interval r # | |
| (Num r, Ord r) => Num (Interval r) Source # | When results of |
Defined in Data.Interval | |
| (Ord r, Read r) => Read (Interval r) Source # | |
| (Real r, Fractional r) => Fractional (Interval r) Source # |
|
| (Ord r, Show r) => Show (Interval r) Source # | |
| NFData r => NFData (Interval r) Source # | |
Defined in Data.Interval.Internal | |
| Eq r => Eq (Interval r) Source # | |
| Ord r => Ord (Interval r) Source # | Note that this Ord is derived and not semantically meaningful.
The primary intended use case is to allow using |
Defined in Data.Interval.Internal | |
| Hashable r => Hashable (Interval r) Source # | |
Defined in Data.Interval.Internal | |
| Ord r => BoundedJoinSemiLattice (Interval r) Source # | |
Defined in Data.Interval | |
| Ord r => BoundedMeetSemiLattice (Interval r) Source # | |
Defined in Data.Interval | |
| Ord r => Lattice (Interval r) Source # | |
module Data.ExtendedReal
Boundary of an interval may be open (excluding an endpoint) or closed (including an endpoint).
Since: 2.0.0
Instances
| Data Boundary Source # | |
Defined in Data.Interval.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boundary -> c Boundary # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boundary # toConstr :: Boundary -> Constr # dataTypeOf :: Boundary -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boundary) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boundary) # gmapT :: (forall b. Data b => b -> b) -> Boundary -> Boundary # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boundary -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boundary -> r # gmapQ :: (forall d. Data d => d -> u) -> Boundary -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boundary -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boundary -> m Boundary # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boundary -> m Boundary # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boundary -> m Boundary # | |
| Bounded Boundary Source # | |
| Enum Boundary Source # | |
Defined in Data.Interval.Internal | |
| Generic Boundary Source # | |
Defined in Data.Interval.Internal | |
| Read Boundary Source # | |
| Show Boundary Source # | |
| NFData Boundary Source # | |
Defined in Data.Interval.Internal | |
| Eq Boundary Source # | |
| Ord Boundary Source # | |
Defined in Data.Interval.Internal | |
| Hashable Boundary Source # | |
Defined in Data.Interval.Internal | |
| type Rep Boundary Source # | |
Construction
Arguments
| :: Ord r | |
| => (Extended r, Boundary) | lower bound and whether it is included |
| -> (Extended r, Boundary) | 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
extractSingleton :: Ord r => Interval r -> Maybe r Source #
If the interval is a single point, return this point.
Since: 2.1.0
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.
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 :: 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
hulls :: Ord r => [Interval r] -> Interval r Source #
convex hull of a list of intervals.
Since: 0.6.0
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,
preserving negative and positive infinities.
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
Intervals relation
relate :: Ord r => Interval r -> Interval r -> Relation Source #
Computes how two intervals are related according to the classificationRelation