Prevent duplication of unsafePerformIO on a multiprocessor
[haskell-directory.git] / Data / IntSet.hs
1 {-# OPTIONS -cpp -fglasgow-exts #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Data.IntSet
5 -- Copyright   :  (c) Daan Leijen 2002
6 -- License     :  BSD-style
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  provisional
9 -- Portability :  portable
10 --
11 -- An efficient implementation of integer sets.
12 --
13 -- Since many function names (but not the type name) clash with
14 -- "Prelude" names, this module is usually imported @qualified@, e.g.
15 --
16 -- >  import Data.IntSet (IntSet)
17 -- >  import qualified Data.IntSet as IntSet
18 --
19 -- The implementation is based on /big-endian patricia trees/.  This data
20 -- structure performs especially well on binary operations like 'union'
21 -- and 'intersection'.  However, my benchmarks show that it is also
22 -- (much) faster on insertions and deletions when compared to a generic
23 -- size-balanced set implementation (see "Data.Set").
24 --
25 --    * Chris Okasaki and Andy Gill,  \"/Fast Mergeable Integer Maps/\",
26 --      Workshop on ML, September 1998, pages 77-86,
27 --      <http://www.cse.ogi.edu/~andy/pub/finite.htm>
28 --
29 --    * D.R. Morrison, \"/PATRICIA -- Practical Algorithm To Retrieve
30 --      Information Coded In Alphanumeric/\", Journal of the ACM, 15(4),
31 --      October 1968, pages 514-534.
32 --
33 -- Many operations have a worst-case complexity of /O(min(n,W))/.
34 -- This means that the operation can become linear in the number of
35 -- elements with a maximum of /W/ -- the number of bits in an 'Int'
36 -- (32 or 64).
37 -----------------------------------------------------------------------------
38
39 module Data.IntSet  ( 
40             -- * Set type
41               IntSet          -- instance Eq,Show
42
43             -- * Operators
44             , (\\)
45
46             -- * Query
47             , null
48             , size
49             , member
50             , notMember
51             , isSubsetOf
52             , isProperSubsetOf
53             
54             -- * Construction
55             , empty
56             , singleton
57             , insert
58             , delete
59             
60             -- * Combine
61             , union, unions
62             , difference
63             , intersection
64             
65             -- * Filter
66             , filter
67             , partition
68             , split
69             , splitMember
70
71             -- * Map
72             , map
73
74             -- * Fold
75             , fold
76
77             -- * Conversion
78             -- ** List
79             , elems
80             , toList
81             , fromList
82             
83             -- ** Ordered list
84             , toAscList
85             , fromAscList
86             , fromDistinctAscList
87                         
88             -- * Debugging
89             , showTree
90             , showTreeWith
91             ) where
92
93
94 import Prelude hiding (lookup,filter,foldr,foldl,null,map)
95 import Data.Bits 
96
97 import qualified Data.List as List
98 import Data.Monoid (Monoid(..))
99 import Data.Typeable
100
101 {-
102 -- just for testing
103 import QuickCheck 
104 import List (nub,sort)
105 import qualified List
106 -}
107
108 #if __GLASGOW_HASKELL__
109 import Text.Read
110 import Data.Generics.Basics (Data(..), mkNorepType)
111 import Data.Generics.Instances ()
112 #endif
113
114 #if __GLASGOW_HASKELL__ >= 503
115 import GHC.Exts ( Word(..), Int(..), shiftRL# )
116 #elif __GLASGOW_HASKELL__
117 import Word
118 import GlaExts ( Word(..), Int(..), shiftRL# )
119 #else
120 import Data.Word
121 #endif
122
123 infixl 9 \\{-This comment teaches CPP correct behaviour -}
124
125 -- A "Nat" is a natural machine word (an unsigned Int)
126 type Nat = Word
127
128 natFromInt :: Int -> Nat
129 natFromInt i = fromIntegral i
130
131 intFromNat :: Nat -> Int
132 intFromNat w = fromIntegral w
133
134 shiftRL :: Nat -> Int -> Nat
135 #if __GLASGOW_HASKELL__
136 {--------------------------------------------------------------------
137   GHC: use unboxing to get @shiftRL@ inlined.
138 --------------------------------------------------------------------}
139 shiftRL (W# x) (I# i)
140   = W# (shiftRL# x i)
141 #else
142 shiftRL x i   = shiftR x i
143 #endif
144
145 {--------------------------------------------------------------------
146   Operators
147 --------------------------------------------------------------------}
148 -- | /O(n+m)/. See 'difference'.
149 (\\) :: IntSet -> IntSet -> IntSet
150 m1 \\ m2 = difference m1 m2
151
152 {--------------------------------------------------------------------
153   Types  
154 --------------------------------------------------------------------}
155 -- | A set of integers.
156 data IntSet = Nil
157             | Tip {-# UNPACK #-} !Int
158             | Bin {-# UNPACK #-} !Prefix {-# UNPACK #-} !Mask !IntSet !IntSet
159
160 type Prefix = Int
161 type Mask   = Int
162
163 instance Monoid IntSet where
164     mempty  = empty
165     mappend = union
166     mconcat = unions
167
168 #if __GLASGOW_HASKELL__
169
170 {--------------------------------------------------------------------
171   A Data instance  
172 --------------------------------------------------------------------}
173
174 -- This instance preserves data abstraction at the cost of inefficiency.
175 -- We omit reflection services for the sake of data abstraction.
176
177 instance Data IntSet where
178   gfoldl f z is = z fromList `f` (toList is)
179   toConstr _    = error "toConstr"
180   gunfold _ _   = error "gunfold"
181   dataTypeOf _  = mkNorepType "Data.IntSet.IntSet"
182
183 #endif
184
185 {--------------------------------------------------------------------
186   Query
187 --------------------------------------------------------------------}
188 -- | /O(1)/. Is the set empty?
189 null :: IntSet -> Bool
190 null Nil   = True
191 null other = False
192
193 -- | /O(n)/. Cardinality of the set.
194 size :: IntSet -> Int
195 size t
196   = case t of
197       Bin p m l r -> size l + size r
198       Tip y -> 1
199       Nil   -> 0
200
201 -- | /O(min(n,W))/. Is the value a member of the set?
202 member :: Int -> IntSet -> Bool
203 member x t
204   = case t of
205       Bin p m l r 
206         | nomatch x p m -> False
207         | zero x m      -> member x l
208         | otherwise     -> member x r
209       Tip y -> (x==y)
210       Nil   -> False
211     
212 -- | /O(log n)/. Is the element not in the set?
213 notMember :: Int -> IntSet -> Bool
214 notMember k = not . member k
215
216 -- 'lookup' is used by 'intersection' for left-biasing
217 lookup :: Int -> IntSet -> Maybe Int
218 lookup k t
219   = let nk = natFromInt k  in seq nk (lookupN nk t)
220
221 lookupN :: Nat -> IntSet -> Maybe Int
222 lookupN k t
223   = case t of
224       Bin p m l r 
225         | zeroN k (natFromInt m) -> lookupN k l
226         | otherwise              -> lookupN k r
227       Tip kx 
228         | (k == natFromInt kx)  -> Just kx
229         | otherwise             -> Nothing
230       Nil -> Nothing
231
232 {--------------------------------------------------------------------
233   Construction
234 --------------------------------------------------------------------}
235 -- | /O(1)/. The empty set.
236 empty :: IntSet
237 empty
238   = Nil
239
240 -- | /O(1)/. A set of one element.
241 singleton :: Int -> IntSet
242 singleton x
243   = Tip x
244
245 {--------------------------------------------------------------------
246   Insert
247 --------------------------------------------------------------------}
248 -- | /O(min(n,W))/. Add a value to the set. When the value is already
249 -- an element of the set, it is replaced by the new one, ie. 'insert'
250 -- is left-biased.
251 insert :: Int -> IntSet -> IntSet
252 insert x t
253   = case t of
254       Bin p m l r 
255         | nomatch x p m -> join x (Tip x) p t
256         | zero x m      -> Bin p m (insert x l) r
257         | otherwise     -> Bin p m l (insert x r)
258       Tip y 
259         | x==y          -> Tip x
260         | otherwise     -> join x (Tip x) y t
261       Nil -> Tip x
262
263 -- right-biased insertion, used by 'union'
264 insertR :: Int -> IntSet -> IntSet
265 insertR x t
266   = case t of
267       Bin p m l r 
268         | nomatch x p m -> join x (Tip x) p t
269         | zero x m      -> Bin p m (insert x l) r
270         | otherwise     -> Bin p m l (insert x r)
271       Tip y 
272         | x==y          -> t
273         | otherwise     -> join x (Tip x) y t
274       Nil -> Tip x
275
276 -- | /O(min(n,W))/. Delete a value in the set. Returns the
277 -- original set when the value was not present.
278 delete :: Int -> IntSet -> IntSet
279 delete x t
280   = case t of
281       Bin p m l r 
282         | nomatch x p m -> t
283         | zero x m      -> bin p m (delete x l) r
284         | otherwise     -> bin p m l (delete x r)
285       Tip y 
286         | x==y          -> Nil
287         | otherwise     -> t
288       Nil -> Nil
289
290
291 {--------------------------------------------------------------------
292   Union
293 --------------------------------------------------------------------}
294 -- | The union of a list of sets.
295 unions :: [IntSet] -> IntSet
296 unions xs
297   = foldlStrict union empty xs
298
299
300 -- | /O(n+m)/. The union of two sets. 
301 union :: IntSet -> IntSet -> IntSet
302 union t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
303   | shorter m1 m2  = union1
304   | shorter m2 m1  = union2
305   | p1 == p2       = Bin p1 m1 (union l1 l2) (union r1 r2)
306   | otherwise      = join p1 t1 p2 t2
307   where
308     union1  | nomatch p2 p1 m1  = join p1 t1 p2 t2
309             | zero p2 m1        = Bin p1 m1 (union l1 t2) r1
310             | otherwise         = Bin p1 m1 l1 (union r1 t2)
311
312     union2  | nomatch p1 p2 m2  = join p1 t1 p2 t2
313             | zero p1 m2        = Bin p2 m2 (union t1 l2) r2
314             | otherwise         = Bin p2 m2 l2 (union t1 r2)
315
316 union (Tip x) t = insert x t
317 union t (Tip x) = insertR x t  -- right bias
318 union Nil t     = t
319 union t Nil     = t
320
321
322 {--------------------------------------------------------------------
323   Difference
324 --------------------------------------------------------------------}
325 -- | /O(n+m)/. Difference between two sets. 
326 difference :: IntSet -> IntSet -> IntSet
327 difference t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
328   | shorter m1 m2  = difference1
329   | shorter m2 m1  = difference2
330   | p1 == p2       = bin p1 m1 (difference l1 l2) (difference r1 r2)
331   | otherwise      = t1
332   where
333     difference1 | nomatch p2 p1 m1  = t1
334                 | zero p2 m1        = bin p1 m1 (difference l1 t2) r1
335                 | otherwise         = bin p1 m1 l1 (difference r1 t2)
336
337     difference2 | nomatch p1 p2 m2  = t1
338                 | zero p1 m2        = difference t1 l2
339                 | otherwise         = difference t1 r2
340
341 difference t1@(Tip x) t2 
342   | member x t2  = Nil
343   | otherwise    = t1
344
345 difference Nil t     = Nil
346 difference t (Tip x) = delete x t
347 difference t Nil     = t
348
349
350
351 {--------------------------------------------------------------------
352   Intersection
353 --------------------------------------------------------------------}
354 -- | /O(n+m)/. The intersection of two sets. 
355 intersection :: IntSet -> IntSet -> IntSet
356 intersection t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
357   | shorter m1 m2  = intersection1
358   | shorter m2 m1  = intersection2
359   | p1 == p2       = bin p1 m1 (intersection l1 l2) (intersection r1 r2)
360   | otherwise      = Nil
361   where
362     intersection1 | nomatch p2 p1 m1  = Nil
363                   | zero p2 m1        = intersection l1 t2
364                   | otherwise         = intersection r1 t2
365
366     intersection2 | nomatch p1 p2 m2  = Nil
367                   | zero p1 m2        = intersection t1 l2
368                   | otherwise         = intersection t1 r2
369
370 intersection t1@(Tip x) t2 
371   | member x t2  = t1
372   | otherwise    = Nil
373 intersection t (Tip x) 
374   = case lookup x t of
375       Just y  -> Tip y
376       Nothing -> Nil
377 intersection Nil t = Nil
378 intersection t Nil = Nil
379
380
381
382 {--------------------------------------------------------------------
383   Subset
384 --------------------------------------------------------------------}
385 -- | /O(n+m)/. Is this a proper subset? (ie. a subset but not equal).
386 isProperSubsetOf :: IntSet -> IntSet -> Bool
387 isProperSubsetOf t1 t2
388   = case subsetCmp t1 t2 of 
389       LT -> True
390       ge -> False
391
392 subsetCmp t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
393   | shorter m1 m2  = GT
394   | shorter m2 m1  = subsetCmpLt
395   | p1 == p2       = subsetCmpEq
396   | otherwise      = GT  -- disjoint
397   where
398     subsetCmpLt | nomatch p1 p2 m2  = GT
399                 | zero p1 m2        = subsetCmp t1 l2
400                 | otherwise         = subsetCmp t1 r2
401     subsetCmpEq = case (subsetCmp l1 l2, subsetCmp r1 r2) of
402                     (GT,_ ) -> GT
403                     (_ ,GT) -> GT
404                     (EQ,EQ) -> EQ
405                     other   -> LT
406
407 subsetCmp (Bin p m l r) t  = GT
408 subsetCmp (Tip x) (Tip y)  
409   | x==y       = EQ
410   | otherwise  = GT  -- disjoint
411 subsetCmp (Tip x) t        
412   | member x t = LT
413   | otherwise  = GT  -- disjoint
414 subsetCmp Nil Nil = EQ
415 subsetCmp Nil t   = LT
416
417 -- | /O(n+m)/. Is this a subset?
418 -- @(s1 `isSubsetOf` s2)@ tells whether @s1@ is a subset of @s2@.
419
420 isSubsetOf :: IntSet -> IntSet -> Bool
421 isSubsetOf t1@(Bin p1 m1 l1 r1) t2@(Bin p2 m2 l2 r2)
422   | shorter m1 m2  = False
423   | shorter m2 m1  = match p1 p2 m2 && (if zero p1 m2 then isSubsetOf t1 l2
424                                                       else isSubsetOf t1 r2)                     
425   | otherwise      = (p1==p2) && isSubsetOf l1 l2 && isSubsetOf r1 r2
426 isSubsetOf (Bin p m l r) t  = False
427 isSubsetOf (Tip x) t        = member x t
428 isSubsetOf Nil t            = True
429
430
431 {--------------------------------------------------------------------
432   Filter
433 --------------------------------------------------------------------}
434 -- | /O(n)/. Filter all elements that satisfy some predicate.
435 filter :: (Int -> Bool) -> IntSet -> IntSet
436 filter pred t
437   = case t of
438       Bin p m l r 
439         -> bin p m (filter pred l) (filter pred r)
440       Tip x 
441         | pred x    -> t
442         | otherwise -> Nil
443       Nil -> Nil
444
445 -- | /O(n)/. partition the set according to some predicate.
446 partition :: (Int -> Bool) -> IntSet -> (IntSet,IntSet)
447 partition pred t
448   = case t of
449       Bin p m l r 
450         -> let (l1,l2) = partition pred l
451                (r1,r2) = partition pred r
452            in (bin p m l1 r1, bin p m l2 r2)
453       Tip x 
454         | pred x    -> (t,Nil)
455         | otherwise -> (Nil,t)
456       Nil -> (Nil,Nil)
457
458
459 -- | /O(log n)/. The expression (@'split' x set@) is a pair @(set1,set2)@
460 -- where all elements in @set1@ are lower than @x@ and all elements in
461 -- @set2@ larger than @x@.
462 --
463 -- > split 3 (fromList [1..5]) == (fromList [1,2], fromList [3,4])
464 split :: Int -> IntSet -> (IntSet,IntSet)
465 split x t
466   = case t of
467       Bin p m l r
468         | m < 0       -> if x >= 0 then let (lt,gt) = split' x l in (union r lt, gt)
469                                    else let (lt,gt) = split' x r in (lt, union gt l)
470                                    -- handle negative numbers.
471         | otherwise   -> split' x t
472       Tip y 
473         | x>y         -> (t,Nil)
474         | x<y         -> (Nil,t)
475         | otherwise   -> (Nil,Nil)
476       Nil             -> (Nil, Nil)
477
478 split' :: Int -> IntSet -> (IntSet,IntSet)
479 split' x t
480   = case t of
481       Bin p m l r
482         | match x p m -> if zero x m then let (lt,gt) = split' x l in (lt,union gt r)
483                                      else let (lt,gt) = split' x r in (union l lt,gt)
484         | otherwise   -> if x < p then (Nil, t)
485                                   else (t, Nil)
486       Tip y 
487         | x>y       -> (t,Nil)
488         | x<y       -> (Nil,t)
489         | otherwise -> (Nil,Nil)
490       Nil -> (Nil,Nil)
491
492 -- | /O(log n)/. Performs a 'split' but also returns whether the pivot
493 -- element was found in the original set.
494 splitMember :: Int -> IntSet -> (IntSet,Bool,IntSet)
495 splitMember x t
496   = case t of
497       Bin p m l r
498         | m < 0       -> if x >= 0 then let (lt,found,gt) = splitMember' x l in (union r lt, found, gt)
499                                    else let (lt,found,gt) = splitMember' x r in (lt, found, union gt l)
500                                    -- handle negative numbers.
501         | otherwise   -> splitMember' x t
502       Tip y 
503         | x>y       -> (t,False,Nil)
504         | x<y       -> (Nil,False,t)
505         | otherwise -> (Nil,True,Nil)
506       Nil -> (Nil,False,Nil)
507
508 splitMember' :: Int -> IntSet -> (IntSet,Bool,IntSet)
509 splitMember' x t
510   = case t of
511       Bin p m l r
512          | match x p m ->  if zero x m then let (lt,found,gt) = splitMember x l in (lt,found,union gt r)
513                                        else let (lt,found,gt) = splitMember x r in (union l lt,found,gt)
514          | otherwise   -> if x < p then (Nil, False, t)
515                                    else (t, False, Nil)
516       Tip y 
517         | x>y       -> (t,False,Nil)
518         | x<y       -> (Nil,False,t)
519         | otherwise -> (Nil,True,Nil)
520       Nil -> (Nil,False,Nil)
521
522 {----------------------------------------------------------------------
523   Map
524 ----------------------------------------------------------------------}
525
526 -- | /O(n*min(n,W))/. 
527 -- @'map' f s@ is the set obtained by applying @f@ to each element of @s@.
528 -- 
529 -- It's worth noting that the size of the result may be smaller if,
530 -- for some @(x,y)@, @x \/= y && f x == f y@
531
532 map :: (Int->Int) -> IntSet -> IntSet
533 map f = fromList . List.map f . toList
534
535 {--------------------------------------------------------------------
536   Fold
537 --------------------------------------------------------------------}
538 -- | /O(n)/. Fold over the elements of a set in an unspecified order.
539 --
540 -- > sum set   == fold (+) 0 set
541 -- > elems set == fold (:) [] set
542 fold :: (Int -> b -> b) -> b -> IntSet -> b
543 fold f z t
544   = case t of
545       Bin 0 m l r | m < 0 -> foldr f (foldr f z l) r  
546       -- put negative numbers before.
547       Bin p m l r -> foldr f z t
548       Tip x       -> f x z
549       Nil         -> z
550
551 foldr :: (Int -> b -> b) -> b -> IntSet -> b
552 foldr f z t
553   = case t of
554       Bin p m l r -> foldr f (foldr f z r) l
555       Tip x       -> f x z
556       Nil         -> z
557           
558 {--------------------------------------------------------------------
559   List variations 
560 --------------------------------------------------------------------}
561 -- | /O(n)/. The elements of a set. (For sets, this is equivalent to toList)
562 elems :: IntSet -> [Int]
563 elems s
564   = toList s
565
566 {--------------------------------------------------------------------
567   Lists 
568 --------------------------------------------------------------------}
569 -- | /O(n)/. Convert the set to a list of elements.
570 toList :: IntSet -> [Int]
571 toList t
572   = fold (:) [] t
573
574 -- | /O(n)/. Convert the set to an ascending list of elements.
575 toAscList :: IntSet -> [Int]
576 toAscList t = toList t
577
578 -- | /O(n*min(n,W))/. Create a set from a list of integers.
579 fromList :: [Int] -> IntSet
580 fromList xs
581   = foldlStrict ins empty xs
582   where
583     ins t x  = insert x t
584
585 -- | /O(n*min(n,W))/. Build a set from an ascending list of elements.
586 fromAscList :: [Int] -> IntSet 
587 fromAscList xs
588   = fromList xs
589
590 -- | /O(n*min(n,W))/. Build a set from an ascending list of distinct elements.
591 fromDistinctAscList :: [Int] -> IntSet
592 fromDistinctAscList xs
593   = fromList xs
594
595
596 {--------------------------------------------------------------------
597   Eq 
598 --------------------------------------------------------------------}
599 instance Eq IntSet where
600   t1 == t2  = equal t1 t2
601   t1 /= t2  = nequal t1 t2
602
603 equal :: IntSet -> IntSet -> Bool
604 equal (Bin p1 m1 l1 r1) (Bin p2 m2 l2 r2)
605   = (m1 == m2) && (p1 == p2) && (equal l1 l2) && (equal r1 r2) 
606 equal (Tip x) (Tip y)
607   = (x==y)
608 equal Nil Nil = True
609 equal t1 t2   = False
610
611 nequal :: IntSet -> IntSet -> Bool
612 nequal (Bin p1 m1 l1 r1) (Bin p2 m2 l2 r2)
613   = (m1 /= m2) || (p1 /= p2) || (nequal l1 l2) || (nequal r1 r2) 
614 nequal (Tip x) (Tip y)
615   = (x/=y)
616 nequal Nil Nil = False
617 nequal t1 t2   = True
618
619 {--------------------------------------------------------------------
620   Ord 
621 --------------------------------------------------------------------}
622
623 instance Ord IntSet where
624     compare s1 s2 = compare (toAscList s1) (toAscList s2) 
625     -- tentative implementation. See if more efficient exists.
626
627 {--------------------------------------------------------------------
628   Show
629 --------------------------------------------------------------------}
630 instance Show IntSet where
631   showsPrec p xs = showParen (p > 10) $
632     showString "fromList " . shows (toList xs)
633
634 showSet :: [Int] -> ShowS
635 showSet []     
636   = showString "{}" 
637 showSet (x:xs) 
638   = showChar '{' . shows x . showTail xs
639   where
640     showTail []     = showChar '}'
641     showTail (x:xs) = showChar ',' . shows x . showTail xs
642
643 {--------------------------------------------------------------------
644   Read
645 --------------------------------------------------------------------}
646 instance Read IntSet where
647 #ifdef __GLASGOW_HASKELL__
648   readPrec = parens $ prec 10 $ do
649     Ident "fromList" <- lexP
650     xs <- readPrec
651     return (fromList xs)
652
653   readListPrec = readListPrecDefault
654 #else
655   readsPrec p = readParen (p > 10) $ \ r -> do
656     ("fromList",s) <- lex r
657     (xs,t) <- reads s
658     return (fromList xs,t)
659 #endif
660
661 {--------------------------------------------------------------------
662   Typeable
663 --------------------------------------------------------------------}
664
665 #include "Typeable.h"
666 INSTANCE_TYPEABLE0(IntSet,intSetTc,"IntSet")
667
668 {--------------------------------------------------------------------
669   Debugging
670 --------------------------------------------------------------------}
671 -- | /O(n)/. Show the tree that implements the set. The tree is shown
672 -- in a compressed, hanging format.
673 showTree :: IntSet -> String
674 showTree s
675   = showTreeWith True False s
676
677
678 {- | /O(n)/. The expression (@'showTreeWith' hang wide map@) shows
679  the tree that implements the set. If @hang@ is
680  'True', a /hanging/ tree is shown otherwise a rotated tree is shown. If
681  @wide@ is 'True', an extra wide version is shown.
682 -}
683 showTreeWith :: Bool -> Bool -> IntSet -> String
684 showTreeWith hang wide t
685   | hang      = (showsTreeHang wide [] t) ""
686   | otherwise = (showsTree wide [] [] t) ""
687
688 showsTree :: Bool -> [String] -> [String] -> IntSet -> ShowS
689 showsTree wide lbars rbars t
690   = case t of
691       Bin p m l r
692           -> showsTree wide (withBar rbars) (withEmpty rbars) r .
693              showWide wide rbars .
694              showsBars lbars . showString (showBin p m) . showString "\n" .
695              showWide wide lbars .
696              showsTree wide (withEmpty lbars) (withBar lbars) l
697       Tip x
698           -> showsBars lbars . showString " " . shows x . showString "\n" 
699       Nil -> showsBars lbars . showString "|\n"
700
701 showsTreeHang :: Bool -> [String] -> IntSet -> ShowS
702 showsTreeHang wide bars t
703   = case t of
704       Bin p m l r
705           -> showsBars bars . showString (showBin p m) . showString "\n" . 
706              showWide wide bars .
707              showsTreeHang wide (withBar bars) l .
708              showWide wide bars .
709              showsTreeHang wide (withEmpty bars) r
710       Tip x
711           -> showsBars bars . showString " " . shows x . showString "\n" 
712       Nil -> showsBars bars . showString "|\n" 
713       
714 showBin p m
715   = "*" -- ++ show (p,m)
716
717 showWide wide bars 
718   | wide      = showString (concat (reverse bars)) . showString "|\n" 
719   | otherwise = id
720
721 showsBars :: [String] -> ShowS
722 showsBars bars
723   = case bars of
724       [] -> id
725       _  -> showString (concat (reverse (tail bars))) . showString node
726
727 node           = "+--"
728 withBar bars   = "|  ":bars
729 withEmpty bars = "   ":bars
730
731
732 {--------------------------------------------------------------------
733   Helpers
734 --------------------------------------------------------------------}
735 {--------------------------------------------------------------------
736   Join
737 --------------------------------------------------------------------}
738 join :: Prefix -> IntSet -> Prefix -> IntSet -> IntSet
739 join p1 t1 p2 t2
740   | zero p1 m = Bin p m t1 t2
741   | otherwise = Bin p m t2 t1
742   where
743     m = branchMask p1 p2
744     p = mask p1 m
745
746 {--------------------------------------------------------------------
747   @bin@ assures that we never have empty trees within a tree.
748 --------------------------------------------------------------------}
749 bin :: Prefix -> Mask -> IntSet -> IntSet -> IntSet
750 bin p m l Nil = l
751 bin p m Nil r = r
752 bin p m l r   = Bin p m l r
753
754   
755 {--------------------------------------------------------------------
756   Endian independent bit twiddling
757 --------------------------------------------------------------------}
758 zero :: Int -> Mask -> Bool
759 zero i m
760   = (natFromInt i) .&. (natFromInt m) == 0
761
762 nomatch,match :: Int -> Prefix -> Mask -> Bool
763 nomatch i p m
764   = (mask i m) /= p
765
766 match i p m
767   = (mask i m) == p
768
769 mask :: Int -> Mask -> Prefix
770 mask i m
771   = maskW (natFromInt i) (natFromInt m)
772
773 zeroN :: Nat -> Nat -> Bool
774 zeroN i m = (i .&. m) == 0
775
776 {--------------------------------------------------------------------
777   Big endian operations  
778 --------------------------------------------------------------------}
779 maskW :: Nat -> Nat -> Prefix
780 maskW i m
781   = intFromNat (i .&. (complement (m-1) `xor` m))
782
783 shorter :: Mask -> Mask -> Bool
784 shorter m1 m2
785   = (natFromInt m1) > (natFromInt m2)
786
787 branchMask :: Prefix -> Prefix -> Mask
788 branchMask p1 p2
789   = intFromNat (highestBitMask (natFromInt p1 `xor` natFromInt p2))
790   
791 {----------------------------------------------------------------------
792   Finding the highest bit (mask) in a word [x] can be done efficiently in
793   three ways:
794   * convert to a floating point value and the mantissa tells us the 
795     [log2(x)] that corresponds with the highest bit position. The mantissa 
796     is retrieved either via the standard C function [frexp] or by some bit 
797     twiddling on IEEE compatible numbers (float). Note that one needs to 
798     use at least [double] precision for an accurate mantissa of 32 bit 
799     numbers.
800   * use bit twiddling, a logarithmic sequence of bitwise or's and shifts (bit).
801   * use processor specific assembler instruction (asm).
802
803   The most portable way would be [bit], but is it efficient enough?
804   I have measured the cycle counts of the different methods on an AMD 
805   Athlon-XP 1800 (~ Pentium III 1.8Ghz) using the RDTSC instruction:
806
807   highestBitMask: method  cycles
808                   --------------
809                    frexp   200
810                    float    33
811                    bit      11
812                    asm      12
813
814   highestBit:     method  cycles
815                   --------------
816                    frexp   195
817                    float    33
818                    bit      11
819                    asm      11
820
821   Wow, the bit twiddling is on today's RISC like machines even faster
822   than a single CISC instruction (BSR)!
823 ----------------------------------------------------------------------}
824
825 {----------------------------------------------------------------------
826   [highestBitMask] returns a word where only the highest bit is set.
827   It is found by first setting all bits in lower positions than the 
828   highest bit and than taking an exclusive or with the original value.
829   Allthough the function may look expensive, GHC compiles this into
830   excellent C code that subsequently compiled into highly efficient
831   machine code. The algorithm is derived from Jorg Arndt's FXT library.
832 ----------------------------------------------------------------------}
833 highestBitMask :: Nat -> Nat
834 highestBitMask x
835   = case (x .|. shiftRL x 1) of 
836      x -> case (x .|. shiftRL x 2) of 
837       x -> case (x .|. shiftRL x 4) of 
838        x -> case (x .|. shiftRL x 8) of 
839         x -> case (x .|. shiftRL x 16) of 
840          x -> case (x .|. shiftRL x 32) of   -- for 64 bit platforms
841           x -> (x `xor` (shiftRL x 1))
842
843
844 {--------------------------------------------------------------------
845   Utilities 
846 --------------------------------------------------------------------}
847 foldlStrict f z xs
848   = case xs of
849       []     -> z
850       (x:xx) -> let z' = f z x in seq z' (foldlStrict f z' xx)
851
852
853 {-
854 {--------------------------------------------------------------------
855   Testing
856 --------------------------------------------------------------------}
857 testTree :: [Int] -> IntSet
858 testTree xs   = fromList xs
859 test1 = testTree [1..20]
860 test2 = testTree [30,29..10]
861 test3 = testTree [1,4,6,89,2323,53,43,234,5,79,12,9,24,9,8,423,8,42,4,8,9,3]
862
863 {--------------------------------------------------------------------
864   QuickCheck
865 --------------------------------------------------------------------}
866 qcheck prop
867   = check config prop
868   where
869     config = Config
870       { configMaxTest = 500
871       , configMaxFail = 5000
872       , configSize    = \n -> (div n 2 + 3)
873       , configEvery   = \n args -> let s = show n in s ++ [ '\b' | _ <- s ]
874       }
875
876
877 {--------------------------------------------------------------------
878   Arbitrary, reasonably balanced trees
879 --------------------------------------------------------------------}
880 instance Arbitrary IntSet where
881   arbitrary = do{ xs <- arbitrary
882                 ; return (fromList xs)
883                 }
884
885
886 {--------------------------------------------------------------------
887   Single, Insert, Delete
888 --------------------------------------------------------------------}
889 prop_Single :: Int -> Bool
890 prop_Single x
891   = (insert x empty == singleton x)
892
893 prop_InsertDelete :: Int -> IntSet -> Property
894 prop_InsertDelete k t
895   = not (member k t) ==> delete k (insert k t) == t
896
897
898 {--------------------------------------------------------------------
899   Union
900 --------------------------------------------------------------------}
901 prop_UnionInsert :: Int -> IntSet -> Bool
902 prop_UnionInsert x t
903   = union t (singleton x) == insert x t
904
905 prop_UnionAssoc :: IntSet -> IntSet -> IntSet -> Bool
906 prop_UnionAssoc t1 t2 t3
907   = union t1 (union t2 t3) == union (union t1 t2) t3
908
909 prop_UnionComm :: IntSet -> IntSet -> Bool
910 prop_UnionComm t1 t2
911   = (union t1 t2 == union t2 t1)
912
913 prop_Diff :: [Int] -> [Int] -> Bool
914 prop_Diff xs ys
915   =  toAscList (difference (fromList xs) (fromList ys))
916     == List.sort ((List.\\) (nub xs)  (nub ys))
917
918 prop_Int :: [Int] -> [Int] -> Bool
919 prop_Int xs ys
920   =  toAscList (intersection (fromList xs) (fromList ys))
921     == List.sort (nub ((List.intersect) (xs)  (ys)))
922
923 {--------------------------------------------------------------------
924   Lists
925 --------------------------------------------------------------------}
926 prop_Ordered
927   = forAll (choose (5,100)) $ \n ->
928     let xs = [0..n::Int]
929     in fromAscList xs == fromList xs
930
931 prop_List :: [Int] -> Bool
932 prop_List xs
933   = (sort (nub xs) == toAscList (fromList xs))
934 -}