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