[project @ 1996-01-11 14:06:51 by partain]
[ghc-hetmet.git] / ghc / lib / ghc / Set.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1995
3 %
4 \section[Set]{An implementation of sets}
5
6 This new (94/04) implementation of sets sits squarely upon our
7 implementation of @FiniteMaps@.  The interface is (roughly?) as
8 before.
9
10 (95/08: This module is no longer part of the GHC compiler proper; it
11 is a GHC library module only, now.)
12
13 \begin{code}
14 module Set (
15         -- not a synonym so we can make it abstract
16         Set,
17
18         mkSet, setToList, emptySet, singletonSet,
19         union, unionManySets, minusSet,
20         elementOf, mapSet,
21         intersect, isEmptySet,
22         cardinality
23         
24         -- to make the interface self-sufficient
25 #if defined(__GLASGOW_HASKELL__)
26         , FiniteMap   -- abstract
27
28         -- for pragmas
29         , keysFM, sizeFM
30 #endif
31     ) where
32
33 import FiniteMap
34 import Maybes           ( maybeToBool
35 #if __HASKELL1__ < 3
36                           , Maybe(..)
37 #endif
38                         )
39 \end{code}
40
41 \begin{code}
42 -- This can't be a type synonym if you want to use constructor classes.
43 data Set a = MkSet (FiniteMap a ()) {-# STRICT #-}
44
45 emptySet :: Set a
46 emptySet = MkSet emptyFM
47
48 singletonSet :: a -> Set a
49 singletonSet x = MkSet (singletonFM x ())
50
51 setToList :: Set a -> [a]
52 setToList (MkSet set) = keysFM set
53
54 mkSet :: Ord a => [a]  -> Set a
55 mkSet xs = MkSet (listToFM [ (x, ()) | x <- xs])
56
57 union :: Ord a => Set a -> Set a -> Set a
58 union (MkSet set1) (MkSet set2) = MkSet (plusFM set1 set2)
59
60 unionManySets :: Ord a => [Set a] -> Set a
61 unionManySets ss = foldr union emptySet ss
62
63 minusSet  :: Ord a => Set a -> Set a -> Set a
64 minusSet (MkSet set1) (MkSet set2) = MkSet (minusFM set1 set2)
65
66 intersect :: Ord a => Set a -> Set a -> Set a
67 intersect (MkSet set1) (MkSet set2) = MkSet (intersectFM set1 set2)
68
69 elementOf :: Ord a => a -> Set a -> Bool
70 elementOf x (MkSet set) = maybeToBool(lookupFM set x)
71
72 isEmptySet :: Set a -> Bool
73 isEmptySet (MkSet set) = sizeFM set == 0
74
75 mapSet :: Ord a => (b -> a) -> Set b -> Set a
76 mapSet f (MkSet set) = MkSet (listToFM [ (f key, ()) | key <- keysFM set ])
77
78 cardinality :: Set a -> Int
79 cardinality (MkSet set) = sizeFM set
80
81 -- fair enough...
82 instance (Eq a) => Eq (Set a) where
83   (MkSet set_1) == (MkSet set_2) = set_1 == set_2
84
85 -- but not so clear what the right thing to do is:
86 {- NO:
87 instance (Ord a) => Ord (Set a) where
88   (MkSet set_1) <= (MkSet set_2) = set_1 <= set_2
89 -}
90 \end{code}