1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE TupleSections #-}
5 module Data.Interval where
7 import Control.DeepSeq (NFData(..))
9 import Data.Data (Data(..))
10 import Data.Eq (Eq(..))
11 import Data.Foldable (concat)
12 import Data.Function (($), flip)
13 import Data.Functor (Functor(..))
14 import qualified Data.Functor as Functor
15 import Data.Maybe (Maybe(..))
16 import Data.Ord (Ord(..), Ordering(..))
18 import Data.Typeable (Typeable)
19 import Prelude (Bounded(..), seq)
20 import Text.Show (Show(..))
26 { adherence :: Adherence
28 deriving (Eq, Data, Show, Typeable)
30 instance Functor Limit where
31 fmap f (Limit a x) = Limit a (f x)
32 instance NFData x => NFData (Limit x) where
33 rnf (Limit _a l) = rnf l
35 data Adherence = Out | In
36 deriving (Eq, Data, Show, Typeable)
38 -- | Return given 'Limit' with its 'adherence' set to the opposite one.
39 flip_limit :: Limit x -> Limit x
40 flip_limit (Limit a x) = Limit (case a of { In -> Out; Out -> In }) x
42 -- ** Comparing 'Limit's
44 -- | Compare two 'low' 'Limit's.
45 newtype LL x = LL { unLL :: x }
47 instance Ord x => Ord (LL (Limit x)) where
48 compare (LL x) (LL y) =
49 case compare (limit x) (limit y) of
51 case (adherence x, adherence y) of
57 -- | Compare two 'high' 'Limit's.
58 newtype HH x = HH { unHH :: x }
60 instance Ord x => Ord (HH (Limit x)) where
61 compare (HH x) (HH y) =
62 case compare (limit x) (limit y) of
64 case (adherence x, adherence y) of
74 = Interval (Limit x, Limit x)
75 deriving (Eq, Show, Data, Typeable)
76 instance (NFData x, Ord x) => NFData (Interval x) where
77 rnf (Interval (x, y)) = rnf x `seq` rnf y
79 low :: Ord x => Interval x -> Limit x
80 low (Interval t) = fst t
82 high :: Ord x => Interval x -> Limit x
83 high (Interval t) = snd t
85 -- | Return 'Interval' with given 'low' then 'high' 'Limit's,
86 -- if they form a valid 'Interval'.
87 interval :: Ord x => Limit x -> Limit x -> Maybe (Interval x)
89 case compare_without_adherence x y of
90 LT -> Just $ Interval (x, y)
92 case (adherence x, adherence y) of
93 (In, In) -> Just $ Interval (x, y)
97 -- | Like 'Functor.fmap', but may return 'Nothing', if mapped 'Interval' is not valid.
98 fmap :: (Ord x, Ord y) => (x -> y) -> Interval x -> Maybe (Interval y)
99 fmap f (Interval (il, ih)) = interval (Functor.fmap f il) (Functor.fmap f ih)
101 -- | Like 'Functor.fmap', but only safe if given map preserves 'Ordering'.
102 fmap_unsafe :: (Ord x, Ord y) => (x -> y) -> Interval x -> Interval y
103 fmap_unsafe f (Interval (il, ih)) = Interval (Functor.fmap f il, Functor.fmap f ih)
106 -- | Like 'Functor.fmap', but on 'Limit's,
107 -- and may return 'Nothing', if mapped 'Interval' is not valid.
108 fmap_limits :: (Ord x, Ord y) => (Limit x -> Limit y) -> Interval x -> Maybe (Interval y)
109 fmap_limits f (Interval (il, ih)) = interval (f il) (f ih)
111 -- | Like 'Functor.fmap', but on 'Limit's
112 -- and only safe if given map preserves 'Ordering'.
113 fmap_limits_unsafe :: (Ord x, Ord y) => (Limit x -> Limit y) -> Interval x -> Interval y
114 fmap_limits_unsafe f (Interval (il, ih)) = Interval (f il, f ih)
117 -- | Lexicographical order, handling 'Adherence' correctly.
118 instance Ord x => Ord (Interval x) where
119 compare (Interval (il, ih)) (Interval (jl, jh)) =
120 case compare (LL il) (LL jl) of
121 EQ -> compare (HH ih) (HH jh)
124 -- | Return 'limit's of given 'Interval' as a tuple.
125 limits :: Ord x => Interval x -> (Limit x, Limit x)
126 limits (Interval t) = t
128 -- | Return an 'Interval' spanning over a single 'limit'.
129 point :: Ord x => x -> Interval x
130 point x = Interval (Limit In x, Limit In x)
132 -- | Return given 'Interval' with 'flip_limit' applied to its 'limit's.
133 flip_limits :: Ord x => Interval x -> Interval x
134 flip_limits (Interval (l, h)) = Interval (flip_limit l, flip_limit h)
136 -- | Return 'Ordering' comparing given 'Interval's according to their 'limit's.
137 compare_without_adherence :: Ord x => Limit x -> Limit x -> Ordering
138 compare_without_adherence (Limit _ x) (Limit _ y) = compare x y
142 -- * 'LT': if given value is lower than all values in given 'Interval'.
143 -- * 'EQ': if given value is into the given 'Interval'.
144 -- * 'GT': if given value is higher than all values in given 'Interval'.
145 locate :: Ord x => x -> Interval x -> Ordering
146 locate x (Interval (l, h)) =
147 case compare x (limit l) of
149 EQ | adherence l == In -> EQ
152 case compare x (limit h) of
154 EQ | adherence h == In -> EQ
158 -- | Return 'True' iif. given value is into the given 'Interval'.
159 within :: Ord x => x -> Interval x -> Bool
160 within x i = locate x i == EQ
162 -- | Return 'True' iif. every value of the first 'Interval' is into the second 'Interval'.
163 into :: Ord x => Interval x -> Interval x -> Bool
166 (Prefix , LT) -> True
167 (Suffixed, GT) -> True
168 (Include , GT) -> True
172 -- | Return 'True' iif. every value of the second 'Interval' is into the first 'Interval'.
173 onto :: Ord x => Interval x -> Interval x -> Bool
177 (<=..<=) :: Ord x => x -> x -> Maybe (Interval x)
180 LT -> Just $ Interval (Limit In x, Limit In y)
181 EQ -> Just $ Interval (Limit In x, Limit In y)
185 (<..<=) :: Ord x => x -> x -> Maybe (Interval x)
188 LT -> Just $ Interval (Limit Out x, Limit In y)
193 (<=..<) :: Ord x => x -> x -> Maybe (Interval x)
196 LT -> Just $ Interval (Limit In x, Limit Out y)
201 (<..<) :: Ord x => x -> x -> Maybe (Interval x)
204 LT -> Just $ Interval (Limit Out x, Limit Out y)
211 = Away -- ^ @-_|@ ('LT') or @|_-@ ('GT')
212 | Adjacent -- ^ @-|@ ('LT') or @|-@ ('GT')
213 | Overlap -- ^ @-+|@ ('LT') or @|+-@ ('GT')
214 | Prefix -- ^ @+|@ ('LT') or @+-@ ('GT')
215 | Suffixed -- ^ @-+@ ('LT') or @|+@ ('GT')
216 | Include -- ^ @-+-@ ('LT') or @|+|@ ('GT')
217 | Equal -- ^ @+@ ('EQ')
220 position :: Ord x => Interval x -> Interval x -> (Position, Ordering)
221 position (Interval (il, ih)) (Interval (jl, jh)) =
222 case compare (LL il) (LL jl) of
224 case compare_without_adherence ih jl of
225 LT -> Away -- PATTERN: -_|
227 case (adherence ih, adherence jl) of
228 (In , In) -> Overlap -- PATTERN: -+|
229 (Out, Out) -> Away -- PATTERN: -_|
230 _ -> Adjacent -- PATTERN: -|
232 case compare (HH ih) (HH jh) of
233 LT -> Overlap -- PATTERN: -+|
234 EQ -> Suffixed -- PATTERN: -+
235 GT -> Include -- PATTERN: -+-
237 case compare (HH ih) (HH jh) of
238 LT -> (Prefix, LT) -- PATTERN: +|
239 EQ -> (Equal , EQ) -- PATTERN: +
240 GT -> (Prefix, GT) -- PATTERN: +-
242 case compare_without_adherence il jh of
244 case compare (HH ih) (HH jh) of
245 LT -> Include -- PATTERN: |+|
246 EQ -> Suffixed -- PATTERN: |+
247 GT -> Overlap -- PATTERN: |+-
249 case (adherence il, adherence jh) of
250 (In , In) -> Overlap -- PATTERN: |+-
251 (Out, Out) -> Away -- PATTERN: |_-
252 _ -> Adjacent -- PATTERN: |-
253 GT -> Away -- PATTERN: |_-
256 -- | Return 'True' iif. 'Position' of given 'Interval's is ('Away', 'LT').
257 (..<<..) :: Ord x => Interval x -> Interval x -> Bool
258 (..<<..) i j = case position i j of
263 -- | Return 'True' iif. 'Position' of given 'Interval's is ('Away', 'GT').
264 (..>>..) :: Ord x => Interval x -> Interval x -> Bool
265 (..>>..) i j = case position i j of
270 -- | Return 'True' iif. 'Position' of given 'Interval's is ('Away', 'LT') or ('Adjacent', 'LT').
271 (..<..) :: Ord x => Interval x -> Interval x -> Bool
272 (..<..) i j = case position i j of
274 (Adjacent, LT) -> True
277 -- | Return 'True' iif. 'Position' of given 'Interval's is ('Away', 'GT') or ('Adjacent', 'GT').
278 (..>..) :: Ord x => Interval x -> Interval x -> Bool
279 (..>..) i j = case position i j of
281 (Adjacent, GT) -> True
285 -- | Return 'True' iif. 'Position' of given 'Interval's is ('Away', 'LT'), ('Adjacent', 'LT'), ('Overlap', 'LT'), ('Prefix', 'LT'), ('Suffixed', 'LT'), ('Include', 'GT'), or ('Equal', _).
286 (..<=..) :: Ord x => Interval x -> Interval x -> Bool
287 (..<=..) i j = case position i j of
289 (Adjacent, LT) -> True
290 (Overlap , LT) -> True
291 (Prefix , LT) -> True
292 (Suffixed, LT) -> True
293 (Include , GT) -> True
298 -- | Return 'True' iif. 'Position' of given 'Interval's is ('Away', 'GT'), ('Adjacent', 'GT'), ('Overlap', 'GT'), ('Prefix', 'GT'), ('Suffixed', 'GT'), ('Include', 'LT'), or ('Equal', _).
299 (..>=..) :: Ord x => Interval x -> Interval x -> Bool
300 (..>=..) i j = case position i j of
302 (Adjacent, GT) -> True
303 (Overlap , GT) -> True
304 (Prefix , GT) -> True
305 (Suffixed, GT) -> True
306 (Include , LT) -> True
312 union :: Ord x => Interval x -> Interval x -> Maybe (Interval x)
315 (Away, _) -> -- PATTERN: -_| or |_-
319 LT -> Just $ Interval (low i, high j) -- PATTERN: -|
321 GT -> Just $ Interval (low j, high i) -- PATTERN: |-
324 LT -> Just $ Interval (low i, high j) -- PATTERN: -+|
326 GT -> Just $ Interval (low j, high i) -- PATTERN: |+-
329 LT -> Just j -- PATTERN: +|
331 GT -> Just i -- PATTERN: +-
334 LT -> Just i -- PATTERN: -+
336 GT -> Just j -- PATTERN: |+
339 LT -> Just i -- PATTERN: -+-
341 GT -> Just j -- PATTERN: |+|
342 (Equal, _) -> -- PATTERN: +
345 intersection :: Ord x => Interval x -> Interval x -> Maybe (Interval x)
348 (Away, _) -> -- PATTERN: -_| or |_-
350 (Adjacent, _) -> -- PATTERN: -| or |-
354 LT -> Just $ Interval (low j, high i) -- PATTERN: -+|
356 GT -> Just $ Interval (low i, high j) -- PATTERN: |+-
359 LT -> Just i -- PATTERN: +|
361 GT -> Just j -- PATTERN: +-
364 LT -> Just j -- PATTERN: -+
366 GT -> Just i -- PATTERN: |+
369 LT -> Just j -- PATTERN: -+-
371 GT -> Just i -- PATTERN: |+|
372 (Equal, _) -> -- PATTERN: +
375 span :: Ord x => Interval x -> Interval x -> Interval x
378 ( unLL (min (LL $ low i) (LL $ low j))
379 , unHH (max (HH $ high i) (HH $ high j))
382 -- * Type 'Unlimitable'
386 | Limited { limited :: x }
388 deriving (Eq, Ord, Show)
389 instance Functor Unlimitable where
390 fmap _f Unlimited_low = Unlimited_low
391 fmap _f Unlimited_high = Unlimited_high
392 fmap f (Limited x) = Limited (f x)
393 instance Bounded (Unlimitable x) where
394 minBound = Unlimited_low
395 maxBound = Unlimited_high
396 instance Bounded (Limit (Unlimitable x)) where
397 minBound = Limit In Unlimited_low
398 maxBound = Limit In Unlimited_high
400 unlimited :: Ord x => Interval (Unlimitable x)
401 unlimited = Interval ( Limit In Unlimited_low
402 , Limit In Unlimited_high )
404 unlimit :: Ord x => Interval x -> Interval (Unlimitable x)
405 unlimit = fmap_unsafe Limited
407 (<..) :: Ord x => x -> Interval (Unlimitable x)
408 (<..) x = Interval (Limit Out (Limited x), Limit In Unlimited_high)
410 (<=..) :: Ord x => x -> Interval (Unlimitable x)
411 (<=..) x = Interval (Limit In (Limited x), Limit In Unlimited_high)
413 (..<) :: Ord x => x -> Interval (Unlimitable x)
414 (..<) x = Interval (Limit In Unlimited_low, Limit Out (Limited x))
416 (..<=) :: Ord x => x -> Interval (Unlimitable x)
417 (..<=) x = Interval (Limit In Unlimited_low, Limit In (Limited x))
421 newtype Pretty x = Pretty x
423 instance (Ord x, Show x) => Show (Pretty (Interval x)) where
426 [ case adherence (low i) of
429 , show (limit $ low i)
431 , show (limit $ high i)
432 , case adherence (high i) of
436 instance (Ord x, Show x) => Show (Pretty (Unlimitable x)) where
439 Unlimited_low -> "-oo"
441 Unlimited_high -> "+oo"