[project @ 2000-11-20 14:48:52 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, ArgVrcs, AlgTyConFlavour(..),
9
10         isFunTyCon, isUnLiftedTyCon, isBoxedTyCon, isProductTyCon,
11         isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
12         isEnumerationTyCon, 
13         isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity,
14         isRecursiveTyCon, newTyConRep,
15
16         mkAlgTyCon, --mkAlgTyCon, 
17         mkClassTyCon,
18         mkFunTyCon,
19         mkPrimTyCon,
20         mkTupleTyCon,
21         mkSynTyCon,
22         mkKindCon,
23         mkSuperKindCon,
24
25         setTyConName,
26
27         tyConName,
28         tyConKind,
29         tyConUnique,
30         tyConTyVars,
31         tyConArgVrcs_maybe,
32         tyConDataCons, tyConDataConsIfAvailable, tyConFamilySize,
33         tyConSelIds,
34         tyConTheta,
35         tyConPrimRep,
36         tyConArity,
37         isClassTyCon,
38         getSynTyConDefn,
39
40         maybeTyConSingleCon,
41
42         matchesTyCon,
43
44         -- Generics
45         tyConGenIds, tyConGenInfo
46 ) where
47
48 #include "HsVersions.h"
49
50 import {-# SOURCE #-} TypeRep ( Type, Kind, SuperKind )
51  -- Should just be Type(Type), but this fails due to bug present up to
52  -- and including 4.02 involving slurping of hi-boot files.  Bug is now fixed.
53
54 import {-# SOURCE #-} DataCon ( DataCon, isExistentialDataCon )
55
56
57 import Class            ( ClassContext )
58 import Var              ( TyVar, Id )
59 import BasicTypes       ( Arity, RecFlag(..), Boxity(..), 
60                           isBoxed, EP(..) )
61 import Name             ( Name, nameUnique, NamedThing(getName) )
62 import PrelNames        ( Unique, Uniquable(..), anyBoxConKey )
63 import PrimRep          ( PrimRep(..), isFollowableRep )
64 import Outputable
65 \end{code}
66
67 %************************************************************************
68 %*                                                                      *
69 \subsection{The data type}
70 %*                                                                      *
71 %************************************************************************
72
73 \begin{code}
74 type KindCon      = TyCon
75 type SuperKindCon = TyCon
76
77 data TyCon
78   = FunTyCon {
79         tyConUnique :: Unique,
80         tyConName   :: Name,
81         tyConKind   :: Kind,
82         tyConArity  :: Arity
83     }
84
85
86   | AlgTyCon {          -- Tuples, data type, and newtype decls.
87                         -- All lifted, all boxed
88         tyConUnique :: Unique,
89         tyConName   :: Name,
90         tyConKind   :: Kind,
91         tyConArity  :: Arity,
92         
93         tyConTyVars   :: [TyVar],
94         tyConArgVrcs  :: ArgVrcs,
95         algTyConTheta :: ClassContext,
96
97         dataCons :: [DataCon],
98                 -- Its data constructors, with fully polymorphic types
99                 --      This list can be empty, when we import a data type abstractly,
100                 --      either (a) the interface is hand-written and doesn't give
101                 --                 the constructors, or
102                 --             (b) in a quest for fast compilation we don't import 
103                 --                 the constructors
104
105         selIds :: [Id], -- Its record selectors (if any)
106
107         noOfDataCons :: Int,    -- Number of data constructors
108                                 -- Usually this is the same as the length of the
109                                 -- dataCons field, but the latter may be empty if
110                                 -- we imported the type abstractly.  But even if we import
111                                 -- abstractly we still need to know the number of constructors
112                                 -- so we can get the return convention right.  Tiresome!
113                                 
114         algTyConFlavour :: AlgTyConFlavour,
115         algTyConRec     :: RecFlag,             -- Tells whether the data type is part of 
116                                                 -- a mutually-recursive group or not
117
118         genInfo :: Maybe (EP Id),       -- Convert T <-> Tring
119                                         -- Some TyCons don't have it; 
120                                         -- e.g. the TyCon for a Class dictionary,
121                                         -- and TyCons with unboxed arguments
122
123         algTyConClass :: Bool           -- True if this tycon comes from a class declaration
124     }
125
126   | PrimTyCon {         -- Primitive types; cannot be defined in Haskell
127                         -- NB: All of these guys are *unlifted*, but not all are *unboxed*
128         tyConUnique  :: Unique,
129         tyConName    :: Name,
130         tyConKind    :: Kind,
131         tyConArity   :: Arity,
132         tyConArgVrcs :: ArgVrcs,
133         primTyConRep :: PrimRep
134     }
135
136   | TupleTyCon {
137
138         tyConUnique :: Unique,
139         tyConName   :: Name,
140         tyConKind   :: Kind,
141         tyConArity  :: Arity,
142         tyConBoxed  :: Boxity,
143         tyConTyVars :: [TyVar],
144         dataCon     :: DataCon,
145         genInfo     :: Maybe (EP Id)            -- Generic type and conv funs 
146     }
147
148   | SynTyCon {
149         tyConUnique :: Unique,
150         tyConName   :: Name,
151         tyConKind   :: Kind,
152         tyConArity  :: Arity,
153
154         tyConTyVars     :: [TyVar],     -- Bound tyvars
155         synTyConDefn    :: Type,        -- Right-hand side, mentioning these type vars.
156                                         -- Acts as a template for the expansion when
157                                         -- the tycon is applied to some types.
158         tyConArgVrcs :: ArgVrcs
159     }
160
161   | KindCon {           -- Type constructor at the kind level
162         tyConUnique :: Unique,
163         tyConName   :: Name,
164         tyConKind   :: SuperKind,
165         tyConArity  :: Arity
166     }
167
168   | SuperKindCon        {               -- The type of kind variables or boxity variables,
169         tyConUnique :: Unique,
170         tyConName   :: Name
171     }
172
173 type ArgVrcs = [(Bool,Bool)]  -- Tyvar variance info: [(occPos,occNeg)]
174
175 data AlgTyConFlavour
176   = DataTyCon           -- Data type
177   | EnumTyCon           -- Special sort of enumeration type
178   | NewTyCon Type       -- Newtype, with its *ultimate* representation type
179                         -- By 'ultimate' I mean that the rep type is not itself
180                         -- a newtype or type synonym.
181
182                         -- The rep type has explicit for-alls for the tyvars of
183                         -- the TyCon.  Thus:
184                         --      newtype T a = MkT [(a,Int)]
185                         -- The rep type is forall a. [(a,Int)]
186                         --
187                         -- The rep type isn't entirely simple:
188                         --  for a recursive newtype we pick () as the rep type
189                         --      newtype T = MkT T
190 \end{code}
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection{TyCon Construction}
195 %*                                                                      *
196 %************************************************************************
197
198 Note: the TyCon constructors all take a Kind as one argument, even though
199 they could, in principle, work out their Kind from their other arguments.
200 But to do so they need functions from Types, and that makes a nasty
201 module mutual-recursion.  And they aren't called from many places.
202 So we compromise, and move their Kind calculation to the call site.
203
204 \begin{code}
205 mkSuperKindCon :: Name -> SuperKindCon
206 mkSuperKindCon name = SuperKindCon {
207                         tyConUnique = nameUnique name,
208                         tyConName = name
209                       }
210
211 mkKindCon :: Name -> SuperKind -> KindCon
212 mkKindCon name kind
213   = KindCon { 
214         tyConUnique = nameUnique name,
215         tyConName = name,
216         tyConArity = 0,
217         tyConKind = kind
218      }
219
220 mkFunTyCon :: Name -> Kind -> TyCon
221 mkFunTyCon name kind 
222   = FunTyCon { 
223         tyConUnique = nameUnique name,
224         tyConName   = name,
225         tyConKind   = kind,
226         tyConArity  = 2
227     }
228
229 tyConGenInfo :: TyCon -> Maybe (EP Id)
230 tyConGenInfo (AlgTyCon   { genInfo = info }) = info
231 tyConGenInfo (TupleTyCon { genInfo = info }) = info
232 tyConGenInfo other                           = Nothing
233
234 tyConGenIds :: TyCon -> [Id]
235 -- Returns the generic-programming Ids; these Ids need bindings
236 tyConGenIds tycon = case tyConGenInfo tycon of
237                         Nothing           -> []
238                         Just (EP from to) -> [from,to]
239
240 -- This is the making of a TyCon. Just the same as the old mkAlgTyCon,
241 -- but now you also have to pass in the generic information about the type
242 -- constructor - you can get hold of it easily (see Generics module)
243 mkAlgTyCon name kind tyvars theta argvrcs cons ncons sels flavour rec 
244               gen_info
245   = AlgTyCon {  
246         tyConName               = name,
247         tyConUnique             = nameUnique name,
248         tyConKind               = kind,
249         tyConArity              = length tyvars,
250         tyConTyVars             = tyvars,
251         tyConArgVrcs            = argvrcs,
252         algTyConTheta           = theta,
253         dataCons                = cons, 
254         selIds                  = sels,
255         noOfDataCons            = ncons,
256         algTyConClass           = False,
257         algTyConFlavour         = flavour,
258         algTyConRec             = rec,
259         genInfo                 = gen_info
260     }
261
262 mkClassTyCon name kind tyvars argvrcs con clas flavour
263   = AlgTyCon {  
264         tyConName               = name,
265         tyConUnique             = nameUnique name,
266         tyConKind               = kind,
267         tyConArity              = length tyvars,
268         tyConTyVars             = tyvars,
269         tyConArgVrcs            = argvrcs,
270         algTyConTheta           = [],
271         dataCons                = [con],
272         selIds                  = [],
273         noOfDataCons            = 1,
274         algTyConClass           = True,
275         algTyConFlavour         = flavour,
276         algTyConRec             = NonRecursive,
277         genInfo                 = Nothing
278     }
279
280
281 mkTupleTyCon name kind arity tyvars con boxed gen_info
282   = TupleTyCon {
283         tyConUnique = nameUnique name,
284         tyConName = name,
285         tyConKind = kind,
286         tyConArity = arity,
287         tyConBoxed = boxed,
288         tyConTyVars = tyvars,
289         dataCon = con,
290         genInfo = gen_info
291     }
292
293 mkPrimTyCon name kind arity arg_vrcs rep 
294   = PrimTyCon {
295         tyConName = name,
296         tyConUnique = nameUnique name,
297         tyConKind = kind,
298         tyConArity = arity,
299         tyConArgVrcs = arg_vrcs,
300         primTyConRep = rep
301     }
302
303 mkSynTyCon name kind arity tyvars rhs argvrcs
304   = SynTyCon {  
305         tyConName = name,
306         tyConUnique = nameUnique name,
307         tyConKind = kind,
308         tyConArity = arity,
309         tyConTyVars = tyvars,
310         synTyConDefn = rhs,
311         tyConArgVrcs = argvrcs
312     }
313
314 setTyConName tc name = tc {tyConName = name, tyConUnique = nameUnique name}
315
316 \end{code}
317
318 \begin{code}
319 isFunTyCon (FunTyCon {}) = True
320 isFunTyCon _             = False
321
322 isPrimTyCon (PrimTyCon {}) = True
323 isPrimTyCon _              = False
324
325 isUnLiftedTyCon (PrimTyCon {}) = True
326 isUnLiftedTyCon (TupleTyCon { tyConBoxed = boxity}) = not (isBoxed boxity)
327 isUnLiftedTyCon _              = False
328
329 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
330 isBoxedTyCon (AlgTyCon {}) = True
331 isBoxedTyCon (FunTyCon {}) = True
332 isBoxedTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
333 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
334
335 -- isAlgTyCon returns True for both @data@ and @newtype@
336 isAlgTyCon (AlgTyCon {})   = True
337 isAlgTyCon (TupleTyCon {}) = True
338 isAlgTyCon other           = False
339
340 -- isDataTyCon returns False for @newtype@ and for unboxed tuples
341 isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data})  = case new_or_data of
342                                                                 NewTyCon _ -> False
343                                                                 other   -> True
344 isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
345 isDataTyCon other = False
346
347 isNewTyCon (AlgTyCon {algTyConFlavour = NewTyCon _}) = True 
348 isNewTyCon other                                     = False
349
350 newTyConRep (AlgTyCon {algTyConFlavour = NewTyCon rep}) = Just rep
351 newTyConRep other                                       = Nothing
352
353 -- A "product" tycon
354 --      has *one* constructor, 
355 --      is *not* existential
356 -- but
357 --      may be  DataType or NewType, 
358 --      may be  unboxed or not, 
359 --      may be  recursive or not
360 isProductTyCon (AlgTyCon {dataCons = [data_con]}) = not (isExistentialDataCon data_con)
361 isProductTyCon (TupleTyCon {})                    = True
362 isProductTyCon other                              = False
363
364 isSynTyCon (SynTyCon {}) = True
365 isSynTyCon _             = False
366
367 isEnumerationTyCon (AlgTyCon {algTyConFlavour = EnumTyCon}) = True
368 isEnumerationTyCon other                                    = False
369
370 -- The unit tycon didn't used to be classed as a tuple tycon
371 -- but I thought that was silly so I've undone it
372 -- If it can't be for some reason, it should be a AlgTyCon
373 isTupleTyCon (TupleTyCon {}) = True
374 isTupleTyCon other           = False
375
376 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
377 isUnboxedTupleTyCon other = False
378
379 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
380 isBoxedTupleTyCon other = False
381
382 tupleTyConBoxity tc = tyConBoxed tc
383
384 isRecursiveTyCon (AlgTyCon {algTyConRec = Recursive}) = True
385 isRecursiveTyCon other                                = False
386 \end{code}
387
388 \begin{code}
389 tyConDataCons :: TyCon -> [DataCon]
390 tyConDataCons tycon = ASSERT2( not (null cons), ppr tycon ) cons
391                     where
392                       cons = tyConDataConsIfAvailable tycon
393
394 tyConDataConsIfAvailable (AlgTyCon {dataCons = cons}) = cons    -- Empty for abstract types
395 tyConDataConsIfAvailable (TupleTyCon {dataCon = con}) = [con]
396 tyConDataConsIfAvailable other                        = []
397         -- You may think this last equation should fail,
398         -- but it's quite convenient to return no constructors for
399         -- a synonym; see for example the call in TcTyClsDecls.
400
401 tyConFamilySize  :: TyCon -> Int
402 tyConFamilySize (AlgTyCon {noOfDataCons = n}) = n
403 tyConFamilySize (TupleTyCon {})               = 1
404 #ifdef DEBUG
405 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
406 #endif
407
408 tyConSelIds :: TyCon -> [Id]
409 tyConSelIds (AlgTyCon {selIds = sels}) = sels
410 tyConSelIds other_tycon                = []
411 \end{code}
412
413 \begin{code}
414 tyConPrimRep :: TyCon -> PrimRep
415 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
416 tyConPrimRep _                                = PtrRep
417 \end{code}
418
419 \begin{code}
420 tyConTheta :: TyCon -> ClassContext
421 tyConTheta (AlgTyCon {algTyConTheta = theta}) = theta
422 -- should ask about anything else
423 \end{code}
424
425 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
426 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
427 actually computed (in another file).
428
429 \begin{code}
430 tyConArgVrcs_maybe :: TyCon -> Maybe ArgVrcs
431
432 tyConArgVrcs_maybe (FunTyCon   {}                     ) = Just [(False,True),(True,False)]
433 tyConArgVrcs_maybe (AlgTyCon   {tyConArgVrcs = oi})     = Just oi
434 tyConArgVrcs_maybe (PrimTyCon  {tyConArgVrcs = oi})     = Just oi
435 tyConArgVrcs_maybe (TupleTyCon {tyConArity = arity   }) = Just (replicate arity (True,False))
436 tyConArgVrcs_maybe (SynTyCon   {tyConArgVrcs = oi })    = Just oi
437 tyConArgVrcs_maybe _                                    = Nothing
438 \end{code}
439
440 \begin{code}
441 getSynTyConDefn :: TyCon -> ([TyVar], Type)
442 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
443 \end{code}
444
445 \begin{code}
446 maybeTyConSingleCon :: TyCon -> Maybe DataCon
447 maybeTyConSingleCon (AlgTyCon {dataCons = [c]})  = Just c
448 maybeTyConSingleCon (AlgTyCon {})                = Nothing
449 maybeTyConSingleCon (TupleTyCon {dataCon = con}) = Just con
450 maybeTyConSingleCon (PrimTyCon {})               = Nothing
451 maybeTyConSingleCon (FunTyCon {})                = Nothing  -- case at funty
452 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $
453                          ppr tc
454 \end{code}
455
456 \begin{code}
457 isClassTyCon :: TyCon -> Bool
458 isClassTyCon (AlgTyCon {algTyConClass = is_class_tycon}) = is_class_tycon
459 isClassTyCon other_tycon                                 = False
460 \end{code}
461
462
463 %************************************************************************
464 %*                                                                      *
465 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
466 %*                                                                      *
467 %************************************************************************
468
469 @TyCon@s are compared by comparing their @Unique@s.
470
471 The strictness analyser needs @Ord@. It is a lexicographic order with
472 the property @(a<=b) || (b<=a)@.
473
474 \begin{code}
475 instance Eq TyCon where
476     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
477     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
478
479 instance Ord TyCon where
480     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
481     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
482     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
483     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
484     compare a b = getUnique a `compare` getUnique b
485
486 instance Uniquable TyCon where
487     getUnique tc = tyConUnique tc
488
489 instance Outputable TyCon where
490     ppr tc  = ppr (getName tc) 
491
492 instance NamedThing TyCon where
493     getName = tyConName
494 \end{code}
495
496
497 %************************************************************************
498 %*                                                                      *
499 \subsection{Kind constructors}
500 %*                                                                      *
501 %************************************************************************
502
503 @matchesTyCon tc1 tc2@ checks whether an appliation
504 (tc1 t1..tn) matches (tc2 t1..tn).  By "matches" we basically mean "equals",
505 except that at the kind level tc2 might have more boxity info than tc1.
506
507 \begin{code}
508 matchesTyCon :: TyCon   -- Expected (e.g. arg type of function)
509              -> TyCon   -- Inferred (e.g. type of actual arg to function)
510              -> Bool
511
512 matchesTyCon tc1 tc2 =  uniq1 == uniq2 || uniq1 == anyBoxConKey
513                      where
514                         uniq1 = tyConUnique tc1
515                         uniq2 = tyConUnique tc2
516 \end{code}
517
518
519