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