{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.IntervalMap.Generic.Interval (
Interval(..),
genericEquals, genericCompare
) where
import qualified Data.IntervalMap.Interval as I
class Ord e => Interval i e | i -> e where
lowerBound :: i -> e
upperBound :: i -> e
leftClosed :: i -> Bool
leftClosed _ = True
rightClosed :: i -> Bool
rightClosed _ = True
before :: i -> i -> Bool
a `before` b = upperBound a < lowerBound b
|| (upperBound a == lowerBound b && not (rightClosed a && leftClosed b))
after :: i -> i -> Bool
a `after` b = b `before` a
subsumes :: i -> i -> Bool
a `subsumes` b = (lowerBound a < lowerBound b || (lowerBound a == lowerBound b && (leftClosed a || not (leftClosed b))))
&&
(upperBound a > upperBound b || (upperBound a == upperBound b && (rightClosed a || not (rightClosed b))))
overlaps :: i -> i -> Bool
a `overlaps` b = (lowerBound a < upperBound b || (lowerBound a == upperBound b && leftClosed a && rightClosed b))
&&
(upperBound a > lowerBound b || (upperBound a == lowerBound b && rightClosed a && leftClosed b))
below :: e -> i -> Bool
p `below` i = case compare p (lowerBound i) of
LT -> True
EQ -> not (leftClosed i)
GT -> False
above :: e -> i -> Bool
p `above` i = case compare p (upperBound i) of
LT -> False
EQ -> not (rightClosed i)
GT -> True
inside :: e -> i -> Bool
p `inside` i = not ((p `above` i) || (p `below` i))
isEmpty :: i -> Bool
isEmpty i | leftClosed i && rightClosed i = lowerBound i > upperBound i
| otherwise = lowerBound i >= upperBound i
compareUpperBounds :: i -> i -> Ordering
compareUpperBounds a b = case compare (upperBound a) (upperBound b) of
LT -> LT
GT -> GT
EQ -> case (rightClosed a, rightClosed b) of
(False, True) -> LT
(True, False) -> GT
_ -> EQ
genericEquals :: (Interval i e) => i -> i -> Bool
genericEquals a b = lowerBound a == lowerBound b && upperBound a == upperBound b
&& leftClosed a == leftClosed b
&& rightClosed a == rightClosed b
genericCompare :: (Interval i e) => i -> i -> Ordering
genericCompare a b = case compareL a b of
LT -> LT
GT -> GT
EQ -> compareU a b
compareL :: (Interval i e) => i -> i -> Ordering
compareL a b = case compare (lowerBound a) (lowerBound b) of
LT -> LT
GT -> GT
EQ -> case (leftClosed a, leftClosed b) of
(True, False) -> LT
(False, True) -> GT
_ -> EQ
compareU :: (Interval i e) => i -> i -> Ordering
compareU a b = case compare (upperBound a) (upperBound b) of
LT -> LT
GT -> GT
EQ -> case (rightClosed a, rightClosed b) of
(True, False) -> GT
(False, True) -> LT
_ -> EQ
instance Ord a => Interval (I.Interval a) a where
lowerBound = I.lowerBound
upperBound = I.upperBound
leftClosed = I.leftClosed
rightClosed = I.rightClosed
overlaps = I.overlaps
subsumes = I.subsumes
before = I.before
after = I.after
above = I.above
below = I.below
inside = I.inside
isEmpty = I.isEmpty
compareUpperBounds = I.compareByUpper