• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

msakai / data-interval / 77

07 Jun 2025 02:32PM UTC coverage: 86.702% (+0.1%) from 86.572%
77

push

github

Bodigrim
Drop support of GHC < 8.6

991 of 1143 relevant lines covered (86.7%)

0.87 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

82.93
/src/Data/IntervalMap/Base.hs
1
{-# OPTIONS_GHC -Wall #-}
2
{-# LANGUAGE CPP, LambdaCase, ScopedTypeVariables, TypeFamilies, DeriveDataTypeable, MultiWayIf, GeneralizedNewtypeDeriving #-}
3
{-# LANGUAGE Trustworthy #-}
4
{-# LANGUAGE RoleAnnotations #-}
5
-----------------------------------------------------------------------------
6
-- |
7
-- Module      :  Data.IntervalMap.Base
8
-- Copyright   :  (c) Masahiro Sakai 2016
9
-- License     :  BSD-style
10
--
11
-- Maintainer  :  masahiro.sakai@gmail.com
12
-- Stability   :  provisional
13
-- Portability :  non-portable (CPP, ScopedTypeVariables, TypeFamilies, DeriveDataTypeable, MultiWayIf, GeneralizedNewtypeDeriving)
14
--
15
-- Interval datatype and interval arithmetic.
16
--
17
-----------------------------------------------------------------------------
18
module Data.IntervalMap.Base
19
  (
20
  -- * IntervalMap type
21
    IntervalMap (..)
22
  , module Data.ExtendedReal
23

24
  -- * Operators
25
  , (!)
26
  , (\\)
27

28
  -- * Query
29
  , null
30
  , member
31
  , notMember
32
  , lookup
33
  , findWithDefault
34
  , span
35

36
  -- * Construction
37
  , whole
38
  , empty
39
  , singleton
40

41
  -- ** Insertion
42
  , insert
43
  , insertWith
44

45
  -- ** Delete\/Update
46
  , delete
47
  , adjust
48
  , update
49
  , alter
50

51
  -- * Combine
52
  , union
53
  , unionWith
54
  , unions
55
  , unionsWith
56
  , intersection
57
  , intersectionWith
58
  , difference
59

60
  -- * Traversal
61
  , map
62
  , mapKeysMonotonic
63

64
  -- * Conversion
65
  , elems
66
  , keys
67
  , assocs
68
  , keysSet
69

70
  -- ** List
71
  , fromList
72
  , fromListWith
73
  , toList
74

75
  -- ** Ordered List
76
  , toAscList
77
  , toDescList
78

79
  -- * Filter
80
  , filter
81
  , split
82

83
  -- * Submap
84
  , isSubmapOf
85
  , isSubmapOfBy
86
  , isProperSubmapOf
87
  , isProperSubmapOfBy
88
  )
89
  where
90

91
import Prelude hiding (null, lookup, map, filter, span, and)
92
import Control.DeepSeq
93
import Data.Data
94
import Data.ExtendedReal
95
import Data.Hashable
96
import Data.Foldable hiding (null, toList)
97
import Data.Map (Map)
98
import qualified Data.Map as Map
99
import Data.Maybe
100
import qualified Data.Semigroup as Semigroup
101
import Data.Interval (Interval)
102
import qualified Data.Interval as Interval
103
import Data.IntervalSet (IntervalSet)
104
import qualified Data.IntervalSet as IntervalSet
105
import qualified GHC.Exts as GHCExts
106

107
-- ------------------------------------------------------------------------
108
-- The IntervalMap type
109

110
-- | A Map from non-empty, disjoint intervals over k to values a.
111
--
112
-- Unlike 'IntervalSet', 'IntervalMap' never merge adjacent mappings,
113
-- even if adjacent intervals are connected and mapped to the same value.
114
newtype IntervalMap r a = IntervalMap (Map (LB r) (Interval r, a))
115
  deriving
116
    ( Eq
×
117
    , Ord
×
118
      -- ^ Note that this Ord is derived and not semantically meaningful.
119
      -- The primary intended use case is to allow using 'IntervalSet'
120
      -- in maps and sets that require ordering.
121
    , Typeable
122
    )
123

124
type role IntervalMap nominal representational
125

126
instance (Ord k, Show k, Show a) => Show (IntervalMap k a) where
127
  showsPrec p (IntervalMap m) = showParen (p > appPrec) $
1✔
128
    showString "fromList " .
1✔
129
    showsPrec (appPrec+1) (Map.elems m)
×
130

131
instance (Ord k, Read k, Read a) => Read (IntervalMap k a) where
132
  readsPrec p =
1✔
133
    (readParen (p > appPrec) $ \s0 -> do
1✔
134
      ("fromList",s1) <- lex s0
1✔
135
      (xs,s2) <- readsPrec (appPrec+1) s1
×
136
      return (fromList xs, s2))
1✔
137

138
appPrec :: Int
139
appPrec = 10
1✔
140

141
-- This instance preserves data abstraction at the cost of inefficiency.
142
-- We provide limited reflection services for the sake of data abstraction.
143

144
instance (Data k, Data a, Ord k) => Data (IntervalMap k a) where
145
  gfoldl k z x   = z fromList `k` toList x
1✔
146
  toConstr _     = fromListConstr
×
147
  gunfold k z c  = case constrIndex c of
×
148
    1 -> k (z fromList)
×
149
    _ -> error "gunfold"
×
150
  dataTypeOf _   = mapDataType
×
151
  dataCast1 f    = gcast1 f
×
152

153
fromListConstr :: Constr
154
fromListConstr = mkConstr mapDataType "fromList" [] Prefix
×
155

156
mapDataType :: DataType
157
mapDataType = mkDataType "Data.IntervalMap.Base.IntervalMap" [fromListConstr]
×
158

159
instance (NFData k, NFData a) => NFData (IntervalMap k a) where
160
  rnf (IntervalMap m) = rnf m
1✔
161

162
instance (Hashable k, Hashable a) => Hashable (IntervalMap k a) where
163
  hashWithSalt s m = hashWithSalt s (toList m)
1✔
164

165
instance Ord k => Monoid (IntervalMap k a) where
166
  mempty = empty
×
167
  mappend = (Semigroup.<>)
×
168
  mconcat = unions
×
169

170
instance Ord k => Semigroup.Semigroup (IntervalMap k a) where
171
  (<>)   = union
1✔
172
  stimes = Semigroup.stimesIdempotentMonoid
×
173

174
instance Ord k => GHCExts.IsList (IntervalMap k a) where
175
  type Item (IntervalMap k a) = (Interval k, a)
176
  fromList = fromList
×
177
  toList = toList
×
178

179
-- ------------------------------------------------------------------------
180

181
newtype LB r = LB (Extended r, Interval.Boundary)
182
  deriving (Eq, NFData, Typeable)
×
183

184
instance Ord r => Ord (LB r) where
185
  compare (LB (lb1, lb1in)) (LB (lb2, lb2in)) =
1✔
186
    -- inclusive lower endpoint shuold be considered smaller
187
    (lb1 `compare` lb2) `mappend` (lb2in `compare` lb1in)
1✔
188

189
-- ------------------------------------------------------------------------
190
-- Operators
191

192
infixl 9 !,\\ --
193

194
-- | Find the value at a key. Calls 'error' when the element can not be found.
195
(!) :: Ord k => IntervalMap k a -> k -> a
196
IntervalMap m ! k =
1✔
197
  case Map.lookupLE (LB (Finite k, Interval.Closed)) m of
1✔
198
    Just (_, (i, a)) | k `Interval.member` i -> a
×
199
    _ -> error "IntervalMap.!: given key is not an element in the map"
×
200

201
-- | Same as 'difference'.
202
(\\) :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k a
203
m1 \\ m2 = difference m1 m2
1✔
204

205
-- ------------------------------------------------------------------------
206
-- Query
207

208
-- | Is the map empty?
209
null :: Ord k => IntervalMap k a -> Bool
210
null (IntervalMap m) = Map.null m
1✔
211

212
-- | Is the key a member of the map? See also 'notMember'.
213
member :: Ord k => k -> IntervalMap k a -> Bool
214
member k (IntervalMap m) =
1✔
215
  case Map.lookupLE (LB (Finite k, Interval.Closed)) m of
1✔
216
    Just (_, (i, _)) -> k `Interval.member` i
1✔
217
    Nothing -> False
1✔
218

219
-- | Is the key not a member of the map? See also 'member'.
220
notMember :: Ord k => k -> IntervalMap k a -> Bool
221
notMember k m = not $ member k m
1✔
222

223
-- | Lookup the value at a key in the map.
224
--
225
-- The function will return the corresponding value as @('Just' value)@,
226
-- or 'Nothing' if the key isn't in the map.
227
lookup :: Ord k => k -> IntervalMap k a -> Maybe a
228
lookup k (IntervalMap m) =
1✔
229
  case Map.lookupLE (LB (Finite k, Interval.Closed)) m of
1✔
230
    Just (_, (i, a)) | k `Interval.member` i -> Just a
1✔
231
    _ -> Nothing
1✔
232

233
-- | The expression @('findWithDefault' def k map)@ returns
234
-- the value at key @k@ or returns default value @def@
235
-- when the key is not in the map.
236
findWithDefault :: Ord k => a -> k -> IntervalMap k a -> a
237
findWithDefault def k (IntervalMap m) =
1✔
238
  case Map.lookupLE (LB (Finite k, Interval.Closed)) m of
1✔
239
    Just (_, (i, a)) | k `Interval.member` i -> a
1✔
240
    _ -> def
1✔
241

242
lookupInterval :: Ord k => Interval k -> IntervalMap k a -> Maybe a
243
lookupInterval i (IntervalMap m) =
1✔
244
  case Map.lookupLE (LB (Interval.lowerBound' i)) m of
1✔
245
    Just (_, (j, a)) | i `Interval.isSubsetOf` j -> Just a
1✔
246
    _ -> Nothing
1✔
247

248
-- | convex hull of key intervals.
249
span :: Ord k => IntervalMap k a -> Interval k
250
span = IntervalSet.span . keysSet
1✔
251

252
-- ------------------------------------------------------------------------
253
-- Construction
254

255
-- | The empty map.
256
empty :: Ord k => IntervalMap k a
257
empty = IntervalMap Map.empty
1✔
258

259
-- | The map that maps whole range of k to a.
260
whole :: Ord k => a -> IntervalMap k a
261
whole a = IntervalMap $ Map.singleton (LB (Interval.lowerBound' i)) (i, a)
1✔
262
  where
263
    i = Interval.whole
1✔
264

265
-- | A map with a single interval.
266
singleton :: Ord k => Interval k -> a -> IntervalMap k a
267
singleton i a
1✔
268
  | Interval.null i = empty
1✔
269
  | otherwise = IntervalMap $ Map.singleton (LB (Interval.lowerBound' i)) (i, a)
1✔
270

271
-- ------------------------------------------------------------------------
272
-- Insertion
273

274
-- | insert a new key and value in the map.
275
-- If the key is already present in the map, the associated value is
276
-- replaced with the supplied value.
277
insert :: Ord k => Interval k -> a -> IntervalMap k a -> IntervalMap k a
278
insert i _ m | Interval.null i = m
1✔
279
insert i a m =
280
  case split i m of
1✔
281
    (IntervalMap m1, _, IntervalMap m2) ->
282
      IntervalMap $ Map.union m1 (Map.insert (LB (Interval.lowerBound' i)) (i,a) m2)
1✔
283

284

285
-- | Insert with a function, combining new value and old value.
286
-- @'insertWith' f key value mp@ will insert the pair (interval, value) into @mp@.
287
-- If the interval overlaps with existing entries, the value for the entry is replace
288
-- with @(f new_value old_value)@.
289
insertWith :: Ord k => (a -> a -> a) -> Interval k -> a -> IntervalMap k a -> IntervalMap k a
290
insertWith _ i _ m | Interval.null i = m
1✔
291
insertWith f i a m = alter g i m
1✔
292
  where
293
    g Nothing = Just a
1✔
294
    g (Just a') = Just $ f a a'
1✔
295

296
-- ------------------------------------------------------------------------
297
-- Delete/Update
298

299
-- | Delete an interval and its value from the map.
300
-- When the interval does not overlap with the map, the original map is returned.
301
delete :: Ord k => Interval k -> IntervalMap k a -> IntervalMap k a
302
delete i m | Interval.null i = m
1✔
303
delete i m =
304
  case split i m of
1✔
305
    (IntervalMap m1, _, IntervalMap m2) ->
306
      IntervalMap $ Map.union m1 m2
1✔
307

308
-- | Update a value at a specific interval with the result of the provided function.
309
-- When the interval does not overlatp with the map, the original map is returned.
310
adjust :: Ord k => (a -> a) -> Interval k -> IntervalMap k a -> IntervalMap k a
311
adjust f = update (Just . f)
1✔
312

313
-- | The expression (@'update' f i map@) updates the value @x@
314
-- at @i@ (if it is in the map). If (@f x@) is 'Nothing', the element is
315
-- deleted. If it is (@'Just' y@), the key @i@ is bound to the new value @y@.
316
update :: Ord k => (a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k a
317
update _ i m | Interval.null i = m
1✔
318
update f i m =
319
  case split i m of
1✔
320
    (IntervalMap m1, IntervalMap m2, IntervalMap m3) ->
321
      IntervalMap $ Map.unions [m1, Map.mapMaybe (\(j,a) -> (\b -> (j,b)) <$> f a) m2, m3]
1✔
322

323
-- | The expression (@'alter' f i map@) alters the value @x@ at @i@, or absence thereof.
324
-- 'alter' can be used to insert, delete, or update a value in a 'IntervalMap'.
325
alter :: Ord k => (Maybe a -> Maybe a) -> Interval k -> IntervalMap k a -> IntervalMap k a
326
alter _ i m | Interval.null i = m
1✔
327
alter f i m =
328
  case split i m of
1✔
329
    (IntervalMap m1, IntervalMap m2, IntervalMap m3) ->
330
      let m2' = Map.mapMaybe (\(j,a) -> (\b -> (j,b)) <$> f (Just a)) m2
1✔
331
          js = IntervalSet.singleton i `IntervalSet.difference` keysSet (IntervalMap m2)
1✔
332
          IntervalMap m2'' =
333
            case f Nothing of
1✔
334
              Nothing -> empty
1✔
335
              Just a -> fromList [(j,a) | j <- IntervalSet.toList js]
1✔
336
      in IntervalMap $ Map.unions [m1, m2', m2'', m3]
1✔
337

338
-- ------------------------------------------------------------------------
339
-- Combine
340

341
-- | The expression (@'union' t1 t2@) takes the left-biased union of @t1@ and @t2@.
342
-- It prefers @t1@ when overlapping keys are encountered,
343
union :: Ord k => IntervalMap k a -> IntervalMap k a -> IntervalMap k a
344
union m1 m2 =
1✔
345
  foldl' (\m (i,a) -> insert i a m) m2 (toList m1)
1✔
346

347
-- | Union with a combining function.
348
unionWith :: Ord k => (a -> a -> a) -> IntervalMap k a -> IntervalMap k a -> IntervalMap k a
349
unionWith f m1 m2 =
1✔
350
  foldl' (\m (i,a) -> insertWith f i a m) m2 (toList m1)
1✔
351

352
-- | The union of a list of maps:
353
--   (@'unions' == 'Prelude.foldl' 'union' 'empty'@).
354
unions :: Ord k => [IntervalMap k a] -> IntervalMap k a
355
unions = foldl' union empty
1✔
356

357
-- | The union of a list of maps, with a combining operation:
358
--   (@'unionsWith' f == 'Prelude.foldl' ('unionWith' f) 'empty'@).
359
unionsWith :: Ord k => (a -> a -> a) -> [IntervalMap k a] -> IntervalMap k a
360
unionsWith f = foldl' (unionWith f) empty
×
361

362
-- | Return elements of the first map not existing in the second map.
363
difference :: Ord k => IntervalMap k a -> IntervalMap k b -> IntervalMap k a
364
difference m1 m2 = foldl' (\m i -> delete i m) m1 (IntervalSet.toList (keysSet m2))
1✔
365

366
-- | Intersection of two maps.
367
-- Return data in the first map for the keys existing in both maps.
368
intersection :: Ord k => IntervalMap k a -> IntervalMap k a -> IntervalMap k a
369
intersection = intersectionWith const
1✔
370

371
-- | Intersection with a combining function.
372
intersectionWith :: Ord k => (a -> b -> c) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k c
373
intersectionWith f im1@(IntervalMap m1) im2@(IntervalMap m2)
1✔
374
  | Map.size m1 >= Map.size m2 = g f im1 im2
1✔
375
  | otherwise = g (flip f) im2 im1
1✔
376
  where
377
    g :: Ord k => (a -> b -> c) -> IntervalMap k a -> IntervalMap k b -> IntervalMap k c
378
    g h jm1 (IntervalMap m3) = IntervalMap $ Map.unions $ go jm1 (Map.elems m3)
1✔
379
      where
380
        go _ [] = []
1✔
381
        go im ((i,b) : xs) =
382
          case split i im of
1✔
383
            (_, IntervalMap m, jm2) ->
384
              Map.map (\(j, a) -> (j, h a b)) m : go jm2 xs
1✔
385

386
-- ------------------------------------------------------------------------
387
-- Traversal
388

389
instance Ord k => Functor (IntervalMap k) where
390
  fmap = map
1✔
391

392
instance Ord k => Foldable (IntervalMap k) where
393
  foldMap f (IntervalMap m) = foldMap (\(_,a) -> f a) m
1✔
394

395
instance Ord k => Traversable (IntervalMap k) where
396
  traverse f (IntervalMap m) = IntervalMap <$> traverse (\(i,a) -> (\b -> (i,b)) <$> f a) m
1✔
397

398
-- | Map a function over all values in the map.
399
map :: (a -> b) -> IntervalMap k a -> IntervalMap k b
400
map f (IntervalMap m) = IntervalMap $ Map.map (\(i, a) -> (i, f a)) m
1✔
401

402
-- | @'mapKeysMonotonic' f s@ is the map obtained by applying @f@ to each key of @s@.
403
-- @f@ must be strictly monotonic.
404
-- That is, for any values @x@ and @y@, if @x@ < @y@ then @f x@ < @f y@.
405
mapKeysMonotonic :: forall k1 k2 a. (Ord k1, Ord k2) => (k1 -> k2) -> IntervalMap k1 a -> IntervalMap k2 a
406
mapKeysMonotonic f = fromList . fmap g . toList
1✔
407
  where
408
    g :: (Interval k1, a) -> (Interval k2, a)
409
    g (i, a) = (Interval.mapMonotonic f i, a)
1✔
410

411
-- ------------------------------------------------------------------------
412

413
-- | Return all elements of the map in the ascending order of their keys.
414
elems :: IntervalMap k a -> [a]
415
elems (IntervalMap m) = [a | (_,a) <- Map.elems m]
×
416

417
-- | Return all keys of the map in ascending order. Subject to list
418
keys :: IntervalMap k a -> [Interval k]
419
keys (IntervalMap m) = [i | (i,_) <- Map.elems m]
1✔
420

421
-- | An alias for 'toAscList'. Return all key\/value pairs in the map
422
-- in ascending key order.
423
assocs :: IntervalMap k a -> [(Interval k, a)]
424
assocs = toAscList
×
425

426
-- | The set of all keys of the map.
427
keysSet :: Ord k => IntervalMap k a -> IntervalSet k
428
keysSet (IntervalMap m) = IntervalSet.fromAscList [i | (i,_) <- Map.elems m]
1✔
429

430
-- | Convert the map to a list of key\/value pairs.
431
toList :: IntervalMap k a -> [(Interval k, a)]
432
toList = toAscList
1✔
433

434
-- | Convert the map to a list of key/value pairs where the keys are in ascending order.
435
toAscList :: IntervalMap k a -> [(Interval k, a)]
436
toAscList (IntervalMap m) = Map.elems m
1✔
437

438
-- | Convert the map to a list of key/value pairs where the keys are in descending order.
439
toDescList :: IntervalMap k a -> [(Interval k, a)]
440
toDescList (IntervalMap m) = fmap snd $ Map.toDescList m
1✔
441

442
-- | Build a map from a list of key\/value pairs.
443
-- If the list contains more than one value for the same key, the last value
444
-- for the key is retained.
445
fromList :: Ord k => [(Interval k, a)] -> IntervalMap k a
446
fromList = foldl' (\m (i,a) -> insert i a m) empty
1✔
447

448
-- | Build a map from a list of key\/value pairs with a combining function.
449
fromListWith :: Ord k => (a -> a -> a) -> [(Interval k, a)] -> IntervalMap k a
450
fromListWith f = foldl' (\m (i,a) -> insertWith f i a m) empty
1✔
451

452
-- ------------------------------------------------------------------------
453
-- Filter
454

455
-- | Filter all values that satisfy some predicate.
456
filter :: Ord k => (a -> Bool) -> IntervalMap k a -> IntervalMap k a
457
filter p (IntervalMap m) = IntervalMap $ Map.filter (\(_,a) -> p a) m
1✔
458

459
-- | The expression (@'split' i map@) is a triple @(map1,map2,map3)@ where
460
-- the keys in @map1@ are smaller than @i@, the keys in @map2@ are included in @i@, and the keys in @map3@ are larger than @i@.
461
split :: Ord k => Interval k -> IntervalMap k a -> (IntervalMap k a, IntervalMap k a, IntervalMap k a)
462
split i (IntervalMap m) =
1✔
463
  case splitLookupLE (LB (Interval.lowerBound' i)) m of
1✔
464
    (smaller, m1, xs) ->
465
      case splitLookupLE (LB (Interval.upperBound i, Interval.Closed)) xs of
1✔
466
        (middle, m2, larger) ->
467
          ( IntervalMap $
1✔
468
              case m1 of
1✔
469
                Nothing -> Map.empty
1✔
470
                Just (j,b) ->
471
                  let k = Interval.intersection (upTo i) j
1✔
472
                  in if Interval.null k
1✔
473
                     then smaller
1✔
474
                     else Map.insert (LB (Interval.lowerBound' k)) (k,b) smaller
1✔
475
          , IntervalMap $ Map.unions $ middle :
1✔
476
              [ Map.singleton (LB (Interval.lowerBound' k)) (k, b)
1✔
477
              | (j, b) <- maybeToList m1 ++ maybeToList m2
1✔
478
              , let k = Interval.intersection i j
1✔
479
              , not (Interval.null k)
1✔
480
              ]
481
          , IntervalMap $ Map.unions $ larger :
1✔
482
              [ Map.singleton (LB (Interval.lowerBound' k)) (k, b)
1✔
483
              | (j, b) <- maybeToList m1 ++ maybeToList m2
1✔
484
              , let k = Interval.intersection (downTo i) j
1✔
485
              , not (Interval.null k)
1✔
486
              ]
487
          )
488

489
-- ------------------------------------------------------------------------
490
-- Submap
491

492
-- | This function is defined as (@'isSubmapOf' = 'isSubmapOfBy' (==)@).
493
isSubmapOf :: (Ord k, Eq a) => IntervalMap k a -> IntervalMap k a -> Bool
494
isSubmapOf = isSubmapOfBy (==)
1✔
495

496
-- |  The expression (@'isSubmapOfBy' f t1 t2@) returns 'True' if
497
-- all keys in @t1@ are in tree @t2@, and when @f@ returns 'True' when
498
-- applied to their respective values.
499
isSubmapOfBy :: Ord k => (a -> b -> Bool) -> IntervalMap k a -> IntervalMap k b -> Bool
500
isSubmapOfBy f m1 m2 = and $
1✔
501
  [ case lookupInterval i m2 of
1✔
502
      Nothing -> False
1✔
503
      Just b -> f a b
1✔
504
  | (i,a) <- toList m1 ]
1✔
505

506
-- |  Is this a proper submap? (ie. a submap but not equal).
507
-- Defined as (@'isProperSubmapOf' = 'isProperSubmapOfBy' (==)@).
508
isProperSubmapOf :: (Ord k, Eq a) => IntervalMap k a -> IntervalMap k a -> Bool
509
isProperSubmapOf = isProperSubmapOfBy (==)
1✔
510

511
-- | Is this a proper submap? (ie. a submap but not equal).
512
-- The expression (@'isProperSubmapOfBy' f m1 m2@) returns 'True' when
513
-- @m1@ and @m2@ are not equal,
514
-- all keys in @m1@ are in @m2@, and when @f@ returns 'True' when
515
-- applied to their respective values.
516
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> IntervalMap k a -> IntervalMap k b -> Bool
517
isProperSubmapOfBy f m1 m2 =
1✔
518
  isSubmapOfBy f m1 m2 &&
1✔
519
  keysSet m1 `IntervalSet.isProperSubsetOf` keysSet m2
1✔
520

521
-- ------------------------------------------------------------------------
522

523
splitLookupLE :: Ord k => k -> Map k v -> (Map k v, Maybe v, Map k v)
524
splitLookupLE k m =
1✔
525
  case Map.splitLookup k m of
1✔
526
    (smaller, Just v, larger) -> (smaller, Just v, larger)
1✔
527
    (smaller, Nothing, larger) ->
528
      case Map.maxView smaller of
1✔
529
        Just (v, smaller') -> (smaller', Just v, larger)
1✔
530
        Nothing -> (smaller, Nothing, larger)
1✔
531

532
upTo :: Ord r => Interval r -> Interval r
533
upTo i =
1✔
534
  case Interval.lowerBound' i of
1✔
535
    (NegInf, _) -> Interval.empty
1✔
536
    (PosInf, _) -> Interval.whole
×
537
    (Finite lb, incl) ->
538
      Interval.interval (NegInf, Interval.Open) (Finite lb, notB incl)
×
539

540
downTo :: Ord r => Interval r -> Interval r
541
downTo i =
1✔
542
  case Interval.upperBound' i of
1✔
543
    (PosInf, _) -> Interval.empty
1✔
544
    (NegInf, _) -> Interval.whole
×
545
    (Finite ub, incl) ->
546
      Interval.interval (Finite ub, notB incl) (PosInf, Interval.Open)
×
547

548
notB :: Interval.Boundary -> Interval.Boundary
549
notB = \case
1✔
550
  Interval.Open   -> Interval.Closed
1✔
551
  Interval.Closed -> Interval.Open
1✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2025 Coveralls, Inc