[project @ 2004-09-30 10:35:15 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, ArgVrcs, FieldLabel,
9
10         PrimRep(..),
11         tyConPrimRep,
12
13         AlgTyConRhs(..), visibleDataCons,
14
15         isFunTyCon, isUnLiftedTyCon, isProductTyCon, isAbstractTyCon,
16         isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
17         isEnumerationTyCon, 
18         isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity,
19         isRecursiveTyCon, newTyConRep, newTyConRhs, isHiBootTyCon,
20
21         mkForeignTyCon, isForeignTyCon,
22
23         mkAlgTyCon,
24         mkClassTyCon,
25         mkFunTyCon,
26         mkPrimTyCon,
27         mkLiftedPrimTyCon,
28         mkTupleTyCon,
29         mkSynTyCon,
30
31         tyConName,
32         tyConKind,
33         tyConUnique,
34         tyConTyVars,
35         tyConArgVrcs,
36         algTcRhs, tyConDataCons, tyConDataCons_maybe, tyConFamilySize,
37         tyConFields, tyConSelIds,
38         tyConStupidTheta,
39         tyConArity,
40         isClassTyCon, tyConClass_maybe,
41         getSynTyConDefn,
42         tyConExtName,           -- External name for foreign types
43
44         maybeTyConSingleCon,
45
46         -- Generics
47         tyConHasGenerics
48 ) where
49
50 #include "HsVersions.h"
51
52 import {-# SOURCE #-} TypeRep ( Type, PredType )
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, isVanillaDataCon )
57
58
59 import Var              ( TyVar, Id )
60 import Class            ( Class )
61 import Kind             ( Kind )
62 import BasicTypes       ( Arity, RecFlag(..), Boxity(..), isBoxed )
63 import Name             ( Name, nameUnique, NamedThing(getName) )
64 import PrelNames        ( Unique, Uniquable(..) )
65 import Maybes           ( orElse )
66 import Outputable
67 import FastString
68 \end{code}
69
70 %************************************************************************
71 %*                                                                      *
72 \subsection{The data type}
73 %*                                                                      *
74 %************************************************************************
75
76 \begin{code}
77 data TyCon
78   = FunTyCon {
79         tyConUnique :: Unique,
80         tyConName   :: Name,
81         tyConKind   :: Kind,
82         tyConArity  :: Arity
83     }
84
85
86   | AlgTyCon {          -- Data type, and newtype decls.
87                         -- All lifted, all boxed
88         tyConUnique :: Unique,
89         tyConName   :: Name,
90         tyConKind   :: Kind,
91         tyConArity  :: Arity,
92         
93         tyConTyVars :: [TyVar],         -- Scopes over (a) the [PredType] in DataTyCon
94                                         --             (b) the cached types in NewTyCon
95                                         --             (c) the types in algTcFields
96                                         -- But not over the data constructors
97         argVrcs     :: ArgVrcs,
98
99         algTcFields :: [(FieldLabel, Type, Id)],  
100                                         -- Its fields (empty if none): 
101                                         -- * field name
102                                         -- * its type (scoped over tby tyConTyVars)
103                                         -- * record selector (name = field name)
104
105         algTcRhs :: AlgTyConRhs,        -- Data constructors in here
106
107         algTcRec :: RecFlag,            -- Tells whether the data type is part of 
108                                         -- a mutually-recursive group or not
109
110         hasGenerics :: Bool,            -- True <=> generic to/from functions are available
111                                         --          (in the exports of the data type's source module)
112
113         algTcClass :: Maybe Class
114                 -- Just cl if this tycon came from a class declaration
115     }
116
117   | PrimTyCon {                 -- Primitive types; cannot be defined in Haskell
118                                 -- Now includes foreign-imported types
119         tyConUnique   :: Unique,
120         tyConName     :: Name,
121         tyConKind     :: Kind,
122         tyConArity    :: Arity,
123         argVrcs       :: ArgVrcs,
124
125         primTyConRep  :: PrimRep,
126                         -- Many primitive tycons are unboxed, but some are
127                         -- boxed (represented by pointers). The CgRep tells.
128
129         isUnLifted   :: Bool,           -- Most primitive tycons are unlifted, 
130                                         -- but foreign-imported ones may not be
131         tyConExtName :: Maybe FastString        -- Just xx for foreign-imported types
132     }
133
134   | TupleTyCon {
135         tyConUnique :: Unique,
136         tyConName   :: Name,
137         tyConKind   :: Kind,
138         tyConArity  :: Arity,
139         tyConBoxed  :: Boxity,
140         tyConTyVars :: [TyVar],
141         dataCon     :: DataCon,
142         hasGenerics :: Bool
143     }
144
145   | SynTyCon {
146         tyConUnique :: Unique,
147         tyConName   :: Name,
148         tyConKind   :: Kind,
149         tyConArity  :: Arity,
150
151         tyConTyVars     :: [TyVar],     -- Bound tyvars
152         synTyConDefn    :: Type,        -- Right-hand side, mentioning these type vars.
153                                         -- Acts as a template for the expansion when
154                                         -- the tycon is applied to some types.
155         argVrcs :: ArgVrcs
156     }
157
158 type FieldLabel = Name
159
160 type ArgVrcs = [(Bool,Bool)]  -- Tyvar variance info: [(occPos,occNeg)]
161         -- [] means "no information, assume the worst"
162
163 data AlgTyConRhs
164   = AbstractTyCon       -- We know nothing about this data type, except 
165                         -- that it's represented by a pointer
166                         -- Used when we export a data type abstractly into
167                         -- an hi file
168
169   | DataTyCon 
170         (Maybe [PredType])      -- Just theta => this tycon was declared in H98 syntax
171                                 --               with the specified "stupid theta"
172                                 --      e.g. data Ord a => T a = ...
173                                 -- Nothing => this tycon was declared by giving the
174                                 --            type signatures for each constructor
175                                 --            (new GADT stuff)
176                                 --      e.g. data T a where { ... }
177         [DataCon]       -- The constructors; can be empty if the user declares
178                         --   the type to have no constructors
179         Bool            -- Cached: True <=> an enumeration type
180
181   | NewTyCon            -- Newtypes always have exactly one constructor
182         DataCon         -- The unique constructor; it has no existentials
183         Type            -- Cached: the argument type of the constructor
184                         --  = the representation type of the tycon
185
186         Type            -- Cached: the *ultimate* representation type
187                         -- By 'ultimate' I mean that the rep type is not itself
188                         -- a newtype or type synonym.
189                         -- The rep type isn't entirely simple:
190                         --  for a recursive newtype we pick () as the rep type
191                         --      newtype T = MkT T
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         -- NB: the rep type isn't necessarily the original RHS of the
198         --     newtype decl, because the rep type looks through other
199         --     newtypes.
200
201 visibleDataCons :: AlgTyConRhs -> [DataCon]
202 visibleDataCons AbstractTyCon      = []
203 visibleDataCons (DataTyCon _ cs _) = cs
204 visibleDataCons (NewTyCon c _ _)   = [c]
205 \end{code}
206
207 %************************************************************************
208 %*                                                                      *
209 \subsection{PrimRep}
210 %*                                                                      *
211 %************************************************************************
212
213 A PrimRep is an abstraction of a type.  It contains information that
214 the code generator needs in order to pass arguments, return results,
215 and store values of this type.
216
217 A PrimRep is somewhat similar to a CgRep (see codeGen/SMRep) and a
218 MachRep (see cmm/MachOp), although each of these types has a distinct
219 and clearly defined purpose:
220
221   - A PrimRep is a CgRep + information about signedness + information
222     about primitive pointers (AddrRep).  Signedness and primitive
223     pointers are required when passing a primitive type to a foreign
224     function, but aren't needed for call/return conventions of Haskell
225     functions.
226
227   - A MachRep is a basic machine type (non-void, doesn't contain
228     information on pointerhood or signedness, but contains some
229     reps that don't have corresponding Haskell types).
230
231 \begin{code}
232 data PrimRep
233   = VoidRep
234   | PtrRep
235   | IntRep              -- signed, word-sized
236   | WordRep             -- unsinged, word-sized
237   | Int64Rep            -- signed, 64 bit (32-bit words only)
238   | Word64Rep           -- unsigned, 64 bit (32-bit words only)
239   | AddrRep             -- a pointer, but not to a Haskell value
240   | FloatRep
241   | DoubleRep
242 \end{code}
243
244 %************************************************************************
245 %*                                                                      *
246 \subsection{TyCon Construction}
247 %*                                                                      *
248 %************************************************************************
249
250 Note: the TyCon constructors all take a Kind as one argument, even though
251 they could, in principle, work out their Kind from their other arguments.
252 But to do so they need functions from Types, and that makes a nasty
253 module mutual-recursion.  And they aren't called from many places.
254 So we compromise, and move their Kind calculation to the call site.
255
256 \begin{code}
257 mkFunTyCon :: Name -> Kind -> TyCon
258 mkFunTyCon name kind 
259   = FunTyCon { 
260         tyConUnique = nameUnique name,
261         tyConName   = name,
262         tyConKind   = kind,
263         tyConArity  = 2
264     }
265
266 -- This is the making of a TyCon. Just the same as the old mkAlgTyCon,
267 -- but now you also have to pass in the generic information about the type
268 -- constructor - you can get hold of it easily (see Generics module)
269 mkAlgTyCon name kind tyvars argvrcs rhs flds is_rec gen_info
270   = AlgTyCon {  
271         tyConName        = name,
272         tyConUnique      = nameUnique name,
273         tyConKind        = kind,
274         tyConArity       = length tyvars,
275         tyConTyVars      = tyvars,
276         argVrcs          = argvrcs,
277         algTcRhs         = rhs,
278         algTcFields      = flds,
279         algTcClass       = Nothing,
280         algTcRec         = is_rec,
281         hasGenerics = gen_info
282     }
283
284 mkClassTyCon name kind tyvars argvrcs rhs clas is_rec
285   = AlgTyCon {  
286         tyConName        = name,
287         tyConUnique      = nameUnique name,
288         tyConKind        = kind,
289         tyConArity       = length tyvars,
290         tyConTyVars      = tyvars,
291         argVrcs          = argvrcs,
292         algTcRhs         = rhs,
293         algTcFields      = [],
294         algTcClass       = Just clas,
295         algTcRec         = is_rec,
296         hasGenerics = False
297     }
298
299
300 mkTupleTyCon name kind arity tyvars con boxed gen_info
301   = TupleTyCon {
302         tyConUnique = nameUnique name,
303         tyConName = name,
304         tyConKind = kind,
305         tyConArity = arity,
306         tyConBoxed = boxed,
307         tyConTyVars = tyvars,
308         dataCon = con,
309         hasGenerics = gen_info
310     }
311
312 -- Foreign-imported (.NET) type constructors are represented
313 -- as primitive, but *lifted*, TyCons for now. They are lifted
314 -- because the Haskell type T representing the (foreign) .NET
315 -- type T is actually implemented (in ILX) as a thunk<T>
316 mkForeignTyCon name ext_name kind arity arg_vrcs
317   = PrimTyCon {
318         tyConName    = name,
319         tyConUnique  = nameUnique name,
320         tyConKind    = kind,
321         tyConArity   = arity,
322         argVrcs      = arg_vrcs,
323         primTyConRep = PtrRep, -- they all do
324         isUnLifted   = False,
325         tyConExtName = ext_name
326     }
327
328
329 -- most Prim tycons are lifted
330 mkPrimTyCon name kind arity arg_vrcs rep
331   = mkPrimTyCon' name kind arity arg_vrcs rep True  
332
333 -- but RealWorld is lifted
334 mkLiftedPrimTyCon name kind arity arg_vrcs rep
335   = mkPrimTyCon' name kind arity arg_vrcs rep False
336
337 mkPrimTyCon' name kind arity arg_vrcs rep is_unlifted
338   = PrimTyCon {
339         tyConName    = name,
340         tyConUnique  = nameUnique name,
341         tyConKind    = kind,
342         tyConArity   = arity,
343         argVrcs      = arg_vrcs,
344         primTyConRep = rep,
345         isUnLifted   = is_unlifted,
346         tyConExtName = Nothing
347     }
348
349 mkSynTyCon name kind tyvars rhs argvrcs
350   = SynTyCon {  
351         tyConName = name,
352         tyConUnique = nameUnique name,
353         tyConKind = kind,
354         tyConArity = length tyvars,
355         tyConTyVars = tyvars,
356         synTyConDefn = rhs,
357         argVrcs      = argvrcs
358     }
359 \end{code}
360
361 \begin{code}
362 isFunTyCon :: TyCon -> Bool
363 isFunTyCon (FunTyCon {}) = True
364 isFunTyCon _             = False
365
366 isAbstractTyCon :: TyCon -> Bool
367 isAbstractTyCon (AlgTyCon { algTcRhs = AbstractTyCon }) = True
368 isAbstractTyCon _ = False
369
370 isPrimTyCon :: TyCon -> Bool
371 isPrimTyCon (PrimTyCon {}) = True
372 isPrimTyCon _              = False
373
374 isUnLiftedTyCon :: TyCon -> Bool
375 isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
376 isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity})      = not (isBoxed boxity)
377 isUnLiftedTyCon _                                       = False
378
379 -- isAlgTyCon returns True for both @data@ and @newtype@
380 isAlgTyCon :: TyCon -> Bool
381 isAlgTyCon (AlgTyCon {})   = True
382 isAlgTyCon (TupleTyCon {}) = True
383 isAlgTyCon other           = False
384
385 isDataTyCon :: TyCon -> Bool
386 -- isDataTyCon returns True for data types that are represented by
387 -- heap-allocated constructors.
388 -- These are srcutinised by Core-level @case@ expressions, and they
389 -- get info tables allocated for them.
390 --      True for all @data@ types
391 --      False for newtypes
392 --                unboxed tuples
393 isDataTyCon (AlgTyCon {algTcRhs = rhs})  
394   = case rhs of
395         DataTyCon _ _ _  -> True
396         NewTyCon _ _ _   -> False
397         AbstractTyCon    -> panic "isDataTyCon"
398
399 isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
400 isDataTyCon other = False
401
402 isNewTyCon :: TyCon -> Bool
403 isNewTyCon (AlgTyCon {algTcRhs = NewTyCon _ _ _}) = True 
404 isNewTyCon other                                  = False
405
406 isProductTyCon :: TyCon -> Bool
407 -- A "product" tycon
408 --      has *one* constructor, 
409 --      is *not* existential
410 -- but
411 --      may be  DataType or NewType, 
412 --      may be  unboxed or not, 
413 --      may be  recursive or not
414 isProductTyCon tc@(AlgTyCon {}) = case algTcRhs tc of
415                                     DataTyCon _ [data_con] _ -> isVanillaDataCon data_con
416                                     NewTyCon _ _ _           -> True
417                                     other                    -> False
418 isProductTyCon (TupleTyCon {})  = True   
419 isProductTyCon other            = False
420
421 isSynTyCon :: TyCon -> Bool
422 isSynTyCon (SynTyCon {}) = True
423 isSynTyCon _             = False
424
425 isEnumerationTyCon :: TyCon -> Bool
426 isEnumerationTyCon (AlgTyCon {algTcRhs = DataTyCon _ _ is_enum}) = is_enum
427 isEnumerationTyCon other                                         = False
428
429 isTupleTyCon :: TyCon -> Bool
430 -- The unit tycon didn't used to be classed as a tuple tycon
431 -- but I thought that was silly so I've undone it
432 -- If it can't be for some reason, it should be a AlgTyCon
433 isTupleTyCon (TupleTyCon {}) = True
434 isTupleTyCon other           = False
435
436 isUnboxedTupleTyCon :: TyCon -> Bool
437 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
438 isUnboxedTupleTyCon other = False
439
440 isBoxedTupleTyCon :: TyCon -> Bool
441 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
442 isBoxedTupleTyCon other = False
443
444 tupleTyConBoxity tc = tyConBoxed tc
445
446 isRecursiveTyCon :: TyCon -> Bool
447 isRecursiveTyCon (AlgTyCon {algTcRec = Recursive}) = True
448 isRecursiveTyCon other                                = False
449
450 isHiBootTyCon :: TyCon -> Bool
451 -- Used for knot-tying in hi-boot files
452 isHiBootTyCon (AlgTyCon {algTcRhs = AbstractTyCon}) = True
453 isHiBootTyCon other                                 = False
454
455 isForeignTyCon :: TyCon -> Bool
456 -- isForeignTyCon identifies foreign-imported type constructors
457 isForeignTyCon (PrimTyCon {tyConExtName = Just _}) = True
458 isForeignTyCon other                               = False
459 \end{code}
460
461 \begin{code}
462 tyConHasGenerics :: TyCon -> Bool
463 tyConHasGenerics (AlgTyCon {hasGenerics = hg})   = hg
464 tyConHasGenerics (TupleTyCon {hasGenerics = hg}) = hg
465 tyConHasGenerics other                           = False        -- Synonyms
466
467 tyConDataCons :: TyCon -> [DataCon]
468 -- It's convenient for tyConDataCons to return the
469 -- empty list for type synonyms etc
470 tyConDataCons tycon = tyConDataCons_maybe tycon `orElse` []
471
472 tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
473 tyConDataCons_maybe (AlgTyCon {algTcRhs = DataTyCon _ cons _}) = Just cons
474 tyConDataCons_maybe (AlgTyCon {algTcRhs = NewTyCon con _ _})   = Just [con]
475 tyConDataCons_maybe (TupleTyCon {dataCon = con})               = Just [con]
476 tyConDataCons_maybe other                                      = Nothing
477
478 tyConFamilySize  :: TyCon -> Int
479 tyConFamilySize (AlgTyCon {algTcRhs = DataTyCon _ cons _}) = length cons
480 tyConFamilySize (AlgTyCon {algTcRhs = NewTyCon _ _ _})     = 1
481 tyConFamilySize (TupleTyCon {})                            = 1
482 #ifdef DEBUG
483 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
484 #endif
485
486 tyConFields :: TyCon -> [(FieldLabel,Type,Id)]
487 tyConFields (AlgTyCon {algTcFields = fs}) = fs
488 tyConFields other_tycon                   = []
489
490 tyConSelIds :: TyCon -> [Id]
491 tyConSelIds tc = [id | (_,_,id) <- tyConFields tc]
492 \end{code}
493
494 \begin{code}
495 newTyConRep :: TyCon -> ([TyVar], Type)
496 newTyConRep (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon _ _ rep}) = (tvs, rep)
497
498 newTyConRhs :: TyCon -> ([TyVar], Type)
499 newTyConRhs (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon _ rhs _}) = (tvs, rhs)
500
501 tyConPrimRep :: TyCon -> PrimRep
502 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
503 tyConPrimRep tc = ASSERT(not (isUnboxedTupleTyCon tc)) PtrRep
504 \end{code}
505
506 \begin{code}
507 tyConStupidTheta :: TyCon -> [PredType]
508 tyConStupidTheta (AlgTyCon {algTcRhs = DataTyCon mb_th _ _}) = mb_th `orElse` []
509 tyConStupidTheta (AlgTyCon {algTcRhs = other})               = []
510 tyConStupidTheta (TupleTyCon {})                                = []
511 -- shouldn't ask about anything else
512 \end{code}
513
514 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
515 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
516 actually computed (in another file).
517
518 \begin{code}
519 tyConArgVrcs :: TyCon -> ArgVrcs
520 tyConArgVrcs (FunTyCon   {})                   = [(False,True),(True,False)]
521 tyConArgVrcs (AlgTyCon   {argVrcs = oi})       = oi
522 tyConArgVrcs (PrimTyCon  {argVrcs = oi})       = oi
523 tyConArgVrcs (TupleTyCon {tyConArity = arity}) = (replicate arity (True,False))
524 tyConArgVrcs (SynTyCon   {argVrcs = oi})       = oi
525 \end{code}
526
527 \begin{code}
528 getSynTyConDefn :: TyCon -> ([TyVar], Type)
529 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
530 \end{code}
531
532 \begin{code}
533 maybeTyConSingleCon :: TyCon -> Maybe DataCon
534 maybeTyConSingleCon (AlgTyCon {algTcRhs = DataTyCon _ [c] _}) = Just c
535 maybeTyConSingleCon (AlgTyCon {algTcRhs = NewTyCon c _ _})    = Just c
536 maybeTyConSingleCon (AlgTyCon {})                             = Nothing
537 maybeTyConSingleCon (TupleTyCon {dataCon = con})              = Just con
538 maybeTyConSingleCon (PrimTyCon {})                            = Nothing
539 maybeTyConSingleCon (FunTyCon {})                             = Nothing  -- case at funty
540 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ppr tc
541 \end{code}
542
543 \begin{code}
544 isClassTyCon :: TyCon -> Bool
545 isClassTyCon (AlgTyCon {algTcClass = Just _}) = True
546 isClassTyCon other_tycon                         = False
547
548 tyConClass_maybe :: TyCon -> Maybe Class
549 tyConClass_maybe (AlgTyCon {algTcClass = maybe_clas}) = maybe_clas
550 tyConClass_maybe ther_tycon                              = Nothing
551 \end{code}
552
553
554 %************************************************************************
555 %*                                                                      *
556 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
557 %*                                                                      *
558 %************************************************************************
559
560 @TyCon@s are compared by comparing their @Unique@s.
561
562 The strictness analyser needs @Ord@. It is a lexicographic order with
563 the property @(a<=b) || (b<=a)@.
564
565 \begin{code}
566 instance Eq TyCon where
567     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
568     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
569
570 instance Ord TyCon where
571     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
572     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
573     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
574     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
575     compare a b = getUnique a `compare` getUnique b
576
577 instance Uniquable TyCon where
578     getUnique tc = tyConUnique tc
579
580 instance Outputable TyCon where
581     ppr tc  = ppr (getName tc) 
582
583 instance NamedThing TyCon where
584     getName = tyConName
585 \end{code}