[project @ 2003-06-25 16:24:56 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           ( orElse )
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                         -- The rep type isn't entirely simple:
185                         --  for a recursive newtype we pick () as the rep type
186                         --      newtype T = MkT T
187                         --
188                         -- The rep type has free type variables the tyConTyVars
189                         -- Thus:
190                         --      newtype T a = MkT [(a,Int)]
191                         -- The rep type is [(a,Int)]
192         -- NB: the rep type isn't necessarily the original RHS of the
193         --     newtype decl, because the rep type looks through other
194         --     newtypes.  If you want hte original RHS, look at the 
195         --     argument type of the data constructor.
196
197 data DataConDetails datacon
198   = DataCons [datacon]  -- Its data constructors, with fully polymorphic types
199                         -- A type can have zero constructors
200
201   | Unknown             -- We're importing this data type from an hi-boot file
202                         -- and we don't know what its constructors are
203
204   | HasCons Int         -- In a quest for compilation speed we have imported
205                         -- only the number of constructors (to get return 
206                         -- conventions right) but not the constructors themselves
207
208 visibleDataCons (DataCons cs) = cs
209 visibleDataCons other         = []
210 \end{code}
211
212
213 %************************************************************************
214 %*                                                                      *
215 \subsection{TyCon Construction}
216 %*                                                                      *
217 %************************************************************************
218
219 Note: the TyCon constructors all take a Kind as one argument, even though
220 they could, in principle, work out their Kind from their other arguments.
221 But to do so they need functions from Types, and that makes a nasty
222 module mutual-recursion.  And they aren't called from many places.
223 So we compromise, and move their Kind calculation to the call site.
224
225 \begin{code}
226 mkSuperKindCon :: Name -> SuperKindCon
227 mkSuperKindCon name = SuperKindCon {
228                         tyConUnique = nameUnique name,
229                         tyConName = name
230                       }
231
232 mkKindCon :: Name -> SuperKind -> KindCon
233 mkKindCon name kind
234   = KindCon { 
235         tyConUnique = nameUnique name,
236         tyConName = name,
237         tyConArity = 0,
238         tyConKind = kind
239      }
240
241 mkFunTyCon :: Name -> Kind -> TyCon
242 mkFunTyCon name kind 
243   = FunTyCon { 
244         tyConUnique = nameUnique name,
245         tyConName   = name,
246         tyConKind   = kind,
247         tyConArity  = 2
248     }
249
250 tyConGenInfo :: TyCon -> Maybe (EP Id)
251 tyConGenInfo (AlgTyCon   { genInfo = info }) = info
252 tyConGenInfo (TupleTyCon { genInfo = info }) = info
253 tyConGenInfo other                           = Nothing
254
255 tyConGenIds :: TyCon -> [Id]
256 -- Returns the generic-programming Ids; these Ids need bindings
257 tyConGenIds tycon = case tyConGenInfo tycon of
258                         Nothing           -> []
259                         Just (EP from to) -> [from,to]
260
261 -- This is the making of a TyCon. Just the same as the old mkAlgTyCon,
262 -- but now you also have to pass in the generic information about the type
263 -- constructor - you can get hold of it easily (see Generics module)
264 mkAlgTyCon name kind tyvars theta argvrcs cons sels flavour is_rec 
265               gen_info
266   = AlgTyCon {  
267         tyConName               = name,
268         tyConUnique             = nameUnique name,
269         tyConKind               = kind,
270         tyConArity              = length tyvars,
271         tyConTyVars             = tyvars,
272         tyConArgVrcs            = argvrcs,
273         algTyConTheta           = theta,
274         dataCons                = cons, 
275         selIds                  = sels,
276         algTyConClass           = Nothing,
277         algTyConFlavour         = flavour,
278         algTyConRec             = is_rec,
279         genInfo                 = gen_info
280     }
281
282 mkClassTyCon name kind tyvars argvrcs con clas flavour is_rec
283   = AlgTyCon {  
284         tyConName               = name,
285         tyConUnique             = nameUnique name,
286         tyConKind               = kind,
287         tyConArity              = length tyvars,
288         tyConTyVars             = tyvars,
289         tyConArgVrcs            = argvrcs,
290         algTyConTheta           = [],
291         dataCons                = DataCons [con],
292         selIds                  = [],
293         algTyConClass           = Just clas,
294         algTyConFlavour         = flavour,
295         algTyConRec             = is_rec,
296         genInfo                 = Nothing
297     }
298
299
300 mkTupleTyCon name kind arity tyvars con boxed gen_info
301   = TupleTyCon {
302         tyConUnique = nameUnique name,
303         tyConName = name,
304         tyConKind = kind,
305         tyConArity = arity,
306         tyConBoxed = boxed,
307         tyConTyVars = tyvars,
308         dataCon = con,
309         genInfo = gen_info
310     }
311
312 -- Foreign-imported (.NET) type constructors are represented
313 -- as primitive, but *lifted*, TyCons for now. They are lifted
314 -- because the Haskell type T representing the (foreign) .NET
315 -- type T is actually implemented (in ILX) as a thunk<T>
316 -- They have PtrRep
317 mkForeignTyCon name ext_name kind arity arg_vrcs
318   = PrimTyCon {
319         tyConName    = name,
320         tyConUnique  = nameUnique name,
321         tyConKind    = kind,
322         tyConArity   = arity,
323         tyConArgVrcs = arg_vrcs,
324         primTyConRep = PtrRep,
325         isUnLifted   = False,
326         tyConExtName = ext_name
327     }
328
329
330 -- most Prim tycons are lifted
331 mkPrimTyCon name kind arity arg_vrcs rep
332   = mkPrimTyCon' name kind arity arg_vrcs rep True  
333
334 -- but RealWorld is lifted
335 mkLiftedPrimTyCon name kind arity arg_vrcs rep
336   = mkPrimTyCon' name kind arity arg_vrcs rep False
337
338 mkPrimTyCon' name kind arity arg_vrcs rep is_unlifted
339   = PrimTyCon {
340         tyConName    = name,
341         tyConUnique  = nameUnique name,
342         tyConKind    = kind,
343         tyConArity   = arity,
344         tyConArgVrcs = arg_vrcs,
345         primTyConRep = rep,
346         isUnLifted   = is_unlifted,
347         tyConExtName = Nothing
348     }
349
350 mkSynTyCon name kind arity tyvars rhs argvrcs
351   = SynTyCon {  
352         tyConName = name,
353         tyConUnique = nameUnique name,
354         tyConKind = kind,
355         tyConArity = arity,
356         tyConTyVars = tyvars,
357         synTyConDefn = rhs,
358         tyConArgVrcs = argvrcs
359     }
360
361 setTyConName tc name = tc {tyConName = name, tyConUnique = nameUnique name}
362
363 \end{code}
364
365 \begin{code}
366 isFunTyCon :: TyCon -> Bool
367 isFunTyCon (FunTyCon {}) = True
368 isFunTyCon _             = False
369
370 isPrimTyCon :: TyCon -> Bool
371 isPrimTyCon (PrimTyCon {}) = True
372 isPrimTyCon _              = False
373
374 isUnLiftedTyCon :: TyCon -> Bool
375 isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
376 isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity})      = not (isBoxed boxity)
377 isUnLiftedTyCon _                                       = False
378
379 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
380 isBoxedTyCon :: TyCon -> Bool
381 isBoxedTyCon (AlgTyCon {}) = True
382 isBoxedTyCon (FunTyCon {}) = True
383 isBoxedTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
384 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
385
386 -- isAlgTyCon returns True for both @data@ and @newtype@
387 isAlgTyCon :: TyCon -> Bool
388 isAlgTyCon (AlgTyCon {})   = True
389 isAlgTyCon (TupleTyCon {}) = True
390 isAlgTyCon other           = False
391
392 isDataTyCon :: TyCon -> Bool
393 -- isDataTyCon returns True for data types that are represented by
394 -- heap-allocated constructors.
395 -- These are srcutinised by Core-level @case@ expressions, and they
396 -- get info tables allocated for them.
397 --      True for all @data@ types
398 --      False for newtypes
399 --                unboxed tuples
400 isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data})  
401   = case new_or_data of
402         NewTyCon _ -> False
403         other      -> True
404
405 isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
406 isDataTyCon other = False
407
408 isNewTyCon :: TyCon -> Bool
409 isNewTyCon (AlgTyCon {algTyConFlavour = NewTyCon _}) = True 
410 isNewTyCon other                                     = False
411
412 isProductTyCon :: TyCon -> Bool
413 -- A "product" tycon
414 --      has *one* constructor, 
415 --      is *not* existential
416 -- but
417 --      may be  DataType or NewType, 
418 --      may be  unboxed or not, 
419 --      may be  recursive or not
420 isProductTyCon (AlgTyCon {dataCons = DataCons [data_con]}) = not (isExistentialDataCon data_con)
421 isProductTyCon (TupleTyCon {})                             = True   
422 isProductTyCon other                                       = False
423
424 isSynTyCon :: TyCon -> Bool
425 isSynTyCon (SynTyCon {}) = True
426 isSynTyCon _             = False
427
428 isEnumerationTyCon :: TyCon -> Bool
429 isEnumerationTyCon (AlgTyCon {algTyConFlavour = EnumTyCon}) = True
430 isEnumerationTyCon other                                    = False
431
432 isTupleTyCon :: TyCon -> Bool
433 -- The unit tycon didn't used to be classed as a tuple tycon
434 -- but I thought that was silly so I've undone it
435 -- If it can't be for some reason, it should be a AlgTyCon
436 isTupleTyCon (TupleTyCon {}) = True
437 isTupleTyCon other           = False
438
439 isUnboxedTupleTyCon :: TyCon -> Bool
440 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
441 isUnboxedTupleTyCon other = False
442
443 isBoxedTupleTyCon :: TyCon -> Bool
444 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
445 isBoxedTupleTyCon other = False
446
447 tupleTyConBoxity tc = tyConBoxed tc
448
449 isRecursiveTyCon :: TyCon -> Bool
450 isRecursiveTyCon (AlgTyCon {algTyConRec = Recursive}) = True
451 isRecursiveTyCon other                                = False
452
453 isForeignTyCon :: TyCon -> Bool
454 -- isForeignTyCon identifies foreign-imported type constructors
455 -- For the moment, they are primitive but lifted, but that may change
456 isForeignTyCon (PrimTyCon {isUnLifted = is_unlifted}) = not is_unlifted
457 isForeignTyCon other                                  = False
458 \end{code}
459
460 \begin{code}
461 tyConDataConDetails :: TyCon -> DataConDetails DataCon
462 tyConDataConDetails (AlgTyCon {dataCons = cons}) = cons
463 tyConDataConDetails (TupleTyCon {dataCon = con}) = DataCons [con]
464 tyConDataConDetails other                        = Unknown
465
466 tyConDataCons :: TyCon -> [DataCon]
467 -- It's convenient for tyConDataCons to return the
468 -- empty list for type synonyms etc
469 tyConDataCons tycon = tyConDataCons_maybe tycon `orElse` []
470
471 tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
472 tyConDataCons_maybe (AlgTyCon {dataCons = DataCons cons}) = Just cons
473 tyConDataCons_maybe (TupleTyCon {dataCon = con})          = Just [con]
474 tyConDataCons_maybe other                                 = Nothing
475
476 tyConFamilySize  :: TyCon -> Int
477 tyConFamilySize (AlgTyCon {dataCons = DataCons cs}) = length cs
478 tyConFamilySize (AlgTyCon {dataCons = HasCons n})   = n
479 tyConFamilySize (TupleTyCon {})                     = 1
480 #ifdef DEBUG
481 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
482 #endif
483
484 tyConSelIds :: TyCon -> [Id]
485 tyConSelIds (AlgTyCon {selIds = sels}) = sels
486 tyConSelIds other_tycon                = []
487 \end{code}
488
489 \begin{code}
490 newTyConRep :: TyCon -> ([TyVar], Type)
491 newTyConRep (AlgTyCon {tyConTyVars = tvs, algTyConFlavour = NewTyCon rep}) = (tvs, rep)
492
493 tyConPrimRep :: TyCon -> PrimRep
494 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
495 tyConPrimRep tc                               = ASSERT( not (isUnboxedTupleTyCon tc) )
496                                                 PtrRep
497         -- We should not be asking what the representation of an
498         -- unboxed tuple is, because it isn't a first class value.
499 \end{code}
500
501 \begin{code}
502 tyConTheta :: TyCon -> [PredType]
503 tyConTheta (AlgTyCon {algTyConTheta = theta}) = theta
504 tyConTheta (TupleTyCon {}) = []
505 -- shouldn't ask about anything else
506 \end{code}
507
508 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
509 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
510 actually computed (in another file).
511
512 \begin{code}
513 tyConArgVrcs_maybe :: TyCon -> Maybe ArgVrcs
514
515 tyConArgVrcs_maybe (FunTyCon   {}                     ) = Just [(False,True),(True,False)]
516 tyConArgVrcs_maybe (AlgTyCon   {tyConArgVrcs = oi})     = Just oi
517 tyConArgVrcs_maybe (PrimTyCon  {tyConArgVrcs = oi})     = Just oi
518 tyConArgVrcs_maybe (TupleTyCon {tyConArity = arity   }) = Just (replicate arity (True,False))
519 tyConArgVrcs_maybe (SynTyCon   {tyConArgVrcs = oi })    = Just oi
520 tyConArgVrcs_maybe _                                    = Nothing
521 \end{code}
522
523 \begin{code}
524 getSynTyConDefn :: TyCon -> ([TyVar], Type)
525 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
526 \end{code}
527
528 \begin{code}
529 maybeTyConSingleCon :: TyCon -> Maybe DataCon
530 maybeTyConSingleCon (AlgTyCon {dataCons = DataCons [c]})  = Just c
531 maybeTyConSingleCon (AlgTyCon {})                         = Nothing
532 maybeTyConSingleCon (TupleTyCon {dataCon = con})          = Just con
533 maybeTyConSingleCon (PrimTyCon {})                        = Nothing
534 maybeTyConSingleCon (FunTyCon {})                         = Nothing  -- case at funty
535 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ppr tc
536 \end{code}
537
538 \begin{code}
539 isClassTyCon :: TyCon -> Bool
540 isClassTyCon (AlgTyCon {algTyConClass = Just _}) = True
541 isClassTyCon other_tycon                         = False
542
543 tyConClass_maybe :: TyCon -> Maybe Class
544 tyConClass_maybe (AlgTyCon {algTyConClass = maybe_clas}) = maybe_clas
545 tyConClass_maybe ther_tycon                              = Nothing
546 \end{code}
547
548
549 %************************************************************************
550 %*                                                                      *
551 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
552 %*                                                                      *
553 %************************************************************************
554
555 @TyCon@s are compared by comparing their @Unique@s.
556
557 The strictness analyser needs @Ord@. It is a lexicographic order with
558 the property @(a<=b) || (b<=a)@.
559
560 \begin{code}
561 instance Eq TyCon where
562     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
563     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
564
565 instance Ord TyCon where
566     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
567     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
568     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
569     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
570     compare a b = getUnique a `compare` getUnique b
571
572 instance Uniquable TyCon where
573     getUnique tc = tyConUnique tc
574
575 instance Outputable TyCon where
576     ppr tc  = ppr (getName tc) 
577
578 instance NamedThing TyCon where
579     getName = tyConName
580 \end{code}
581
582
583 %************************************************************************
584 %*                                                                      *
585 \subsection{Kind constructors}
586 %*                                                                      *
587 %************************************************************************
588
589 @matchesTyCon tc1 tc2@ checks whether an appliation
590 (tc1 t1..tn) matches (tc2 t1..tn).  By "matches" we basically mean "equals",
591 except that at the kind level tc2 might have more boxity info than tc1.
592
593 \begin{code}
594 matchesTyCon :: TyCon   -- Expected (e.g. arg type of function)
595              -> TyCon   -- Inferred (e.g. type of actual arg to function)
596              -> Bool
597
598 matchesTyCon tc1 tc2 =  uniq1 == uniq2 || uniq1 == anyBoxConKey
599                      where
600                         uniq1 = tyConUnique tc1
601                         uniq2 = tyConUnique tc2
602 \end{code}
603
604
605