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