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