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