[project @ 2003-12-30 16:29: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, ArgVrcs, 
9
10         AlgTyConFlavour(..), 
11         DataConDetails(..), visibleDataCons,
12
13         isFunTyCon, isUnLiftedTyCon, isProductTyCon,
14         isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
15         isEnumerationTyCon, 
16         isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity,
17         isRecursiveTyCon, newTyConRep, isHiBootTyCon,
18
19         mkForeignTyCon, isForeignTyCon,
20
21         mkAlgTyCon,
22         mkClassTyCon,
23         mkFunTyCon,
24         mkPrimTyCon,
25         mkLiftedPrimTyCon,
26         mkTupleTyCon,
27         mkSynTyCon,
28
29         tyConName,
30         tyConKind,
31         tyConUnique,
32         tyConTyVars,
33         tyConArgVrcs,
34         tyConDataConDetails, tyConDataCons, tyConDataCons_maybe, tyConFamilySize,
35         tyConSelIds,
36         tyConTheta,
37         tyConPrimRep,
38         tyConArity,
39         isClassTyCon, tyConClass_maybe,
40         getSynTyConDefn,
41         tyConExtName,           -- External name for foreign types
42
43         maybeTyConSingleCon,
44
45         -- Generics
46         tyConHasGenerics
47 ) where
48
49 #include "HsVersions.h"
50
51 import {-# SOURCE #-} TypeRep ( Type, PredType )
52  -- Should just be Type(Type), but this fails due to bug present up to
53  -- and including 4.02 involving slurping of hi-boot files.  Bug is now fixed.
54
55 import {-# SOURCE #-} DataCon ( DataCon, isExistentialDataCon )
56
57
58 import Var              ( TyVar, Id )
59 import Class            ( Class )
60 import Kind             ( Kind )
61 import BasicTypes       ( Arity, RecFlag(..), Boxity(..), isBoxed )
62 import Name             ( Name, nameUnique, NamedThing(getName) )
63 import PrelNames        ( Unique, Uniquable(..) )
64 import PrimRep          ( PrimRep(..) )
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 {          -- Tuples, 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         dataCons :: DataConDetails DataCon,
98
99         selIds :: [Id], -- Its record selectors (if any)
100
101         algTyConFlavour :: AlgTyConFlavour,
102         algTyConRec     :: RecFlag,     -- Tells whether the data type is part of 
103                                         -- a mutually-recursive group or not
104
105         hasGenerics :: Bool,    -- True <=> generic to/from functions are available
106                                         --          (in the exports of the data type's source module)
107
108         algTyConClass :: Maybe Class
109                 -- Just cl if this tycon came from a class declaration
110     }
111
112   | PrimTyCon {                 -- Primitive types; cannot be defined in Haskell
113                                 -- Now includes foreign-imported types
114         tyConUnique  :: Unique,
115         tyConName    :: Name,
116         tyConKind    :: Kind,
117         tyConArity   :: Arity,
118         argVrcs      :: ArgVrcs,
119         primTyConRep :: PrimRep,        -- Many primitive tycons are unboxed, but some are
120                                         -- boxed (represented by pointers). The PrimRep tells.
121
122         isUnLifted   :: Bool,   -- Most primitive tycons are unlifted, 
123                                 -- but foreign-imported ones may not be
124         tyConExtName :: Maybe FastString        -- Just xx for foreign-imported types
125     }
126
127   | TupleTyCon {
128
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 AlgTyConFlavour
156   = DataTyCon Bool      -- Data type; True <=> an enumeration type
157
158   | NewTyCon Type       -- Newtype, with its *ultimate* representation type
159                         -- By 'ultimate' I mean that the rep type is not itself
160                         -- a newtype or type synonym.
161                         -- The rep type isn't entirely simple:
162                         --  for a recursive newtype we pick () as the rep type
163                         --      newtype T = MkT T
164                         --
165                         -- The rep type has free type variables the tyConTyVars
166                         -- Thus:
167                         --      newtype T a = MkT [(a,Int)]
168                         -- The rep type is [(a,Int)]
169         -- NB: the rep type isn't necessarily the original RHS of the
170         --     newtype decl, because the rep type looks through other
171         --     newtypes.  If you want hte original RHS, look at the 
172         --     argument type of the data constructor.
173
174 data DataConDetails datacon
175   = DataCons [datacon]  -- Its data constructors, with fully polymorphic types
176                         -- A type can have zero constructors
177
178   | Unknown             -- Used only when We're importing this data type from an 
179                         -- hi-boot file, so we don't know what its constructors are
180
181 visibleDataCons (DataCons cs) = cs
182 visibleDataCons other         = []
183 \end{code}
184
185
186 %************************************************************************
187 %*                                                                      *
188 \subsection{TyCon Construction}
189 %*                                                                      *
190 %************************************************************************
191
192 Note: the TyCon constructors all take a Kind as one argument, even though
193 they could, in principle, work out their Kind from their other arguments.
194 But to do so they need functions from Types, and that makes a nasty
195 module mutual-recursion.  And they aren't called from many places.
196 So we compromise, and move their Kind calculation to the call site.
197
198 \begin{code}
199 mkFunTyCon :: Name -> Kind -> TyCon
200 mkFunTyCon name kind 
201   = FunTyCon { 
202         tyConUnique = nameUnique name,
203         tyConName   = name,
204         tyConKind   = kind,
205         tyConArity  = 2
206     }
207
208 -- This is the making of a TyCon. Just the same as the old mkAlgTyCon,
209 -- but now you also have to pass in the generic information about the type
210 -- constructor - you can get hold of it easily (see Generics module)
211 mkAlgTyCon name kind tyvars theta argvrcs cons sels flavour is_rec gen_info
212   = AlgTyCon {  
213         tyConName        = name,
214         tyConUnique      = nameUnique name,
215         tyConKind        = kind,
216         tyConArity       = length tyvars,
217         tyConTyVars      = tyvars,
218         argVrcs          = argvrcs,
219         algTyConTheta    = theta,
220         dataCons         = cons, 
221         selIds           = sels,
222         algTyConClass    = Nothing,
223         algTyConFlavour  = flavour,
224         algTyConRec      = is_rec,
225         hasGenerics = gen_info
226     }
227
228 mkClassTyCon name kind tyvars argvrcs con clas flavour is_rec
229   = AlgTyCon {  
230         tyConName        = name,
231         tyConUnique      = nameUnique name,
232         tyConKind        = kind,
233         tyConArity       = length tyvars,
234         tyConTyVars      = tyvars,
235         argVrcs          = argvrcs,
236         algTyConTheta    = [],
237         dataCons         = DataCons [con],
238         selIds           = [],
239         algTyConClass    = Just clas,
240         algTyConFlavour  = flavour,
241         algTyConRec      = is_rec,
242         hasGenerics = False
243     }
244
245
246 mkTupleTyCon name kind arity tyvars con boxed gen_info
247   = TupleTyCon {
248         tyConUnique = nameUnique name,
249         tyConName = name,
250         tyConKind = kind,
251         tyConArity = arity,
252         tyConBoxed = boxed,
253         tyConTyVars = tyvars,
254         dataCon = con,
255         hasGenerics = gen_info
256     }
257
258 -- Foreign-imported (.NET) type constructors are represented
259 -- as primitive, but *lifted*, TyCons for now. They are lifted
260 -- because the Haskell type T representing the (foreign) .NET
261 -- type T is actually implemented (in ILX) as a thunk<T>
262 -- They have PtrRep
263 mkForeignTyCon name ext_name kind arity arg_vrcs
264   = PrimTyCon {
265         tyConName    = name,
266         tyConUnique  = nameUnique name,
267         tyConKind    = kind,
268         tyConArity   = arity,
269         argVrcs      = arg_vrcs,
270         primTyConRep = PtrRep,
271         isUnLifted   = False,
272         tyConExtName = ext_name
273     }
274
275
276 -- most Prim tycons are lifted
277 mkPrimTyCon name kind arity arg_vrcs rep
278   = mkPrimTyCon' name kind arity arg_vrcs rep True  
279
280 -- but RealWorld is lifted
281 mkLiftedPrimTyCon name kind arity arg_vrcs rep
282   = mkPrimTyCon' name kind arity arg_vrcs rep False
283
284 mkPrimTyCon' name kind arity arg_vrcs rep is_unlifted
285   = PrimTyCon {
286         tyConName    = name,
287         tyConUnique  = nameUnique name,
288         tyConKind    = kind,
289         tyConArity   = arity,
290         argVrcs      = arg_vrcs,
291         primTyConRep = rep,
292         isUnLifted   = is_unlifted,
293         tyConExtName = Nothing
294     }
295
296 mkSynTyCon name kind tyvars rhs argvrcs
297   = SynTyCon {  
298         tyConName = name,
299         tyConUnique = nameUnique name,
300         tyConKind = kind,
301         tyConArity = length tyvars,
302         tyConTyVars = tyvars,
303         synTyConDefn = rhs,
304         argVrcs      = argvrcs
305     }
306 \end{code}
307
308 \begin{code}
309 isFunTyCon :: TyCon -> Bool
310 isFunTyCon (FunTyCon {}) = True
311 isFunTyCon _             = False
312
313 isPrimTyCon :: TyCon -> Bool
314 isPrimTyCon (PrimTyCon {}) = True
315 isPrimTyCon _              = False
316
317 isUnLiftedTyCon :: TyCon -> Bool
318 isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
319 isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity})      = not (isBoxed boxity)
320 isUnLiftedTyCon _                                       = False
321
322 #ifdef UNUSED
323 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
324 isBoxedTyCon :: TyCon -> Bool
325 isBoxedTyCon (AlgTyCon {}) = True
326 isBoxedTyCon (FunTyCon {}) = True
327 isBoxedTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
328 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
329 #endif
330
331 -- isAlgTyCon returns True for both @data@ and @newtype@
332 isAlgTyCon :: TyCon -> Bool
333 isAlgTyCon (AlgTyCon {})   = True
334 isAlgTyCon (TupleTyCon {}) = True
335 isAlgTyCon other           = False
336
337 isDataTyCon :: TyCon -> Bool
338 -- isDataTyCon returns True for data types that are represented by
339 -- heap-allocated constructors.
340 -- These are srcutinised by Core-level @case@ expressions, and they
341 -- get info tables allocated for them.
342 --      True for all @data@ types
343 --      False for newtypes
344 --                unboxed tuples
345 isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data})  
346   = case new_or_data of
347         NewTyCon _ -> False
348         other      -> True
349
350 isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
351 isDataTyCon other = False
352
353 isNewTyCon :: TyCon -> Bool
354 isNewTyCon (AlgTyCon {algTyConFlavour = NewTyCon _}) = True 
355 isNewTyCon other                                     = False
356
357 isProductTyCon :: TyCon -> Bool
358 -- A "product" tycon
359 --      has *one* constructor, 
360 --      is *not* existential
361 -- but
362 --      may be  DataType or NewType, 
363 --      may be  unboxed or not, 
364 --      may be  recursive or not
365 isProductTyCon (AlgTyCon {dataCons = DataCons [data_con]}) = not (isExistentialDataCon data_con)
366 isProductTyCon (TupleTyCon {})                             = True   
367 isProductTyCon other                                       = False
368
369 isSynTyCon :: TyCon -> Bool
370 isSynTyCon (SynTyCon {}) = True
371 isSynTyCon _             = False
372
373 isEnumerationTyCon :: TyCon -> Bool
374 isEnumerationTyCon (AlgTyCon {algTyConFlavour = DataTyCon is_enum}) = is_enum
375 isEnumerationTyCon other                                            = False
376
377 isTupleTyCon :: TyCon -> Bool
378 -- The unit tycon didn't used to be classed as a tuple tycon
379 -- but I thought that was silly so I've undone it
380 -- If it can't be for some reason, it should be a AlgTyCon
381 isTupleTyCon (TupleTyCon {}) = True
382 isTupleTyCon other           = False
383
384 isUnboxedTupleTyCon :: TyCon -> Bool
385 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
386 isUnboxedTupleTyCon other = False
387
388 isBoxedTupleTyCon :: TyCon -> Bool
389 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
390 isBoxedTupleTyCon other = False
391
392 tupleTyConBoxity tc = tyConBoxed tc
393
394 isRecursiveTyCon :: TyCon -> Bool
395 isRecursiveTyCon (AlgTyCon {algTyConRec = Recursive}) = True
396 isRecursiveTyCon other                                = False
397
398 isHiBootTyCon :: TyCon -> Bool
399 -- Used for knot-tying in hi-boot files
400 isHiBootTyCon (AlgTyCon {dataCons = Unknown}) = True
401 isHiBootTyCon other                           = False
402
403 isForeignTyCon :: TyCon -> Bool
404 -- isForeignTyCon identifies foreign-imported type constructors
405 -- For the moment, they are primitive but lifted, but that may change
406 isForeignTyCon (PrimTyCon {isUnLifted = is_unlifted}) = not is_unlifted
407 isForeignTyCon other                                  = False
408 \end{code}
409
410 \begin{code}
411 tyConHasGenerics :: TyCon -> Bool
412 tyConHasGenerics (AlgTyCon {hasGenerics = hg})   = hg
413 tyConHasGenerics (TupleTyCon {hasGenerics = hg}) = hg
414 tyConHasGenerics other                           = False        -- Synonyms
415
416 tyConDataConDetails :: TyCon -> DataConDetails DataCon
417 tyConDataConDetails (AlgTyCon {dataCons = cons}) = cons
418 tyConDataConDetails (TupleTyCon {dataCon = con}) = DataCons [con]
419 tyConDataConDetails other                        = pprPanic "tyConDataConDetails" (ppr other)
420
421 tyConDataCons :: TyCon -> [DataCon]
422 -- It's convenient for tyConDataCons to return the
423 -- empty list for type synonyms etc
424 tyConDataCons tycon = tyConDataCons_maybe tycon `orElse` []
425
426 tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
427 tyConDataCons_maybe (AlgTyCon {dataCons = DataCons cons}) = Just cons
428 tyConDataCons_maybe (TupleTyCon {dataCon = con})          = Just [con]
429 tyConDataCons_maybe other                                 = Nothing
430
431 tyConFamilySize  :: TyCon -> Int
432 tyConFamilySize (AlgTyCon {dataCons = DataCons cs}) = length cs
433 tyConFamilySize (TupleTyCon {})                     = 1
434 #ifdef DEBUG
435 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
436 #endif
437
438 tyConSelIds :: TyCon -> [Id]
439 tyConSelIds (AlgTyCon {selIds = sels}) = sels
440 tyConSelIds other_tycon                = []
441 \end{code}
442
443 \begin{code}
444 newTyConRep :: TyCon -> ([TyVar], Type)
445 newTyConRep (AlgTyCon {tyConTyVars = tvs, algTyConFlavour = NewTyCon rep}) = (tvs, rep)
446
447 tyConPrimRep :: TyCon -> PrimRep
448 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
449 tyConPrimRep tc                               = ASSERT( not (isUnboxedTupleTyCon tc) )
450                                                 PtrRep
451         -- We should not be asking what the representation of an
452         -- unboxed tuple is, because it isn't a first class value.
453 \end{code}
454
455 \begin{code}
456 tyConTheta :: TyCon -> [PredType]
457 tyConTheta (AlgTyCon {algTyConTheta = theta}) = theta
458 tyConTheta (TupleTyCon {}) = []
459 -- shouldn't ask about anything else
460 \end{code}
461
462 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
463 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
464 actually computed (in another file).
465
466 \begin{code}
467 tyConArgVrcs :: TyCon -> ArgVrcs
468 tyConArgVrcs (FunTyCon   {})                   = [(False,True),(True,False)]
469 tyConArgVrcs (AlgTyCon   {argVrcs = oi})       = oi
470 tyConArgVrcs (PrimTyCon  {argVrcs = oi})       = oi
471 tyConArgVrcs (TupleTyCon {tyConArity = arity}) = (replicate arity (True,False))
472 tyConArgVrcs (SynTyCon   {argVrcs = oi})       = oi
473 \end{code}
474
475 \begin{code}
476 getSynTyConDefn :: TyCon -> ([TyVar], Type)
477 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
478 \end{code}
479
480 \begin{code}
481 maybeTyConSingleCon :: TyCon -> Maybe DataCon
482 maybeTyConSingleCon (AlgTyCon {dataCons = DataCons [c]})  = Just c
483 maybeTyConSingleCon (AlgTyCon {})                         = Nothing
484 maybeTyConSingleCon (TupleTyCon {dataCon = con})          = Just con
485 maybeTyConSingleCon (PrimTyCon {})                        = Nothing
486 maybeTyConSingleCon (FunTyCon {})                         = Nothing  -- case at funty
487 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ppr tc
488 \end{code}
489
490 \begin{code}
491 isClassTyCon :: TyCon -> Bool
492 isClassTyCon (AlgTyCon {algTyConClass = Just _}) = True
493 isClassTyCon other_tycon                         = False
494
495 tyConClass_maybe :: TyCon -> Maybe Class
496 tyConClass_maybe (AlgTyCon {algTyConClass = maybe_clas}) = maybe_clas
497 tyConClass_maybe ther_tycon                              = Nothing
498 \end{code}
499
500
501 %************************************************************************
502 %*                                                                      *
503 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
504 %*                                                                      *
505 %************************************************************************
506
507 @TyCon@s are compared by comparing their @Unique@s.
508
509 The strictness analyser needs @Ord@. It is a lexicographic order with
510 the property @(a<=b) || (b<=a)@.
511
512 \begin{code}
513 instance Eq TyCon where
514     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
515     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
516
517 instance Ord TyCon where
518     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
519     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
520     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
521     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
522     compare a b = getUnique a `compare` getUnique b
523
524 instance Uniquable TyCon where
525     getUnique tc = tyConUnique tc
526
527 instance Outputable TyCon where
528     ppr tc  = ppr (getName tc) 
529
530 instance NamedThing TyCon where
531     getName = tyConName
532 \end{code}