summaryrefslogtreecommitdiff
path: root/ghc/compiler/utils/FiniteMap.lhs
blob: 384a7d122a647ef028a650cf1326e28c279882e4 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
%
% (c) The AQUA Project, Glasgow University, 1994-1996
%
\section[FiniteMap]{An implementation of finite maps}

``Finite maps'' are the heart of the compiler's
lookup-tables/environments and its implementation of sets.  Important
stuff!

This code is derived from that in the paper:
\begin{display}
	S Adams
	"Efficient sets: a balancing act"
	Journal of functional programming 3(4) Oct 1993, pp553-562
\end{display}

The code is SPECIALIZEd to various highly-desirable types (e.g., Id)
near the end (only \tr{#ifdef COMPILING_GHC}).

\begin{code}
#ifdef COMPILING_GHC
#include "HsVersions.h"
#define IF_NOT_GHC(a) {--}
#else
#define ASSERT(e) {--}
#define IF_NOT_GHC(a) a
#define COMMA ,
#endif

#if defined(COMPILING_GHC) && defined(DEBUG_FINITEMAPS)/* NB NB NB */
#define OUTPUTABLE_key , Outputable key
#else
#define OUTPUTABLE_key {--}
#endif

module FiniteMap (
	FiniteMap,		-- abstract type

	emptyFM, unitFM, listToFM,

	addToFM,
	addToFM_C,
	addListToFM,
	addListToFM_C,
	IF_NOT_GHC(delFromFM COMMA)
	delListFromFM,

	plusFM,
	plusFM_C,
	minusFM,
	foldFM,

	IF_NOT_GHC(intersectFM COMMA)
	IF_NOT_GHC(intersectFM_C COMMA)
	IF_NOT_GHC(mapFM COMMA filterFM COMMA)

	sizeFM, isEmptyFM, elemFM, lookupFM, lookupWithDefaultFM,

	fmToList, keysFM, eltsFM

#ifdef COMPILING_GHC
	, bagToFM
	, FiniteSet(..), emptySet, mkSet, isEmptySet
	, elementOf, setToList, union, minusSet
#endif

	-- To make it self-sufficient
#if __HASKELL1__ < 3
	, Maybe
#endif
    ) where

import Maybes

#ifdef COMPILING_GHC
import Ubiq{-uitous-}
# ifdef DEBUG
import Pretty
# endif
import Bag	( foldBag )
#if ! OMIT_NATIVE_CODEGEN
#define IF_NCG(a) a
#else
#define IF_NCG(a) {--}
#endif
#endif

-- SIGH: but we use unboxed "sizes"...
#if __GLASGOW_HASKELL__
#define IF_GHC(a,b) a
#else /* not GHC */
#define IF_GHC(a,b) b
#endif /* not GHC */
\end{code}


%************************************************************************
%*									*
\subsection{The signature of the module}
%*									*
%************************************************************************

\begin{code}
--	BUILDING
emptyFM		:: FiniteMap key elt
unitFM		:: key -> elt -> FiniteMap key elt
listToFM	:: (Ord key OUTPUTABLE_key) => [(key,elt)] -> FiniteMap key elt
			-- In the case of duplicates, the last is taken
#ifdef COMPILING_GHC
bagToFM		:: (Ord key OUTPUTABLE_key) => Bag (key,elt) -> FiniteMap key elt
			-- In the case of duplicates, who knows which is taken
#endif

--	ADDING AND DELETING
		   -- Throws away any previous binding
		   -- In the list case, the items are added starting with the
		   -- first one in the list
addToFM		:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> key -> elt  -> FiniteMap key elt
addListToFM	:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> [(key,elt)] -> FiniteMap key elt

		   -- Combines with previous binding
addToFM_C	:: (Ord key OUTPUTABLE_key) => (elt -> elt -> elt)
			   -> FiniteMap key elt -> key -> elt
			   -> FiniteMap key elt
addListToFM_C	:: (Ord key OUTPUTABLE_key) => (elt -> elt -> elt)
			   -> FiniteMap key elt -> [(key,elt)]
			   -> FiniteMap key elt

		   -- Deletion doesn't complain if you try to delete something
		   -- which isn't there
delFromFM	:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> key   -> FiniteMap key elt
delListFromFM	:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> [key] -> FiniteMap key elt

--	COMBINING
		   -- Bindings in right argument shadow those in the left
plusFM		:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> FiniteMap key elt
			   -> FiniteMap key elt

		   -- Combines bindings for the same thing with the given function
plusFM_C	:: (Ord key OUTPUTABLE_key) => (elt -> elt -> elt)
			   -> FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt

minusFM		:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt
		   -- (minusFM a1 a2) deletes from a1 any bindings which are bound in a2

intersectFM	:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt
intersectFM_C	:: (Ord key OUTPUTABLE_key) => (elt -> elt -> elt)
			   -> FiniteMap key elt -> FiniteMap key elt -> FiniteMap key elt

--	MAPPING, FOLDING, FILTERING
foldFM		:: (key -> elt -> a -> a) -> a -> FiniteMap key elt -> a
mapFM		:: (key -> elt1 -> elt2) -> FiniteMap key elt1 -> FiniteMap key elt2
filterFM	:: (Ord key OUTPUTABLE_key) => (key -> elt -> Bool)
			   -> FiniteMap key elt -> FiniteMap key elt

--	INTERROGATING
sizeFM		:: FiniteMap key elt -> Int
isEmptyFM	:: FiniteMap key elt -> Bool

elemFM		:: (Ord key OUTPUTABLE_key) => key -> FiniteMap key elt -> Bool
lookupFM	:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> key -> Maybe elt
lookupWithDefaultFM
		:: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> elt -> key -> elt
		-- lookupWithDefaultFM supplies a "default" elt
		-- to return for an unmapped key

--	LISTIFYING
fmToList	:: FiniteMap key elt -> [(key,elt)]
keysFM		:: FiniteMap key elt -> [key]
eltsFM		:: FiniteMap key elt -> [elt]
\end{code}

%************************************************************************
%*									*
\subsection{The @FiniteMap@ data type, and building of same}
%*									*
%************************************************************************

Invariants about @FiniteMap@:
\begin{enumerate}
\item
all keys in a FiniteMap are distinct
\item
all keys in left  subtree are $<$ key in Branch and
all keys in right subtree are $>$ key in Branch
\item
size field of a Branch gives number of Branch nodes in the tree
\item
size of left subtree is differs from size of right subtree by a
factor of at most \tr{sIZE_RATIO}
\end{enumerate}

\begin{code}
data FiniteMap key elt
  = EmptyFM
  | Branch key elt	    	-- Key and elt stored here
    IF_GHC(Int#,Int{-STRICT-})	-- Size >= 1
    (FiniteMap key elt)	    	-- Children
    (FiniteMap key elt)
\end{code}

\begin{code}
emptyFM = EmptyFM
{-
emptyFM
  = Branch bottom bottom IF_GHC(0#,0) bottom bottom
  where
    bottom = panic "emptyFM"
-}

-- #define EmptyFM (Branch _ _ IF_GHC(0#,0) _ _)

unitFM key elt = Branch key elt IF_GHC(1#,1) emptyFM emptyFM

listToFM = addListToFM emptyFM

#ifdef COMPILING_GHC
bagToFM = foldBag plusFM (\ (k,v) -> unitFM k v) emptyFM
#endif
\end{code}

%************************************************************************
%*									*
\subsection{Adding to and deleting from @FiniteMaps@}
%*									*
%************************************************************************

\begin{code}
addToFM fm key elt = addToFM_C (\ old new -> new) fm key elt

addToFM_C combiner EmptyFM key elt = unitFM key elt
addToFM_C combiner (Branch key elt size fm_l fm_r) new_key new_elt
#ifdef __GLASGOW_HASKELL__
  = case _tagCmp new_key key of
	_LT -> mkBalBranch key elt (addToFM_C combiner fm_l new_key new_elt) fm_r
	_GT -> mkBalBranch key elt fm_l (addToFM_C combiner fm_r new_key new_elt)
	_EQ -> Branch new_key (combiner elt new_elt) size fm_l fm_r
#else
  | new_key < key = mkBalBranch key elt (addToFM_C combiner fm_l new_key new_elt) fm_r
  | new_key > key = mkBalBranch key elt fm_l (addToFM_C combiner fm_r new_key new_elt)
  | otherwise	  = Branch new_key (combiner elt new_elt) size fm_l fm_r
#endif

addListToFM fm key_elt_pairs = addListToFM_C (\ old new -> new) fm key_elt_pairs

addListToFM_C combiner fm key_elt_pairs
  = foldl add fm key_elt_pairs	-- foldl adds from the left
  where
    add fmap (key,elt) = addToFM_C combiner fmap key elt
\end{code}

\begin{code}
delFromFM EmptyFM del_key = emptyFM
delFromFM (Branch key elt size fm_l fm_r) del_key
#ifdef __GLASGOW_HASKELL__
  = case _tagCmp del_key key of
	_GT -> mkBalBranch key elt fm_l (delFromFM fm_r del_key)
	_LT -> mkBalBranch key elt (delFromFM fm_l del_key) fm_r
	_EQ -> glueBal fm_l fm_r
#else
  | del_key > key
  = mkBalBranch key elt fm_l (delFromFM fm_r del_key)

  | del_key < key
  = mkBalBranch key elt (delFromFM fm_l del_key) fm_r

  | key == del_key
  = glueBal fm_l fm_r
#endif

delListFromFM fm keys = foldl delFromFM fm keys
\end{code}

%************************************************************************
%*									*
\subsection{Combining @FiniteMaps@}
%*									*
%************************************************************************

\begin{code}
plusFM_C combiner EmptyFM fm2 = fm2
plusFM_C combiner fm1 EmptyFM = fm1
plusFM_C combiner fm1 (Branch split_key elt2 _ left right)
  = mkVBalBranch split_key new_elt
		 (plusFM_C combiner lts left)
		 (plusFM_C combiner gts right)
  where
    lts     = splitLT fm1 split_key
    gts     = splitGT fm1 split_key
    new_elt = case lookupFM fm1 split_key of
		Nothing   -> elt2
		Just elt1 -> combiner elt1 elt2

-- It's worth doing plusFM specially, because we don't need
-- to do the lookup in fm1.

plusFM EmptyFM fm2 = fm2
plusFM fm1 EmptyFM = fm1
plusFM fm1 (Branch split_key elt1 _ left right)
  = mkVBalBranch split_key elt1 (plusFM lts left) (plusFM gts right)
  where
    lts     = splitLT fm1 split_key
    gts     = splitGT fm1 split_key

minusFM EmptyFM fm2 = emptyFM
minusFM fm1 EmptyFM = fm1
minusFM fm1 (Branch split_key elt _ left right)
  = glueVBal (minusFM lts left) (minusFM gts right)
	-- The two can be way different, so we need glueVBal
  where
    lts = splitLT fm1 split_key		-- NB gt and lt, so the equal ones
    gts = splitGT fm1 split_key		-- are not in either.

intersectFM fm1 fm2 = intersectFM_C (\ left right -> right) fm1 fm2

intersectFM_C combiner fm1 EmptyFM = emptyFM
intersectFM_C combiner EmptyFM fm2 = emptyFM
intersectFM_C combiner fm1 (Branch split_key elt2 _ left right)

  | maybeToBool maybe_elt1	-- split_elt *is* in intersection
  = mkVBalBranch split_key (combiner elt1 elt2) (intersectFM_C combiner lts left)
						(intersectFM_C combiner gts right)

  | otherwise			-- split_elt is *not* in intersection
  = glueVBal (intersectFM_C combiner lts left) (intersectFM_C combiner gts right)

  where
    lts = splitLT fm1 split_key		-- NB gt and lt, so the equal ones
    gts = splitGT fm1 split_key		-- are not in either.

    maybe_elt1 = lookupFM fm1 split_key
    Just elt1  = maybe_elt1
\end{code}

%************************************************************************
%*									*
\subsection{Mapping, folding, and filtering with @FiniteMaps@}
%*									*
%************************************************************************

\begin{code}
foldFM k z EmptyFM = z
foldFM k z (Branch key elt _ fm_l fm_r)
  = foldFM k (k key elt (foldFM k z fm_r)) fm_l

mapFM f EmptyFM = emptyFM
mapFM f (Branch key elt size fm_l fm_r)
  = Branch key (f key elt) size (mapFM f fm_l) (mapFM f fm_r)

filterFM p EmptyFM = emptyFM
filterFM p (Branch key elt _ fm_l fm_r)
  | p key elt		-- Keep the item
  = mkVBalBranch key elt (filterFM p fm_l) (filterFM p fm_r)

  | otherwise		-- Drop the item
  = glueVBal (filterFM p fm_l) (filterFM p fm_r)
\end{code}

%************************************************************************
%*									*
\subsection{Interrogating @FiniteMaps@}
%*									*
%************************************************************************

\begin{code}
--{-# INLINE sizeFM #-}
sizeFM EmptyFM		     = 0
sizeFM (Branch _ _ size _ _) = IF_GHC(I# size, size)

isEmptyFM fm = sizeFM fm == 0

lookupFM EmptyFM key = Nothing
lookupFM (Branch key elt _ fm_l fm_r) key_to_find
#ifdef __GLASGOW_HASKELL__
  = case _tagCmp key_to_find key of
	_LT -> lookupFM fm_l key_to_find
	_GT -> lookupFM fm_r key_to_find
	_EQ -> Just elt
#else
  | key_to_find < key = lookupFM fm_l key_to_find
  | key_to_find > key = lookupFM fm_r key_to_find
  | otherwise	  = Just elt
#endif

key `elemFM` fm
  = case (lookupFM fm key) of { Nothing -> False; Just elt -> True }

lookupWithDefaultFM fm deflt key
  = case (lookupFM fm key) of { Nothing -> deflt; Just elt -> elt }
\end{code}

%************************************************************************
%*									*
\subsection{Listifying @FiniteMaps@}
%*									*
%************************************************************************

\begin{code}
fmToList fm = foldFM (\ key elt rest -> (key,elt) : rest) [] fm
keysFM fm   = foldFM (\ key elt rest -> key : rest)       [] fm
eltsFM fm   = foldFM (\ key elt rest -> elt : rest)       [] fm
\end{code}


%************************************************************************
%*									*
\subsection{The implementation of balancing}
%*									*
%************************************************************************

%************************************************************************
%*									*
\subsubsection{Basic construction of a @FiniteMap@}
%*									*
%************************************************************************

@mkBranch@ simply gets the size component right.  This is the ONLY
(non-trivial) place the Branch object is built, so the ASSERTion
recursively checks consistency.  (The trivial use of Branch is in
@unitFM@.)

\begin{code}
sIZE_RATIO :: Int
sIZE_RATIO = 5

mkBranch :: (Ord key OUTPUTABLE_key) 		-- Used for the assertion checking only
	 => Int
	 -> key -> elt
	 -> FiniteMap key elt -> FiniteMap key elt
	 -> FiniteMap key elt

mkBranch which key elt fm_l fm_r
  = --ASSERT( left_ok && right_ok && balance_ok )
#if defined(COMPILING_GHC) && defined(DEBUG_FINITEMAPS)
    if not ( left_ok && right_ok && balance_ok ) then
	pprPanic ("mkBranch:"++show which) (ppAboves [ppr PprDebug [left_ok, right_ok, balance_ok],
				       ppr PprDebug key,
				       ppr PprDebug fm_l,
				       ppr PprDebug fm_r])
    else
#endif
    let
	result = Branch key elt (unbox (1 + left_size + right_size)) fm_l fm_r
    in
--    if sizeFM result <= 8 then
	result
--    else
--	pprTrace ("mkBranch:"++(show which)) (ppr PprDebug result) (
--	result
--	)
  where
    left_ok  = case fm_l of
		EmptyFM		         -> True
		Branch left_key _ _ _ _  -> let
						biggest_left_key = fst (findMax fm_l)
					    in
					    biggest_left_key < key
    right_ok = case fm_r of
		EmptyFM		         -> True
		Branch right_key _ _ _ _ -> let
						smallest_right_key = fst (findMin fm_r)
					    in
					    key < smallest_right_key
    balance_ok = True -- sigh
{- LATER:
    balance_ok
      = -- Both subtrees have one or no elements...
	(left_size + right_size <= 1)
-- NO	      || left_size == 0  -- ???
-- NO	      || right_size == 0 -- ???
    	-- ... or the number of elements in a subtree does not exceed
	-- sIZE_RATIO times the number of elements in the other subtree
      || (left_size  * sIZE_RATIO >= right_size &&
    	  right_size * sIZE_RATIO >= left_size)
-}

    left_size  = sizeFM fm_l
    right_size = sizeFM fm_r

#ifdef __GLASGOW_HASKELL__
    unbox :: Int -> Int#
    unbox (I# size) = size
#else
    unbox :: Int -> Int
    unbox x = x
#endif
\end{code}

%************************************************************************
%*									*
\subsubsection{{\em Balanced} construction of a @FiniteMap@}
%*									*
%************************************************************************

@mkBalBranch@ rebalances, assuming that the subtrees aren't too far
out of whack.

\begin{code}
mkBalBranch :: (Ord key OUTPUTABLE_key)
	    => key -> elt
	    -> FiniteMap key elt -> FiniteMap key elt
	    -> FiniteMap key elt

mkBalBranch key elt fm_L fm_R

  | size_l + size_r < 2
  = mkBranch 1{-which-} key elt fm_L fm_R

  | size_r > sIZE_RATIO * size_l	-- Right tree too big
  = case fm_R of
	Branch _ _ _ fm_rl fm_rr
		| sizeFM fm_rl < 2 * sizeFM fm_rr -> single_L fm_L fm_R
		| otherwise	   	          -> double_L fm_L fm_R
	-- Other case impossible

  | size_l > sIZE_RATIO * size_r	-- Left tree too big
  = case fm_L of
	Branch _ _ _ fm_ll fm_lr
		| sizeFM fm_lr < 2 * sizeFM fm_ll -> single_R fm_L fm_R
		| otherwise		          -> double_R fm_L fm_R
	-- Other case impossible

  | otherwise				-- No imbalance
  = mkBranch 2{-which-} key elt fm_L fm_R

  where
    size_l   = sizeFM fm_L
    size_r   = sizeFM fm_R

    single_L fm_l (Branch key_r elt_r _ fm_rl fm_rr)
	= mkBranch 3{-which-} key_r elt_r (mkBranch 4{-which-} key elt fm_l fm_rl) fm_rr

    double_L fm_l (Branch key_r elt_r _ (Branch key_rl elt_rl _ fm_rll fm_rlr) fm_rr)
	= mkBranch 5{-which-} key_rl elt_rl (mkBranch 6{-which-} key   elt   fm_l   fm_rll)
				 (mkBranch 7{-which-} key_r elt_r fm_rlr fm_rr)

    single_R (Branch key_l elt_l _ fm_ll fm_lr) fm_r
	= mkBranch 8{-which-} key_l elt_l fm_ll (mkBranch 9{-which-} key elt fm_lr fm_r)

    double_R (Branch key_l elt_l _ fm_ll (Branch key_lr elt_lr _ fm_lrl fm_lrr)) fm_r
	= mkBranch 10{-which-} key_lr elt_lr (mkBranch 11{-which-} key_l elt_l fm_ll  fm_lrl)
				 (mkBranch 12{-which-} key   elt   fm_lrr fm_r)
\end{code}


\begin{code}
mkVBalBranch :: (Ord key OUTPUTABLE_key)
	     => key -> elt
	     -> FiniteMap key elt -> FiniteMap key elt
	     -> FiniteMap key elt

-- Assert: in any call to (mkVBalBranch_C comb key elt l r),
--	   (a) all keys in l are < all keys in r
--	   (b) all keys in l are < key
--	   (c) all keys in r are > key

mkVBalBranch key elt EmptyFM fm_r = addToFM fm_r key elt
mkVBalBranch key elt fm_l EmptyFM = addToFM fm_l key elt

mkVBalBranch key elt fm_l@(Branch key_l elt_l _ fm_ll fm_lr)
		     fm_r@(Branch key_r elt_r _ fm_rl fm_rr)
  | sIZE_RATIO * size_l < size_r
  = mkBalBranch key_r elt_r (mkVBalBranch key elt fm_l fm_rl) fm_rr

  | sIZE_RATIO * size_r < size_l
  = mkBalBranch key_l elt_l fm_ll (mkVBalBranch key elt fm_lr fm_r)

  | otherwise
  = mkBranch 13{-which-} key elt fm_l fm_r

  where
    size_l = sizeFM fm_l
    size_r = sizeFM fm_r
\end{code}

%************************************************************************
%*									*
\subsubsection{Gluing two trees together}
%*									*
%************************************************************************

@glueBal@ assumes its two arguments aren't too far out of whack, just
like @mkBalBranch@.  But: all keys in first arg are $<$ all keys in
second.

\begin{code}
glueBal :: (Ord key OUTPUTABLE_key)
	=> FiniteMap key elt -> FiniteMap key elt
	-> FiniteMap key elt

glueBal EmptyFM fm2 = fm2
glueBal fm1 EmptyFM = fm1
glueBal fm1 fm2
	-- The case analysis here (absent in Adams' program) is really to deal
	-- with the case where fm2 is a singleton. Then deleting the minimum means
	-- we pass an empty tree to mkBalBranch, which breaks its invariant.
  | sizeFM fm2 > sizeFM fm1
  = mkBalBranch mid_key2 mid_elt2 fm1 (deleteMin fm2)

  | otherwise
  = mkBalBranch mid_key1 mid_elt1 (deleteMax fm1) fm2
  where
    (mid_key1, mid_elt1) = findMax fm1
    (mid_key2, mid_elt2) = findMin fm2
\end{code}

@glueVBal@ copes with arguments which can be of any size.
But: all keys in first arg are $<$ all keys in second.

\begin{code}
glueVBal :: (Ord key OUTPUTABLE_key)
	 => FiniteMap key elt -> FiniteMap key elt
	 -> FiniteMap key elt

glueVBal EmptyFM fm2 = fm2
glueVBal fm1 EmptyFM = fm1
glueVBal fm_l@(Branch key_l elt_l _ fm_ll fm_lr)
	 fm_r@(Branch key_r elt_r _ fm_rl fm_rr)
  | sIZE_RATIO * size_l < size_r
  = mkBalBranch key_r elt_r (glueVBal fm_l fm_rl) fm_rr

  | sIZE_RATIO * size_r < size_l
  = mkBalBranch key_l elt_l fm_ll (glueVBal fm_lr fm_r)

  | otherwise		-- We now need the same two cases as in glueBal above.
  = glueBal fm_l fm_r
  where
    (mid_key_l,mid_elt_l) = findMax fm_l
    (mid_key_r,mid_elt_r) = findMin fm_r
    size_l = sizeFM fm_l
    size_r = sizeFM fm_r
\end{code}

%************************************************************************
%*									*
\subsection{Local utilities}
%*									*
%************************************************************************

\begin{code}
splitLT, splitGT :: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> key -> FiniteMap key elt

-- splitLT fm split_key  =  fm restricted to keys <  split_key
-- splitGT fm split_key  =  fm restricted to keys >  split_key

splitLT EmptyFM split_key = emptyFM
splitLT (Branch key elt _ fm_l fm_r) split_key
#ifdef __GLASGOW_HASKELL__
  = case _tagCmp split_key key of
	_LT -> splitLT fm_l split_key
	_GT -> mkVBalBranch key elt fm_l (splitLT fm_r split_key)
	_EQ -> fm_l
#else
  | split_key < key = splitLT fm_l split_key
  | split_key > key = mkVBalBranch key elt fm_l (splitLT fm_r split_key)
  | otherwise	    = fm_l
#endif

splitGT EmptyFM split_key = emptyFM
splitGT (Branch key elt _ fm_l fm_r) split_key
#ifdef __GLASGOW_HASKELL__
  = case _tagCmp split_key key of
	_GT -> splitGT fm_r split_key
	_LT -> mkVBalBranch key elt (splitGT fm_l split_key) fm_r
	_EQ -> fm_r
#else
  | split_key > key = splitGT fm_r split_key
  | split_key < key = mkVBalBranch key elt (splitGT fm_l split_key) fm_r
  | otherwise	    = fm_r
#endif

findMin :: FiniteMap key elt -> (key,elt)
findMin (Branch key elt _ EmptyFM _) = (key,elt)
findMin (Branch key elt _ fm_l    _) = findMin fm_l

deleteMin :: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> FiniteMap key elt
deleteMin (Branch key elt _ EmptyFM fm_r) = fm_r
deleteMin (Branch key elt _ fm_l    fm_r) = mkBalBranch key elt (deleteMin fm_l) fm_r

findMax :: FiniteMap key elt -> (key,elt)
findMax (Branch key elt _ _ EmptyFM) = (key,elt)
findMax (Branch key elt _ _    fm_r) = findMax fm_r

deleteMax :: (Ord key OUTPUTABLE_key) => FiniteMap key elt -> FiniteMap key elt
deleteMax (Branch key elt _ fm_l EmptyFM) = fm_l
deleteMax (Branch key elt _ fm_l    fm_r) = mkBalBranch key elt fm_l (deleteMax fm_r)
\end{code}

%************************************************************************
%*									*
\subsection{Output-ery}
%*									*
%************************************************************************

\begin{code}
#if defined(COMPILING_GHC) && defined(DEBUG_FINITEMAPS)

instance (Outputable key) => Outputable (FiniteMap key elt) where
    ppr sty fm = pprX sty fm

pprX sty EmptyFM = ppChar '!'
pprX sty (Branch key elt sz fm_l fm_r)
 = ppBesides [ppLparen, pprX sty fm_l, ppSP,
	      ppr sty key, ppSP, ppInt (IF_GHC(I# sz, sz)), ppSP,
	      pprX sty fm_r, ppRparen]
#endif

#ifndef COMPILING_GHC
instance (Eq key, Eq elt) => Eq (FiniteMap key elt) where
  fm_1 == fm_2 = (sizeFM   fm_1 == sizeFM   fm_2) &&   -- quick test
		 (fmToList fm_1 == fmToList fm_2)

{- NO: not clear what The Right Thing to do is:
instance (Ord key, Ord elt) => Ord (FiniteMap key elt) where
  fm_1 <= fm_2 = (sizeFM   fm_1 <= sizeFM   fm_2) &&   -- quick test
		 (fmToList fm_1 <= fmToList fm_2)
-}
#endif
\end{code}

%************************************************************************
%*									*
\subsection{FiniteSets---a thin veneer}
%*									*
%************************************************************************

\begin{code}
#ifdef COMPILING_GHC

type FiniteSet key = FiniteMap key ()
emptySet	:: FiniteSet key
mkSet		:: (Ord key OUTPUTABLE_key) => [key] -> FiniteSet key
isEmptySet	:: FiniteSet key -> Bool
elementOf	:: (Ord key OUTPUTABLE_key) => key -> FiniteSet key -> Bool
minusSet	:: (Ord key OUTPUTABLE_key) => FiniteSet key -> FiniteSet key -> FiniteSet key
setToList	:: FiniteSet key -> [key]
union		:: (Ord key OUTPUTABLE_key) => FiniteSet key -> FiniteSet key -> FiniteSet key

emptySet = emptyFM
mkSet xs = listToFM [ (x, ()) | x <- xs]
isEmptySet = isEmptyFM
elementOf = elemFM
minusSet  = minusFM
setToList = keysFM
union = plusFM

#endif
\end{code}

%************************************************************************
%*									*
\subsection{Efficiency pragmas for GHC}
%*									*
%************************************************************************

When the FiniteMap module is used in GHC, we specialise it for
\tr{Uniques}, for dastardly efficiency reasons.

\begin{code}
#if 0
#if defined(COMPILING_GHC) && __GLASGOW_HASKELL__

{-# SPECIALIZE listToFM
		:: [(Int,elt)] -> FiniteMap Int elt,
		   [(CLabel,elt)] -> FiniteMap CLabel elt,
		   [(FAST_STRING,elt)] -> FiniteMap FAST_STRING elt,
		   [((FAST_STRING,FAST_STRING),elt)] -> FiniteMap (FAST_STRING, FAST_STRING) elt
    IF_NCG(COMMA   [(Reg COMMA elt)] -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE addToFM
		:: FiniteMap Int elt -> Int -> elt  -> FiniteMap Int elt,
		   FiniteMap FAST_STRING elt -> FAST_STRING -> elt  -> FiniteMap FAST_STRING elt,
		   FiniteMap CLabel elt -> CLabel -> elt  -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> Reg -> elt  -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE addListToFM
		:: FiniteMap Int elt -> [(Int,elt)] -> FiniteMap Int elt,
		   FiniteMap CLabel elt -> [(CLabel,elt)] -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> [(Reg COMMA elt)] -> FiniteMap Reg elt)
    #-}
{-NOT EXPORTED!! # SPECIALIZE addToFM_C
		:: (elt -> elt -> elt) -> FiniteMap Int elt -> Int -> elt -> FiniteMap Int elt,
		   (elt -> elt -> elt) -> FiniteMap CLabel elt -> CLabel -> elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   (elt -> elt -> elt) -> FiniteMap Reg elt -> Reg -> elt -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE addListToFM_C
		:: (elt -> elt -> elt) -> FiniteMap Int elt -> [(Int,elt)] -> FiniteMap Int elt,
		   (elt -> elt -> elt) -> FiniteMap TyCon elt -> [(TyCon,elt)] -> FiniteMap TyCon elt,
		   (elt -> elt -> elt) -> FiniteMap CLabel elt -> [(CLabel,elt)] -> FiniteMap CLabel elt
    IF_NCG(COMMA   (elt -> elt -> elt) -> FiniteMap Reg elt -> [(Reg COMMA elt)] -> FiniteMap Reg elt)
    #-}
{-NOT EXPORTED!!! # SPECIALIZE delFromFM
		:: FiniteMap Int elt -> Int   -> FiniteMap Int elt,
		   FiniteMap CLabel elt -> CLabel   -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> Reg   -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE delListFromFM
		:: FiniteMap Int elt -> [Int] -> FiniteMap Int elt,
		   FiniteMap CLabel elt -> [CLabel] -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> [Reg] -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE elemFM
		:: FAST_STRING -> FiniteMap FAST_STRING elt -> Bool
    #-}
{-not EXPORTED!!! # SPECIALIZE filterFM
		:: (Int -> elt -> Bool) -> FiniteMap Int elt -> FiniteMap Int elt,
		   (CLabel -> elt -> Bool) -> FiniteMap CLabel elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   (Reg -> elt -> Bool) -> FiniteMap Reg elt -> FiniteMap Reg elt)
    #-}
{-NOT EXPORTED!!! # SPECIALIZE intersectFM
		:: FiniteMap Int elt -> FiniteMap Int elt -> FiniteMap Int elt,
		   FiniteMap CLabel elt -> FiniteMap CLabel elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> FiniteMap Reg elt -> FiniteMap Reg elt)
    #-}
{-not EXPORTED !!!# SPECIALIZE intersectFM_C
		:: (elt -> elt -> elt) -> FiniteMap Int elt -> FiniteMap Int elt -> FiniteMap Int elt,
		   (elt -> elt -> elt) -> FiniteMap CLabel elt -> FiniteMap CLabel elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   (elt -> elt -> elt) -> FiniteMap Reg elt -> FiniteMap Reg elt -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE lookupFM
		:: FiniteMap Int elt -> Int -> Maybe elt,
		   FiniteMap CLabel elt -> CLabel -> Maybe elt,
		   FiniteMap FAST_STRING elt -> FAST_STRING -> Maybe elt,
		   FiniteMap (FAST_STRING,FAST_STRING) elt -> (FAST_STRING,FAST_STRING) -> Maybe elt
    IF_NCG(COMMA   FiniteMap Reg elt -> Reg -> Maybe elt)
    #-}
{-# SPECIALIZE lookupWithDefaultFM
		:: FiniteMap Int elt -> elt -> Int -> elt,
		   FiniteMap CLabel elt -> elt -> CLabel -> elt
    IF_NCG(COMMA   FiniteMap Reg elt -> elt -> Reg -> elt)
    #-}
{-# SPECIALIZE minusFM
		:: FiniteMap Int elt -> FiniteMap Int elt -> FiniteMap Int elt,
		   FiniteMap TyCon elt -> FiniteMap TyCon elt -> FiniteMap TyCon elt,
		   FiniteMap FAST_STRING elt -> FiniteMap FAST_STRING elt -> FiniteMap FAST_STRING elt,
		   FiniteMap CLabel elt -> FiniteMap CLabel elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> FiniteMap Reg elt -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE plusFM
		:: FiniteMap Int elt -> FiniteMap Int elt -> FiniteMap Int elt,
		   FiniteMap TyCon elt -> FiniteMap TyCon elt -> FiniteMap TyCon elt,
		   FiniteMap CLabel elt -> FiniteMap CLabel elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   FiniteMap Reg elt -> FiniteMap Reg elt -> FiniteMap Reg elt)
    #-}
{-# SPECIALIZE plusFM_C
		:: (elt -> elt -> elt) -> FiniteMap Int elt -> FiniteMap Int elt -> FiniteMap Int elt,
		   (elt -> elt -> elt) -> FiniteMap CLabel elt -> FiniteMap CLabel elt -> FiniteMap CLabel elt
    IF_NCG(COMMA   (elt -> elt -> elt) -> FiniteMap Reg elt -> FiniteMap Reg elt -> FiniteMap Reg elt)
    #-}

#endif {- compiling for GHC -}
#endif {- 0 -}
\end{code}