@@ -1158,7 +1158,20 @@ nequal _ _ = True
11581158--------------------------------------------------------------------}
11591159
11601160instance Ord IntSet where
1161- compare s1 s2 = orderingOf $ relateTop s1 s2
1161+ compare Nil Nil = EQ
1162+ compare Nil _ = LT
1163+ compare _ Nil = GT
1164+ compare t1@ (Tip _ _) t2@ (Tip _ _)
1165+ = orderingOf $ relateTipTip t1 t2
1166+ compare xs ys
1167+ | (xsNeg, xsNonNeg) <- splitSign xs
1168+ , (ysNeg, ysNonNeg) <- splitSign ys
1169+ = case relate xsNeg ysNeg of
1170+ Less -> LT
1171+ Prefix -> if null xsNonNeg then LT else GT
1172+ Equals -> orderingOf (relate xsNonNeg ysNonNeg)
1173+ FlipPrefix -> if null ysNonNeg then GT else LT
1174+ Greater -> GT
11621175
11631176-- | detailed outcome of lexicographic comparison of lists.
11641177-- w.r.t. Ordering, there are two extra cases,
@@ -1184,51 +1197,25 @@ orderingOf r = case r of
11841197 FlipPrefix -> GT
11851198 Greater -> GT
11861199
1187- -- The following gets complicated since integers are
1188- -- effectively handled (in the tree) by their binary representation:
1189- -- if a bit is zero, the left branch is taken.
1190- -- This also holds for the sign bit (the MSB),
1191- -- so negative numbers are in the right subtree:
1192- -- after Bin p m l r = fromList [-1,0]
1193- -- we have l = fromList [0], r = fromList [-1] .
1194- -- This can only happen at the very top, so handle this separetely,
1195- -- and avoid the check for the "mixed" case during recursion (function 'relate')
1196- -- We also avoid checking for Nil in 'relate', since it cannot appear below Bin.
1197-
1198- relateTop :: IntSet -> IntSet -> Relation
1199- {-# INLINE relateTop #-}
1200- relateTop Nil Nil = Equals
1201- relateTop Nil t2 = Prefix
1202- relateTop t1 Nil = FlipPrefix
1203- relateTop t1@ (Bin p1 m1 l1 r1) t2@ (Bin p2 m2 l2 r2)
1204- | mixed t1 && mixed t2 = combine (relate r1 r2) (relate l1 l2)
1205- | mixed t1 = combine_left (relate r1 t2)
1206- | mixed t2 = combine_right (relate t1 r2)
1207- | otherwise = relate t1 t2
1208- relateTop t1@ (Bin p1 m1 l1 r1) t2@ (Tip p2 bm2)
1209- | mixed t1 = combine_left (relate r1 t2)
1210- | otherwise = relate t1 t2
1211- relateTop t1@ (Tip p1 bm1) t2@ (Bin p2 m2 l2 r2)
1212- | mixed t2 = combine_right (relate t1 r2)
1213- | otherwise = relate t1 t2
1214- relateTop t1@ (Tip _ _) t2@ (Tip _ _) = relateTipTip t1 t2
1215-
1216- -- | precondition: each argument is non-Nil and non-mixed
1200+ -- | precondition: each argument is non-mixed
12171201relate :: IntSet -> IntSet -> Relation
1202+ relate Nil Nil = Equals
1203+ relate Nil t2 = Prefix
1204+ relate t1 Nil = FlipPrefix
12181205relate t1@ (Tip p1 bm1) t2@ (Tip p2 bm2) = relateTipTip t1 t2
12191206relate t1@ (Bin p1 m1 l1 r1) t2@ (Bin p2 m2 l2 r2)
12201207 | otherwise = case compare (natFromInt m1) (natFromInt m2) of
12211208 GT -> combine_left (relate l1 t2)
12221209 EQ -> combine (relate l1 l2) (relate r1 r2)
12231210 LT -> combine_right (relate t1 l2)
1224- relate t1@ (Bin p1 m1 l1 r1) t2@ (Tip p2 bm2 )
1225- | upperbound t1 < lowerbound t2 = Less
1226- | lowerbound t1 > upperbound t2 = Greater
1211+ relate t1@ (Bin p1 m1 l1 r1) t2@ (Tip p2 _ )
1212+ | succUpperbound t1 <= lowerbound t2 = Less
1213+ | lowerbound t1 >= succUpperbound t2 = Greater
12271214 | 0 == (m1 .&. p2) = combine_left (relate l1 t2)
12281215 | otherwise = Less
1229- relate t1@ (Tip p1 bm1 ) t2@ (Bin p2 m2 l2 r2)
1230- | upperbound t1 < lowerbound t2 = Less
1231- | lowerbound t1 > upperbound t2 = Greater
1216+ relate t1@ (Tip p1 _ ) t2@ (Bin p2 m2 l2 r2)
1217+ | succUpperbound t1 <= lowerbound t2 = Less
1218+ | lowerbound t1 >= succUpperbound t2 = Greater
12321219 | 0 == (p1 .&. m2) = combine_right (relate t1 l2)
12331220 | otherwise = Greater
12341221
@@ -1291,23 +1278,31 @@ combine_right r = case r of
12911278 FlipPrefix -> Less
12921279 Greater -> Greater
12931280
1294- -- | does the set contain both numbers >= 0 and numbers < 0 ?
1295- mixed :: IntSet -> Bool
1296- mixed (Bin p m l r) = m == bit ( wordSize - 1 )
1297-
12981281-- | shall only be applied to non-mixed non-Nil trees
12991282lowerbound :: IntSet -> Int
13001283{-# INLINE lowerbound #-}
13011284lowerbound (Tip p _) = p
1302- lowerbound t@ (Bin p m _ _) = p
1303-
1304- -- | shall only be applied to non-mixed non-Nil trees
1305- upperbound :: IntSet -> Int
1306- {-# INLINE upperbound #-}
1307- upperbound (Tip p _) = p + wordSize - 1
1308- upperbound t@ (Bin p m _ _) = p + m - 1
1309-
1310-
1285+ lowerbound (Bin p _ _ _) = p
1286+
1287+ -- | this is one more than the actual upper bound (to save one operation)
1288+ -- shall only be applied to non-mixed non-Nil trees
1289+ succUpperbound :: IntSet -> Int
1290+ {-# INLINE succUpperbound #-}
1291+ succUpperbound (Tip p _) = p + wordSize
1292+ succUpperbound (Bin p m _ _) = p + shiftR m 1
1293+
1294+ -- | split a set into subsets of negative and non-negative elements
1295+ splitSign :: IntSet -> (IntSet ,IntSet )
1296+ {-# INLINE splitSign #-}
1297+ splitSign t@ (Tip kx _)
1298+ | kx >= 0 = (Nil , t)
1299+ | otherwise = (t, Nil )
1300+ splitSign t@ (Bin p m l r)
1301+ -- m < 0 is the usual way to find out if we have positives and negatives (see findMax)
1302+ | m < 0 = (r, l)
1303+ | p < 0 = (t, Nil )
1304+ | otherwise = (Nil , t)
1305+ splitSign Nil = (Nil , Nil )
13111306
13121307{- -------------------------------------------------------------------
13131308 Show
0 commit comments