[project @ 1996-12-19 09:10:02 by simonpj]
[ghc-hetmet.git] / ghc / compiler / types / Class.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[Class]{The @Class@ datatype}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module Class (
10         GenClass(..), SYN_IE(Class),
11
12         mkClass,
13         classKey, classOps, classSelIds,
14         classSuperDictSelId, classOpId, classDefaultMethodId,
15         classSig, classBigSig, classInstEnv,
16         isSuperClassOf,
17         classOpTagByOccName, classOpTagByOccName_maybe,
18
19         GenClassOp(..), SYN_IE(ClassOp),
20         mkClassOp,
21         classOpTag, classOpString,
22         classOpLocalType,
23
24         SYN_IE(ClassInstEnv)
25     ) where
26
27 CHK_Ubiq() -- debugging consistency check
28
29 IMPORT_DELOOPER(TyLoop)
30
31 import TyCon            ( TyCon )
32 import TyVar            ( SYN_IE(TyVar), GenTyVar )
33 import Usage            ( GenUsage, SYN_IE(Usage), SYN_IE(UVar) )
34
35 import MatchEnv         ( MatchEnv )
36 import Maybes           ( assocMaybe )
37 import Name             ( changeUnique, Name, OccName, occNameString )
38 import Unique           -- Keys for built-in classes
39 import Pretty           ( SYN_IE(Pretty), ppCat, ppPStr )
40 import PprStyle         ( PprStyle(..) )
41 import SrcLoc           ( SrcLoc )
42 import Util
43 \end{code}
44
45 %************************************************************************
46 %*                                                                      *
47 \subsection[Class-basic]{@Class@: basic definition}
48 %*                                                                      *
49 %************************************************************************
50
51 A @Class@ corresponds to a Greek kappa in the static semantics:
52
53 The parameterisation wrt tyvar and uvar is only necessary to
54 get appropriately general instances of Ord3 for GenType.
55
56 \begin{code}
57 data GenClassOp ty
58   = ClassOp     OccName -- The operation name
59
60                 Int     -- Unique within a class; starts at 1
61
62                 ty      -- Type; the class tyvar is free (you can find
63                         -- it from the class). This means that a
64                         -- ClassOp doesn't make much sense outside the
65                         -- context of its parent class.
66
67 data GenClass tyvar uvar
68   = Class
69         Unique          -- Key for fast comparison
70         Name
71
72         tyvar           -- The class type variable
73
74         [GenClass tyvar uvar]   -- Immediate superclasses, and the
75         [Id]                    -- corresponding selector functions to
76                                 -- extract them from a dictionary of this
77                                 -- class
78
79         [GenClassOp (GenType tyvar uvar)] -- The * class operations
80         [Id]                              --     * selector functions
81         [Id]                              --     * default methods
82                           -- They are all ordered by tag.  The
83                           -- selector ids are less innocent than they
84                           -- look, because their IdInfos contains
85                           -- suitable specialisation information.  In
86                           -- particular, constant methods are
87                           -- instances of selectors at suitably simple
88                           -- types.
89
90         ClassInstEnv      -- Gives details of all the instances of this class
91
92         [(GenClass tyvar uvar, [GenClass tyvar uvar])]
93                           -- Indirect superclasses;
94                           --   (k,[k1,...,kn]) means that
95                           --   k is an immediate superclass of k1
96                           --   k1 is an immediate superclass of k2
97                           --   ... and kn is an immediate superclass
98                           -- of this class.  (This is all redundant
99                           -- information, since it can be derived from
100                           -- the superclass information above.)
101
102 type Class        = GenClass TyVar UVar
103 type ClassOp      = GenClassOp Type
104
105 type ClassInstEnv = MatchEnv Type Id            -- The Ids are dfuns
106 \end{code}
107
108 The @mkClass@ function fills in the indirect superclasses.
109
110 \begin{code}
111 mkClass :: Unique -> Name -> TyVar
112         -> [Class] -> [Id]
113         -> [ClassOp] -> [Id] -> [Id]
114         -> ClassInstEnv
115         -> Class
116
117 mkClass uniq full_name tyvar super_classes superdict_sels
118         class_ops dict_sels defms class_insts
119   = Class uniq (changeUnique full_name uniq) tyvar
120                 super_classes superdict_sels
121                 class_ops dict_sels defms
122                 class_insts
123                 trans_clos
124   where
125     trans_clos :: [(Class,[Class])]
126     trans_clos = transitiveClosure succ (==) [ (clas, []) | clas <- super_classes ]
127
128     succ (clas@(Class _ _ _ super_classes _ _ _ _ _ _), links)
129       = [(super, (clas:links)) | super <- super_classes]
130 \end{code}
131
132 %************************************************************************
133 %*                                                                      *
134 \subsection[Class-selectors]{@Class@: simple selectors}
135 %*                                                                      *
136 %************************************************************************
137
138 The rest of these functions are just simple selectors.
139
140 \begin{code}
141 classKey (Class key _ _ _ _ _ _ _ _ _) = key
142 classOps (Class _ _ _ _ _ ops _ _ _ _) = ops
143 classSelIds (Class _ _ _ _ _ _ sels _ _ _) = sels
144
145 classOpId (Class _ _ _ _ _ ops op_ids _ _ _) op
146   = op_ids !! (classOpTag op - 1)
147 classDefaultMethodId (Class _ _ _ _ _ ops _ defm_ids _ _) op
148   = defm_ids !! (classOpTag op - 1)
149 classSuperDictSelId (Class _ _ _ scs scsel_ids _ _ _ _ _) super_clas
150   = assoc "classSuperDictSelId" (scs `zip` scsel_ids) super_clas
151
152 classSig :: GenClass t u -> (t, [GenClass t u], [GenClassOp (GenType t u)])
153 classSig (Class _ _ tyvar super_classes _ ops _ _ _ _)
154   = (tyvar, super_classes, ops)
155
156 classBigSig (Class _ _ tyvar super_classes sdsels ops sels defms _ _)
157   = (tyvar, super_classes, sdsels, ops, sels, defms)
158
159 classInstEnv (Class _ _ _ _ _ _ _ _ inst_env _) = inst_env
160 \end{code}
161
162 @a `isSuperClassOf` b@ returns @Nothing@ if @a@ is not a superclass of
163 @b@, but if it is, it returns $@Just@~[k_1,\ldots,k_n]$, where the
164 $k_1,\ldots,k_n$ are exactly as described in the definition of the
165 @GenClass@ constructor above.
166
167 \begin{code}
168 isSuperClassOf :: Class -> Class -> Maybe [Class]
169 clas `isSuperClassOf` (Class _ _ _ _ _ _ _ _ _ links) = assocMaybe links clas
170 \end{code}
171
172 %************************************************************************
173 %*                                                                      *
174 \subsection[Class-instances]{Instance declarations for @Class@}
175 %*                                                                      *
176 %************************************************************************
177
178 We compare @Classes@ by their keys (which include @Uniques@).
179
180 \begin{code}
181 instance Ord3 (GenClass tyvar uvar) where
182   cmp (Class k1 _ _ _ _ _ _ _ _ _) (Class k2 _ _ _ _ _ _ _ _ _)  = cmp k1 k2
183
184 instance Eq (GenClass tyvar uvar) where
185     (Class k1 _ _ _ _ _ _ _ _ _) == (Class k2 _ _ _ _ _ _ _ _ _) = k1 == k2
186     (Class k1 _ _ _ _ _ _ _ _ _) /= (Class k2 _ _ _ _ _ _ _ _ _) = k1 /= k2
187
188 instance Ord (GenClass tyvar uvar) where
189     (Class k1 _ _ _ _ _ _ _ _ _) <= (Class k2 _ _ _ _ _ _ _ _ _) = k1 <= k2
190     (Class k1 _ _ _ _ _ _ _ _ _) <  (Class k2 _ _ _ _ _ _ _ _ _) = k1 <  k2
191     (Class k1 _ _ _ _ _ _ _ _ _) >= (Class k2 _ _ _ _ _ _ _ _ _) = k1 >= k2
192     (Class k1 _ _ _ _ _ _ _ _ _) >  (Class k2 _ _ _ _ _ _ _ _ _) = k1 >  k2
193     _tagCmp a b = case cmp a b of { LT_ -> _LT; EQ_ -> _EQ; GT__ -> _GT }
194 \end{code}
195
196 \begin{code}
197 instance Uniquable (GenClass tyvar uvar) where
198     uniqueOf (Class u _ _ _ _ _ _ _ _ _) = u
199
200 instance NamedThing (GenClass tyvar uvar) where
201     getName (Class _ n _ _ _ _ _ _ _ _) = n
202
203 instance NamedThing (GenClassOp ty) where
204     getOccName (ClassOp occ _ _) = occ
205 \end{code}
206
207
208 %************************************************************************
209 %*                                                                      *
210 \subsection[ClassOp-basic]{@ClassOp@: type and basic functions}
211 %*                                                                      *
212 %************************************************************************
213
214 A @ClassOp@ represents a a class operation.  From it and its parent
215 class we can construct the dictionary-selector @Id@ for the
216 operation/superclass dictionary, and the @Id@ for its default method.
217 It appears in a list inside the @Class@ object.
218
219 The type of a method in a @ClassOp@ object is its local type; that is,
220 without the overloading of the class itself.  For example, in the
221 declaration
222 \begin{pseudocode}
223         class Foo a where
224                 op :: Ord b => a -> b -> a
225 \end{pseudocode}
226 the type recorded for @op@ in the @ClassOp@ list of the @Class@ object is
227 just
228         $\forall \beta.~
229                 @Ord@~\beta \Rightarrow
230                 \alpha \rightarrow \beta \rightarrow alpha$
231
232 (where $\alpha$ is the class type variable recorded in the @Class@
233 object).  Of course, the type of @op@ recorded in the GVE will be its
234 ``full'' type
235
236         $\forall \alpha \forall \beta.~
237                 @Foo@~\alpha \Rightarrow
238                 ~@Ord@~\beta \Rightarrow \alpha
239                 \rightarrow \beta \rightarrow alpha$
240
241 ******************************************************************
242 **** That is, the type variables of a class op selector
243 ***  are all at the outer level.
244 ******************************************************************
245
246 \begin{code}
247 mkClassOp :: OccName -> Int -> ty -> GenClassOp ty
248 mkClassOp name tag ty = ClassOp name tag ty
249
250 classOpTag :: GenClassOp ty -> Int
251 classOpTag    (ClassOp _ tag _) = tag
252
253 classOpString :: GenClassOp ty -> FAST_STRING
254 classOpString (ClassOp occ _ _) = occNameString occ
255
256 classOpLocalType :: GenClassOp ty -> ty {-SigmaType-}
257 classOpLocalType (ClassOp _ _ ty) = ty
258 \end{code}
259
260 Rather unsavoury ways of getting ClassOp tags:
261 \begin{code}
262 classOpTagByOccName_maybe :: Class -> OccName -> Maybe Int
263 classOpTagByOccName       :: Class -> OccName -> Int
264
265 classOpTagByOccName clas op
266   = case (classOpTagByOccName_maybe clas op) of
267       Just tag -> tag
268 #ifdef DEBUG
269       Nothing  -> pprPanic "classOpTagByOccName:" (ppCat (ppr PprDebug op : map (ppPStr . classOpString) (classOps clas)))
270 #endif
271
272 classOpTagByOccName_maybe clas op
273   = go (classOps clas) 1
274   where
275     go []                     _   = Nothing
276     go (ClassOp occ _ _ : ns) tag = if occ == op
277                                     then Just tag
278                                     else go ns (tag+1)
279 \end{code}
280
281 %************************************************************************
282 %*                                                                      *
283 \subsection[ClassOp-instances]{Instance declarations for @ClassOp@}
284 %*                                                                      *
285 %************************************************************************
286
287 @ClassOps@ are compared by their tags.
288
289 \begin{code}
290 instance Eq (GenClassOp ty) where
291     (ClassOp _ i1 _) == (ClassOp _ i2 _) = i1 == i2
292     (ClassOp _ i1 _) /= (ClassOp _ i2 _) = i1 == i2
293
294 instance Ord (GenClassOp ty) where
295     (ClassOp _ i1 _) <= (ClassOp _ i2 _) = i1 <= i2
296     (ClassOp _ i1 _) <  (ClassOp _ i2 _) = i1 <  i2
297     (ClassOp _ i1 _) >= (ClassOp _ i2 _) = i1 >= i2
298     (ClassOp _ i1 _) >  (ClassOp _ i2 _) = i1 >  i2
299     -- ToDo: something for _tagCmp? (WDP 94/10)
300 \end{code}