module Numeric.Interval
(
Interval
, lowerBound
, upperBound
, singleton
, interval
, lowerBounded
, upperBounded
, maxInterval
, difference
, intersect
, merge
, member
, isSingleton
, isInfinite
, hasNegatives
, hasPositives
, contains
, elems
, minValue
, maxValue
, plus
, minus
, times
, div
, abs
, negate
, pretty
) where
import Data.Maybe (isJust)
import Prelude hiding (abs, div, isInfinite, negate)
import qualified Numeric.Bound as B
import Numeric.Distance (Dist)
data Interval a = Interval
{ lowerBound :: B.LowerBound a
, upperBound :: B.UpperBound a
}
deriving (Eq, Show)
singleton :: a -> Interval a
singleton value =
Interval (B.closedLower value) (B.closedUpper value)
interval :: Ord a => B.LowerBound a -> B.UpperBound a -> Maybe (Interval a)
interval lower upper
| lower `B.isAbove` upper = Nothing
| otherwise = Just (Interval lower upper)
lowerBounded :: B.LowerBound a -> Interval a
lowerBounded lb = Interval lb B.infiniteUpper
upperBounded :: B.UpperBound a -> Interval a
upperBounded ub = Interval B.infiniteLower ub
maxInterval :: Interval a
maxInterval = Interval B.infiniteLower B.infiniteUpper
contains :: Ord a => Interval a -> Interval a -> Bool
contains (Interval xl xh) (Interval yl yh) =
xl <= yl && yh <= xh
isInfinite :: Interval a -> Bool
isInfinite iv =
B.isInfiniteLower (lowerBound iv) ||
B.isInfiniteUpper (upperBound iv)
isSingleton :: Eq a => Interval a -> Bool
isSingleton iv =
B.isSingleton (lowerBound iv) (upperBound iv)
hasNegatives :: (Num a, Ord a) => Interval a -> Bool
hasNegatives = B.isNegativeLower . lowerBound
hasPositives :: (Num a, Ord a) => Interval a -> Bool
hasPositives = B.isPositiveUpper . upperBound
member :: Ord a => a -> Interval a -> Bool
member value iv =
B.containsLower value (lowerBound iv) &&
B.containsUpper value (upperBound iv)
elems :: Enum a => Interval a -> Maybe [a]
elems iv = B.elems (lowerBound iv) (upperBound iv)
intersect :: Ord a => Interval a -> Interval a -> Maybe (Interval a)
intersect (Interval xl xh) (Interval yl yh)
| yl `B.isAbove` xh || yh `B.isBelow` xl = Nothing
| otherwise =
Just $ Interval (max xl yl) (min xh yh)
difference :: Dist a => Interval a -> Interval a -> [Interval a]
difference whole@(Interval low high) diff =
case intersect whole diff of
Nothing -> [whole]
Just di ->
let lowInterval = do
adjHigh <- B.adjacentUpper (lowerBound di)
interval low adjHigh
upInterval = do
adjLow <- B.adjacentLower (upperBound di)
interval adjLow high
in
case (lowInterval, upInterval) of
(Just li, Just ui) -> [li, ui]
(Just li, Nothing) -> [li]
(Nothing, Just ui) -> [ui]
(Nothing, Nothing) -> []
merge :: Dist a => Interval a -> Interval a -> Maybe (Interval a)
merge l@(Interval xl xh) r@(Interval yl yh)
| isJust (intersect l r) = Just $ Interval (min xl yl) (max xh yh)
| B.mergeable xh yl = Just $ Interval xl yh
| B.mergeable yh xl = Just $ Interval yl xh
| otherwise = Nothing
maxValue :: Interval a -> Maybe a
maxValue = B.maxValue . upperBound
minValue :: Interval a -> Maybe a
minValue = B.minValue . lowerBound
plus :: Num a => Interval a -> Interval a -> Interval a
plus (Interval xl xh) (Interval yl yh) =
Interval
(xl `B.plusLower` yl)
(xh `B.plusUpper` yh)
minus :: Num a => Interval a -> Interval a -> Interval a
minus (Interval xl xh) (Interval yl yh) =
Interval
(xl `B.minusUpper` yh)
(xh `B.minusLower` yl)
times :: (Num a, Ord a) => Interval a -> Interval a -> Interval a
times (Interval xl xh) (Interval yl yh) =
case result of
(Just low, Just up) -> Interval low up
(Just low, Nothing) -> lowerBounded low
(Nothing , Just up) -> upperBounded up
(Nothing , Nothing) -> maxInterval
where
ll = xl `B.timesLower` yl
lh = xl `B.timesMixed` yh
hl = yl `B.timesMixed` xh
hh = xh `B.timesUpper` yh
temp1 = B.applyResult (Nothing, Nothing) ll
temp2 = B.applyResult temp1 lh
temp3 = B.applyResult temp2 hl
result = B.applyResult temp3 hh
div :: Integral a => Interval a -> Interval a -> Interval a
div (Interval xl xh) r@(Interval yl yh)
| member 0 r = maxInterval
| otherwise =
case result of
(Just low, Just up) -> Interval low up
(Just low, Nothing) -> lowerBounded low
(Nothing , Just up) -> upperBounded up
(Nothing , Nothing) -> maxInterval
where
ll = xl `B.divLower` yl
lh = xl `B.divLowerUpper` yh
hl = xh `B.divUpperLower` yl
hh = xh `B.divUpper` yh
temp1 = B.applyResult (Nothing, Nothing) ll
temp2 = B.applyResult temp1 lh
temp3 = B.applyResult temp2 hl
result = B.applyResult temp3 hh
negate :: Num a => Interval a -> Interval a
negate (Interval low high) =
Interval
(B.negateUpper high)
(B.negateLower low)
abs :: (Num a, Ord a) => Interval a -> Interval a
abs r@(Interval low high)
| B.isNegativeLower low =
Interval
(max (B.closedLower 0) (B.negateUpper high))
(max (B.negateLower low) high)
| otherwise = r
pretty :: Show a => Interval a -> String
pretty (Interval low high) =
B.prettyLower low ++ "," ++ B.prettyUpper high