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