@@ -1215,156 +1215,8 @@ nequal _ _ = True
1215
1215
--------------------------------------------------------------------}
1216
1216
1217
1217
instance Ord IntSet where
1218
- compare Nil Nil = EQ
1219
- compare Nil _ = LT
1220
- compare _ Nil = GT
1221
- compare t1@ (Tip _ _) t2@ (Tip _ _)
1222
- = orderingOf $ relateTipTip t1 t2
1223
- compare xs ys
1224
- | (xsNeg, xsNonNeg) <- splitSign xs
1225
- , (ysNeg, ysNonNeg) <- splitSign ys
1226
- = case relate xsNeg ysNeg of
1227
- Less -> LT
1228
- Prefix -> if null xsNonNeg then LT else GT
1229
- Equals -> orderingOf (relate xsNonNeg ysNonNeg)
1230
- FlipPrefix -> if null ysNonNeg then GT else LT
1231
- Greater -> GT
1232
-
1233
- -- | detailed outcome of lexicographic comparison of lists.
1234
- -- w.r.t. Ordering, there are two extra cases,
1235
- -- since (++) is not monotonic w.r.t. lex. order on lists
1236
- -- (which is used by definition):
1237
- -- consider comparison of (Bin [0,3,4] [ 6] ) to (Bin [0,3] [7] )
1238
- -- where [0,3,4] > [0,3] but [0,3,4,6] < [0,3,7].
1239
-
1240
- data Relation
1241
- = Less -- ^ holds for [0,3,4] [0,3,5,1]
1242
- | Prefix -- ^ holds for [0,3,4] [0,3,4,5]
1243
- | Equals -- ^ holds for [0,3,4] [0,3,4]
1244
- | FlipPrefix -- ^ holds for [0,3,4] [0,3]
1245
- | Greater -- ^ holds for [0,3,4] [0,2,5]
1246
- deriving (Show , Eq )
1247
-
1248
- orderingOf :: Relation -> Ordering
1249
- {-# INLINE orderingOf #-}
1250
- orderingOf r = case r of
1251
- Less -> LT
1252
- Prefix -> LT
1253
- Equals -> EQ
1254
- FlipPrefix -> GT
1255
- Greater -> GT
1256
-
1257
- -- | precondition: each argument is non-mixed
1258
- relate :: IntSet -> IntSet -> Relation
1259
- relate Nil Nil = Equals
1260
- relate Nil _t2 = Prefix
1261
- relate _t1 Nil = FlipPrefix
1262
- relate t1@ Tip {} t2@ Tip {} = relateTipTip t1 t2
1263
- relate t1@ (Bin _p1 m1 l1 r1) t2@ (Bin _p2 m2 l2 r2)
1264
- | succUpperbound t1 <= lowerbound t2 = Less
1265
- | lowerbound t1 >= succUpperbound t2 = Greater
1266
- | otherwise = case compare (natFromInt m1) (natFromInt m2) of
1267
- GT -> combine_left (relate l1 t2)
1268
- EQ -> combine (relate l1 l2) (relate r1 r2)
1269
- LT -> combine_right (relate t1 l2)
1270
- relate t1@ (Bin _p1 m1 l1 _r1) t2@ (Tip p2 _bm2)
1271
- | succUpperbound t1 <= lowerbound t2 = Less
1272
- | lowerbound t1 >= succUpperbound t2 = Greater
1273
- | 0 == (m1 .&. p2) = combine_left (relate l1 t2)
1274
- | otherwise = Less
1275
- relate t1@ (Tip p1 _bm1) t2@ (Bin _p2 m2 l2 _r2)
1276
- | succUpperbound t1 <= lowerbound t2 = Less
1277
- | lowerbound t1 >= succUpperbound t2 = Greater
1278
- | 0 == (p1 .&. m2) = combine_right (relate t1 l2)
1279
- | otherwise = Greater
1280
-
1281
- relateTipTip :: IntSet -> IntSet -> Relation
1282
- {-# INLINE relateTipTip #-}
1283
- relateTipTip (Tip p1 bm1) (Tip p2 bm2) = case compare p1 p2 of
1284
- LT -> Less
1285
- EQ -> relateBM bm1 bm2
1286
- GT -> Greater
1287
- relateTipTip _ _ = error " relateTipTip"
1288
-
1289
- relateBM :: BitMap -> BitMap -> Relation
1290
- {-# inline relateBM #-}
1291
- relateBM w1 w2 | w1 == w2 = Equals
1292
- relateBM w1 w2 =
1293
- let delta = xor w1 w2
1294
- lowest_diff_mask = delta .&. complement (delta- 1 )
1295
- prefix = (complement lowest_diff_mask + 1 )
1296
- .&. (complement lowest_diff_mask)
1297
- in if 0 == lowest_diff_mask .&. w1
1298
- then if 0 == w1 .&. prefix
1299
- then Prefix else Greater
1300
- else if 0 == w2 .&. prefix
1301
- then FlipPrefix else Less
1302
-
1303
- -- | This function has the property
1304
- -- relate t1@(Bin p m l1 r1) t2@(Bin p m l2 r2) = combine (relate l1 l2) (relate r1 r2)
1305
- -- It is important that `combine` is lazy in the second argument (achieved by inlining)
1306
- combine :: Relation -> Relation -> Relation
1307
- {-# inline combine #-}
1308
- combine r eq = case r of
1309
- Less -> Less
1310
- Prefix -> Greater
1311
- Equals -> eq
1312
- FlipPrefix -> Less
1313
- Greater -> Greater
1314
-
1315
- -- | This function has the property
1316
- -- relate t1@(Bin p1 m1 l1 r1) t2 = combine_left (relate l1 t2)
1317
- -- under the precondition that the range of l1 contains the range of t2,
1318
- -- and r1 is non-empty
1319
- combine_left :: Relation -> Relation
1320
- {-# inline combine_left #-}
1321
- combine_left r = case r of
1322
- Less -> Less
1323
- Prefix -> Greater
1324
- Equals -> FlipPrefix
1325
- FlipPrefix -> FlipPrefix
1326
- Greater -> Greater
1327
-
1328
- -- | This function has the property
1329
- -- relate t1 t2@(Bin p2 m2 l2 r2) = combine_right (relate t1 l2)
1330
- -- under the precondition that the range of t1 is included in the range of l2,
1331
- -- and r2 is non-empty
1332
- combine_right :: Relation -> Relation
1333
- {-# inline combine_right #-}
1334
- combine_right r = case r of
1335
- Less -> Less
1336
- Prefix -> Prefix
1337
- Equals -> Prefix
1338
- FlipPrefix -> Less
1339
- Greater -> Greater
1340
-
1341
- -- | shall only be applied to non-mixed non-Nil trees
1342
- lowerbound :: IntSet -> Int
1343
- {-# INLINE lowerbound #-}
1344
- lowerbound Nil = error " lowerbound: Nil"
1345
- lowerbound (Tip p _) = p
1346
- lowerbound (Bin p _ _ _) = p
1347
-
1348
- -- | this is one more than the actual upper bound (to save one operation)
1349
- -- shall only be applied to non-mixed non-Nil trees
1350
- succUpperbound :: IntSet -> Int
1351
- {-# INLINE succUpperbound #-}
1352
- succUpperbound Nil = error " succUpperbound: Nil"
1353
- succUpperbound (Tip p _) = p + wordSize
1354
- succUpperbound (Bin p m _ _) = p + shiftR m 1
1355
-
1356
- -- | split a set into subsets of negative and non-negative elements
1357
- splitSign :: IntSet -> (IntSet ,IntSet )
1358
- {-# INLINE splitSign #-}
1359
- splitSign t@ (Tip kx _)
1360
- | kx >= 0 = (Nil , t)
1361
- | otherwise = (t, Nil )
1362
- splitSign t@ (Bin p m l r)
1363
- -- m < 0 is the usual way to find out if we have positives and negatives (see findMax)
1364
- | m < 0 = (r, l)
1365
- | p < 0 = (t, Nil )
1366
- | otherwise = (Nil , t)
1367
- splitSign Nil = (Nil , Nil )
1218
+ compare s1 s2 = compare (toAscList s1) (toAscList s2)
1219
+ -- tentative implementation. See if more efficient exists.
1368
1220
1369
1221
{- -------------------------------------------------------------------
1370
1222
Show
0 commit comments