[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / lib / ghc / ListSetOps.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
3 %
4 \section[ListSetOps]{Set-like operations on lists}
5
6 \begin{code}
7 module ListSetOps (
8         unionLists,
9         intersectLists,
10         minusList
11 #if ! defined(COMPILING_GHC)
12         , disjointLists, intersectingLists
13 #endif
14    ) where
15
16 #if defined(COMPILING_GHC)
17 import Util
18 # ifdef USE_ATTACK_PRAGMAS
19 import AbsUniType
20 import Id               ( Id )
21 # endif
22 #endif
23 \end{code}
24
25 \begin{code}
26 unionLists :: (Eq a) => [a] -> [a] -> [a]
27 unionLists []     []            = []
28 unionLists []     b             = b
29 unionLists a       []           = a
30 unionLists (a:as) b
31   | a `is_elem` b = unionLists as b
32   | otherwise     = a : unionLists as b
33   where
34 #if defined(COMPILING_GHC)
35     is_elem = isIn "unionLists"
36 #else
37     is_elem = elem
38 #endif
39
40 intersectLists :: (Eq a) => [a] -> [a] -> [a]
41 intersectLists []     []                = []
42 intersectLists []     b                 = []
43 intersectLists a      []                = []
44 intersectLists (a:as) b
45   | a `is_elem` b = a : intersectLists as b
46   | otherwise     = intersectLists as b
47   where
48 #if defined(COMPILING_GHC)
49     is_elem = isIn "intersectLists"
50 #else
51     is_elem = elem
52 #endif
53 \end{code}
54
55 Everything in the first list that is not in the second list:
56 \begin{code}
57 minusList :: (Eq a) => [a] -> [a] -> [a]
58 minusList xs ys = [ x | x <- xs, x `not_elem` ys]
59   where
60 #if defined(COMPILING_GHC)
61     not_elem = isn'tIn "minusList"
62 #else
63     not_elem = notElem
64 #endif
65 \end{code}
66
67 \begin{code}
68 #if ! defined(COMPILING_GHC)
69
70 disjointLists, intersectingLists :: Eq a => [a] -> [a] -> Bool
71
72 disjointLists []     bs = True
73 disjointLists (a:as) bs
74   | a `elem` bs = False
75   | otherwise   = disjointLists as bs
76
77 intersectingLists xs ys = not (disjointLists xs ys)
78 #endif
79 \end{code}
80
81 \begin{code}
82 #if defined(COMPILING_GHC)
83 # ifdef USE_ATTACK_PRAGMAS
84
85 {-# SPECIALIZE unionLists     :: [TyVar] -> [TyVar] -> [TyVar] #-}
86 {-# SPECIALIZE intersectLists :: [TyVar] -> [TyVar] -> [TyVar] #-}
87
88 {-# SPECIALIZE minusList :: [TyVar] -> [TyVar] -> [TyVar],
89                             [Id]    -> [Id]    -> [Id],
90                             [Int]   -> [Int]   -> [Int]
91  #-}
92
93 # endif
94 #endif
95 \end{code}