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