[project @ 1998-12-22 16:31:28 by simonpj]
[ghc-hetmet.git] / ghc / compiler / types / TyCon.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[TyCon]{The @TyCon@ datatype}
5
6 \begin{code}
7 module TyCon(
8         TyCon, KindCon, SuperKindCon,
9
10         isFunTyCon, isUnLiftedTyCon, isBoxedTyCon, isProductTyCon,
11         isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
12         isEnumerationTyCon, isTupleTyCon, isUnboxedTupleTyCon,
13
14         mkAlgTyCon,
15         mkFunTyCon,
16         mkPrimTyCon,
17         mkTupleTyCon,
18         mkSynTyCon,
19         mkKindCon,
20         mkSuperKindCon,
21
22         tyConKind,
23         tyConUnique,
24         tyConTyVars,
25         tyConDataCons,
26         tyConFamilySize,
27         tyConDerivings,
28         tyConTheta,
29         tyConPrimRep,
30         tyConArity,
31         tyConClass_maybe,
32         getSynTyConDefn,
33
34         maybeTyConSingleCon,
35
36         matchesTyCon
37 ) where
38
39 #include "HsVersions.h"
40
41 import {-# SOURCE #-} Type  ( Type, Kind, SuperKind )
42 import {-# SOURCE #-} DataCon ( DataCon )
43
44 import Class            ( Class )
45 import Var              ( TyVar )
46 import BasicTypes       ( Arity, NewOrData(..), RecFlag(..) )
47 import Maybes
48 import Name             ( Name, nameUnique, NamedThing(getName) )
49 import Unique           ( Unique, Uniquable(..), anyBoxConKey )
50 import PrimRep          ( PrimRep(..), isFollowableRep )
51 import Outputable
52 \end{code}
53
54 %************************************************************************
55 %*                                                                      *
56 \subsection{The data type}
57 %*                                                                      *
58 %************************************************************************
59
60 \begin{code}
61 type KindCon      = TyCon
62 type SuperKindCon = TyCon
63
64 data TyCon
65   = FunTyCon {
66         tyConUnique :: Unique,
67         tyConName   :: Name,
68         tyConKind   :: Kind,
69         tyConArity  :: Arity
70     }
71
72
73   | AlgTyCon {          -- Tuples, data type, and newtype decls.
74                         -- All lifted, all boxed
75         tyConUnique :: Unique,
76         tyConName   :: Name,
77         tyConKind   :: Kind,
78         tyConArity  :: Arity,
79         
80         tyConTyVars     :: [TyVar],
81         dataTyConTheta  :: [(Class,[Type])],
82
83         dataCons :: [DataCon],
84                 -- Its data constructors, with fully polymorphic types
85                 --      This list can be empty, when we import a data type abstractly,
86                 --      either (a) the interface is hand-written and doesn't give
87                 --                 the constructors, or
88                 --             (b) in a quest for fast compilation we don't import 
89                 --                 the constructors
90
91         dataTyConDerivings   :: [Class],        -- Classes which have derived instances
92
93         dataTyConClass_maybe :: (Maybe Class),  -- Nothing for ordinary types; 
94                                                 -- Just c for the type constructor
95                                                 -- for dictionaries of class c.
96         algTyConFlavour :: NewOrData,
97         algTyConRec     :: RecFlag              -- Tells whether the data type is part of 
98                                                 -- a mutually-recursive group or not
99     }
100
101   | PrimTyCon {         -- Primitive types; cannot be defined in Haskell
102                         -- NB: All of these guys are *unlifted*, but not all are *unboxed*
103         tyConUnique  :: Unique,
104         tyConName    :: Name,
105         tyConKind    :: Kind,
106         tyConArity   :: Arity,
107         primTyConRep :: PrimRep
108     }
109
110   | TupleTyCon {
111
112         tyConUnique :: Unique,
113         tyConName   :: Name,
114         tyConKind   :: Kind,
115         tyConArity  :: Arity,
116         tyConBoxed  :: Bool,            -- True for boxed; False for unboxed
117         tyConTyVars :: [TyVar],
118         dataCon     :: DataCon
119     }
120
121   | SynTyCon {
122         tyConUnique :: Unique,
123         tyConName   :: Name,
124         tyConKind   :: Kind,
125         tyConArity  :: Arity,
126
127         tyConTyVars :: [TyVar],         -- Bound tyvars
128         synTyConDefn :: Type            -- Right-hand side, mentioning these type vars.
129                                         -- Acts as a template for the expansion when
130                                         -- the tycon is applied to some types.
131     }
132
133   | KindCon {           -- Type constructor at the kind level
134         tyConUnique :: Unique,
135         tyConName   :: Name,
136         tyConKind   :: SuperKind,
137         tyConArity  :: Arity
138     }
139
140   | SuperKindCon        {               -- The type of kind variables or boxity variables,
141         tyConUnique :: Unique,
142         tyConName   :: Name
143     }
144 \end{code}
145
146 %************************************************************************
147 %*                                                                      *
148 \subsection{TyCon Construction}
149 %*                                                                      *
150 %************************************************************************
151
152 Note: the TyCon constructors all take a Kind as one argument, even though
153 they could, in principle, work out their Kind from their other arguments.
154 But to do so they need functions from Types, and that makes a nasty
155 module mutual-recursion.  And they aren't called from many places.
156 So we compromise, and move their Kind calculation to the call site.
157
158 \begin{code}
159 mkSuperKindCon :: Name -> SuperKindCon
160 mkSuperKindCon name = SuperKindCon {
161                         tyConUnique = nameUnique name,
162                         tyConName = name
163                       }
164
165 mkKindCon :: Name -> SuperKind -> KindCon
166 mkKindCon name kind
167   = KindCon { 
168         tyConUnique = nameUnique name,
169         tyConName = name,
170         tyConArity = 0,
171         tyConKind = kind
172      }
173
174 mkFunTyCon :: Name -> Kind -> TyCon
175 mkFunTyCon name kind 
176   = FunTyCon { 
177         tyConUnique = nameUnique name,
178         tyConName   = name,
179         tyConKind   = kind,
180         tyConArity  = 2
181     }
182                             
183 mkAlgTyCon name kind tyvars theta cons derivs maybe_clas flavour rec
184   = AlgTyCon {  
185         tyConName = name,
186         tyConUnique = nameUnique name,
187         tyConKind = kind,
188         tyConArity = length tyvars,
189         tyConTyVars = tyvars,
190         dataTyConTheta = theta,
191         dataCons = cons,
192         dataTyConDerivings = derivs,
193         dataTyConClass_maybe = maybe_clas,
194         algTyConFlavour = flavour,
195         algTyConRec = rec
196     }
197
198 mkTupleTyCon name kind arity tyvars con boxed
199   = TupleTyCon {
200         tyConUnique = nameUnique name,
201         tyConName = name,
202         tyConKind = kind,
203         tyConArity = arity,
204         tyConBoxed = boxed,
205         tyConTyVars = tyvars,
206         dataCon = con
207     }
208
209 mkPrimTyCon name kind arity rep 
210   = PrimTyCon {
211         tyConName = name,
212         tyConUnique = nameUnique name,
213         tyConKind = kind,
214         tyConArity = arity,
215         primTyConRep = rep
216     }
217
218 mkSynTyCon name kind arity tyvars rhs 
219   = SynTyCon {  
220         tyConName = name,
221         tyConUnique = nameUnique name,
222         tyConKind = kind,
223         tyConArity = arity,
224         tyConTyVars = tyvars,
225         synTyConDefn = rhs
226     }
227 \end{code}
228
229 \begin{code}
230 isFunTyCon (FunTyCon {}) = True
231 isFunTyCon _             = False
232
233 isPrimTyCon (PrimTyCon {}) = True
234 isPrimTyCon _              = False
235
236 isUnLiftedTyCon (PrimTyCon {}) = True
237 isUnLiftedTyCon (TupleTyCon { tyConBoxed = False }) = True
238 isUnLiftedTyCon _              = False
239
240 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
241 isBoxedTyCon (AlgTyCon {}) = True
242 isBoxedTyCon (FunTyCon {}) = True
243 isBoxedTyCon (TupleTyCon {tyConBoxed = boxed}) = boxed
244 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
245
246 -- isAlgTyCon returns True for both @data@ and @newtype@
247 isAlgTyCon (AlgTyCon {})   = True
248 isAlgTyCon (TupleTyCon {}) = True
249 isAlgTyCon other           = False
250
251 -- isDataTyCon returns False for @newtype@ and for unboxed tuples
252 isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data})  = case new_or_data of
253                                                                 NewType -> False
254                                                                 other   -> True
255 isDataTyCon (TupleTyCon {tyConBoxed = True}) = True     
256 isDataTyCon other = False
257
258 isNewTyCon (AlgTyCon {algTyConFlavour = NewType}) = True 
259 isNewTyCon other                                  = False
260
261 -- A "product" tycon is non-recursive and has one constructor,
262 -- whether DataType or NewType
263 isProductTyCon (AlgTyCon {dataCons = [c], algTyConRec = NonRecursive}) = True
264 isProductTyCon (TupleTyCon {}) = True
265 isProductTyCon other = False
266
267 isSynTyCon (SynTyCon {}) = True
268 isSynTyCon _             = False
269
270 isEnumerationTyCon (AlgTyCon {algTyConFlavour = EnumType}) = True
271 isEnumerationTyCon other                                   = False
272
273 -- The unit tycon isn't classed as a tuple tycon
274 isTupleTyCon (TupleTyCon {tyConArity = arity, tyConBoxed = True}) = arity >= 2
275 isTupleTyCon other = False
276
277 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = False}) = True
278 isUnboxedTupleTyCon other = False
279 \end{code}
280
281 \begin{code}
282 tyConDataCons :: TyCon -> [DataCon]
283 tyConDataCons (AlgTyCon {dataCons = cons}) = cons
284 tyConDataCons (TupleTyCon {dataCon = con}) = [con]
285 tyConDataCons other                        = []
286         -- You may think this last equation should fail,
287         -- but it's quite convenient to return no constructors for
288         -- a synonym; see for example the call in TcTyClsDecls.
289
290 tyConFamilySize  :: TyCon -> Int
291 tyConFamilySize (AlgTyCon {dataCons = cons}) = length cons
292 tyConFamilySize (TupleTyCon {}) = 1
293 #ifdef DEBUG
294 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
295 #endif
296
297 tyConPrimRep :: TyCon -> PrimRep
298 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
299 tyConPrimRep _                                = PtrRep
300 \end{code}
301
302 \begin{code}
303 tyConDerivings :: TyCon -> [Class]
304 tyConDerivings (AlgTyCon {dataTyConDerivings = derivs}) = derivs
305 tyConDerivings other                                    = []
306 \end{code}
307
308 \begin{code}
309 tyConTheta :: TyCon -> [(Class, [Type])]
310 tyConTheta (AlgTyCon {dataTyConTheta = theta}) = theta
311 -- should ask about anything else
312 \end{code}
313
314 \begin{code}
315 getSynTyConDefn :: TyCon -> ([TyVar], Type)
316 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
317 \end{code}
318
319 \begin{code}
320 maybeTyConSingleCon :: TyCon -> Maybe DataCon
321 maybeTyConSingleCon (AlgTyCon {dataCons = [c]})  = Just c
322 maybeTyConSingleCon (AlgTyCon {})                = Nothing
323 maybeTyConSingleCon (TupleTyCon {dataCon = con}) = Just con
324 maybeTyConSingleCon (PrimTyCon {})               = Nothing
325 \end{code}
326
327 \begin{code}
328 tyConClass_maybe :: TyCon -> Maybe Class
329 tyConClass_maybe (AlgTyCon {dataTyConClass_maybe = maybe_cls}) = maybe_cls
330 tyConClass_maybe other_tycon                                   = Nothing
331 \end{code}
332
333
334 %************************************************************************
335 %*                                                                      *
336 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
337 %*                                                                      *
338 %************************************************************************
339
340 @TyCon@s are compared by comparing their @Unique@s.
341
342 The strictness analyser needs @Ord@. It is a lexicographic order with
343 the property @(a<=b) || (b<=a)@.
344
345 \begin{code}
346 instance Eq TyCon where
347     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
348     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
349
350 instance Ord TyCon where
351     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
352     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
353     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
354     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
355     compare a b = getUnique a `compare` getUnique b
356
357 instance Uniquable TyCon where
358     getUnique tc = tyConUnique tc
359
360 instance Outputable TyCon where
361     ppr tc  = ppr (getName tc)
362
363 instance NamedThing TyCon where
364     getName = tyConName
365 \end{code}
366
367
368 %************************************************************************
369 %*                                                                      *
370 \subsection{Kind constructors}
371 %*                                                                      *
372 %************************************************************************
373
374 @matchesTyCon tc1 tc2@ checks whether an appliation
375 (tc1 t1..tn) matches (tc2 t1..tn).  By "matches" we basically mean "equals",
376 except that at the kind level tc2 might have more boxity info than tc1.
377
378 \begin{code}
379 matchesTyCon :: TyCon   -- Expected (e.g. arg type of function)
380              -> TyCon   -- Inferred (e.g. type of actual arg to function)
381              -> Bool
382
383 matchesTyCon tc1 tc2 =  uniq1 == uniq2 || uniq1 == anyBoxConKey
384                      where
385                         uniq1 = tyConUnique tc1
386                         uniq2 = tyConUnique tc2
387 \end{code}