[project @ 2000-11-06 08:15:20 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         mkAlgTyConRep, --mkAlgTyCon, 
17         mkClassTyCon,
18         mkFunTyCon,
19         mkPrimTyCon,
20         mkTupleTyCon,
21         mkSynTyCon,
22         mkKindCon,
23         mkSuperKindCon,
24
25         setTyConName,
26
27         tyConName,
28         tyConKind,
29         tyConUnique,
30         tyConTyVars,
31         tyConArgVrcs_maybe,
32         tyConDataCons, tyConDataConsIfAvailable,
33         tyConFamilySize,
34         tyConTheta,
35         tyConPrimRep,
36         tyConArity,
37         isClassTyCon,
38         getSynTyConDefn,
39
40         maybeTyConSingleCon,
41
42         matchesTyCon,
43
44         -- Generics
45         tyConGenIds, tyConGenInfo
46 ) where
47
48 #include "HsVersions.h"
49
50 import {-# SOURCE #-} TypeRep ( Type, Kind, SuperKind )
51  -- Should just be Type(Type), but this fails due to bug present up to
52  -- and including 4.02 involving slurping of hi-boot files.  Bug is now fixed.
53
54 import {-# SOURCE #-} DataCon ( DataCon, isExistentialDataCon )
55
56
57 import Class            ( ClassContext )
58 import Var              ( TyVar, Id )
59 import BasicTypes       ( Arity, RecFlag(..), Boxity(..), 
60                           isBoxed, EP(..) )
61 import Name             ( Name, nameUnique, NamedThing(getName) )
62 import PrelNames        ( Unique, Uniquable(..), anyBoxConKey )
63 import PrimRep          ( PrimRep(..), isFollowableRep )
64 import Outputable
65 \end{code}
66
67 %************************************************************************
68 %*                                                                      *
69 \subsection{The data type}
70 %*                                                                      *
71 %************************************************************************
72
73 \begin{code}
74 type KindCon      = TyCon
75 type SuperKindCon = TyCon
76
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         tyConArgVrcs  :: ArgVrcs,
95         algTyConTheta :: ClassContext,
96
97         dataCons :: [DataCon],
98                 -- Its data constructors, with fully polymorphic types
99                 --      This list can be empty, when we import a data type abstractly,
100                 --      either (a) the interface is hand-written and doesn't give
101                 --                 the constructors, or
102                 --             (b) in a quest for fast compilation we don't import 
103                 --                 the constructors
104
105         noOfDataCons :: Int,    -- Number of data constructors
106                                 -- Usually this is the same as the length of the
107                                 -- dataCons field, but the latter may be empty if
108                                 -- we imported the type abstractly.  But even if we import
109                                 -- abstractly we still need to know the number of constructors
110                                 -- so we can get the return convention right.  Tiresome!
111                                 
112         algTyConFlavour :: AlgTyConFlavour,
113         algTyConRec     :: RecFlag,             -- Tells whether the data type is part of 
114                                                 -- a mutually-recursive group or not
115
116         genInfo :: Maybe (EP Id),       -- Convert T <-> Tring
117                                         -- Some TyCons don't have it; 
118                                         -- e.g. the TyCon for a Class dictionary,
119                                         -- and TyCons with unboxed arguments
120
121         algTyConClass :: Bool           -- True if this tycon comes from a class declaration
122     }
123
124   | PrimTyCon {         -- Primitive types; cannot be defined in Haskell
125                         -- NB: All of these guys are *unlifted*, but not all are *unboxed*
126         tyConUnique  :: Unique,
127         tyConName    :: Name,
128         tyConKind    :: Kind,
129         tyConArity   :: Arity,
130         tyConArgVrcs :: ArgVrcs,
131         primTyConRep :: PrimRep
132     }
133
134   | TupleTyCon {
135
136         tyConUnique :: Unique,
137         tyConName   :: Name,
138         tyConKind   :: Kind,
139         tyConArity  :: Arity,
140         tyConBoxed  :: Boxity,
141         tyConTyVars :: [TyVar],
142         dataCon     :: DataCon,
143         genInfo     :: Maybe (EP Id)            -- Generic type and conv funs 
144     }
145
146   | SynTyCon {
147         tyConUnique :: Unique,
148         tyConName   :: Name,
149         tyConKind   :: Kind,
150         tyConArity  :: Arity,
151
152         tyConTyVars     :: [TyVar],     -- Bound tyvars
153         synTyConDefn    :: Type,        -- Right-hand side, mentioning these type vars.
154                                         -- Acts as a template for the expansion when
155                                         -- the tycon is applied to some types.
156         tyConArgVrcs :: ArgVrcs
157     }
158
159   | KindCon {           -- Type constructor at the kind level
160         tyConUnique :: Unique,
161         tyConName   :: Name,
162         tyConKind   :: SuperKind,
163         tyConArity  :: Arity
164     }
165
166   | SuperKindCon        {               -- The type of kind variables or boxity variables,
167         tyConUnique :: Unique,
168         tyConName   :: Name
169     }
170
171 type ArgVrcs = [(Bool,Bool)]  -- Tyvar variance info: [(occPos,occNeg)]
172                               -- *NB*: this is tyvar variance info, *not*
173                               --       termvar usage info.
174
175 data AlgTyConFlavour
176   = DataTyCon           -- Data type
177   | EnumTyCon           -- Special sort of enumeration type
178   | NewTyCon Type       -- Newtype, with its *ultimate* representation type
179                         -- By 'ultimate' I mean that the rep type is not itself
180                         -- a newtype or type synonym.
181
182                         -- The rep type has explicit for-alls for the tyvars of
183                         -- the TyCon.  Thus:
184                         --      newtype T a = MkT [(a,Int)]
185                         -- The rep type is forall a. [(a,Int)]
186                         --
187                         -- The rep type isn't entirely simple:
188                         --  for a recursive newtype we pick () as the rep type
189                         --      newtype T = MkT T
190 \end{code}
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection{TyCon Construction}
195 %*                                                                      *
196 %************************************************************************
197
198 Note: the TyCon constructors all take a Kind as one argument, even though
199 they could, in principle, work out their Kind from their other arguments.
200 But to do so they need functions from Types, and that makes a nasty
201 module mutual-recursion.  And they aren't called from many places.
202 So we compromise, and move their Kind calculation to the call site.
203
204 \begin{code}
205 mkSuperKindCon :: Name -> SuperKindCon
206 mkSuperKindCon name = SuperKindCon {
207                         tyConUnique = nameUnique name,
208                         tyConName = name
209                       }
210
211 mkKindCon :: Name -> SuperKind -> KindCon
212 mkKindCon name kind
213   = KindCon { 
214         tyConUnique = nameUnique name,
215         tyConName = name,
216         tyConArity = 0,
217         tyConKind = kind
218      }
219
220 mkFunTyCon :: Name -> Kind -> TyCon
221 mkFunTyCon name kind 
222   = FunTyCon { 
223         tyConUnique = nameUnique name,
224         tyConName   = name,
225         tyConKind   = kind,
226         tyConArity  = 2
227     }
228
229 tyConGenInfo :: TyCon -> Maybe (EP Id)
230 tyConGenInfo (AlgTyCon   { genInfo = info }) = info
231 tyConGenInfo (TupleTyCon { genInfo = info }) = info
232 tyConGenInfo other                           = Nothing
233
234 tyConGenIds :: TyCon -> [Id]
235 -- Returns the generic-programming Ids; these Ids need bindings
236 tyConGenIds tycon = case tyConGenInfo tycon of
237                         Nothing           -> []
238                         Just (EP from to) -> [from,to]
239
240 -- This is the making of a TyCon. Just the same as the old mkAlgTyCon,
241 -- but now you also have to pass in the generic information about the type
242 -- constructor - you can get hold of it easily (see Generics module)
243 mkAlgTyConRep name kind tyvars theta argvrcs cons ncons flavour rec 
244               gen_info
245   = AlgTyCon {  
246         tyConName               = name,
247         tyConUnique             = nameUnique name,
248         tyConKind               = kind,
249         tyConArity              = length tyvars,
250         tyConTyVars             = tyvars,
251         tyConArgVrcs            = argvrcs,
252         algTyConTheta           = theta,
253         dataCons                = cons, 
254         noOfDataCons            = ncons,
255         algTyConClass           = False,
256         algTyConFlavour         = flavour,
257         algTyConRec             = rec,
258         genInfo                 = gen_info
259     }
260
261 mkClassTyCon name kind tyvars argvrcs con clas flavour
262   = AlgTyCon {  
263         tyConName               = name,
264         tyConUnique             = nameUnique name,
265         tyConKind               = kind,
266         tyConArity              = length tyvars,
267         tyConTyVars             = tyvars,
268         tyConArgVrcs            = argvrcs,
269         algTyConTheta           = [],
270         dataCons                = [con],
271         noOfDataCons            = 1,
272         algTyConClass           = True,
273         algTyConFlavour         = flavour,
274         algTyConRec             = NonRecursive,
275         genInfo                 = Nothing
276     }
277
278
279 mkTupleTyCon name kind arity tyvars con boxed gen_info
280   = TupleTyCon {
281         tyConUnique = nameUnique name,
282         tyConName = name,
283         tyConKind = kind,
284         tyConArity = arity,
285         tyConBoxed = boxed,
286         tyConTyVars = tyvars,
287         dataCon = con,
288         genInfo = gen_info
289     }
290
291 mkPrimTyCon name kind arity arg_vrcs rep 
292   = PrimTyCon {
293         tyConName = name,
294         tyConUnique = nameUnique name,
295         tyConKind = kind,
296         tyConArity = arity,
297         tyConArgVrcs = arg_vrcs,
298         primTyConRep = rep
299     }
300
301 mkSynTyCon name kind arity tyvars rhs argvrcs
302   = SynTyCon {  
303         tyConName = name,
304         tyConUnique = nameUnique name,
305         tyConKind = kind,
306         tyConArity = arity,
307         tyConTyVars = tyvars,
308         synTyConDefn = rhs,
309         tyConArgVrcs = argvrcs
310     }
311
312 setTyConName tc name = tc {tyConName = name, tyConUnique = nameUnique name}
313
314 \end{code}
315
316 \begin{code}
317 isFunTyCon (FunTyCon {}) = True
318 isFunTyCon _             = False
319
320 isPrimTyCon (PrimTyCon {}) = True
321 isPrimTyCon _              = False
322
323 isUnLiftedTyCon (PrimTyCon {}) = True
324 isUnLiftedTyCon (TupleTyCon { tyConBoxed = boxity}) = not (isBoxed boxity)
325 isUnLiftedTyCon _              = False
326
327 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
328 isBoxedTyCon (AlgTyCon {}) = True
329 isBoxedTyCon (FunTyCon {}) = True
330 isBoxedTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
331 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
332
333 -- isAlgTyCon returns True for both @data@ and @newtype@
334 isAlgTyCon (AlgTyCon {})   = True
335 isAlgTyCon (TupleTyCon {}) = True
336 isAlgTyCon other           = False
337
338 -- isDataTyCon returns False for @newtype@ and for unboxed tuples
339 isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data})  = case new_or_data of
340                                                                 NewTyCon _ -> False
341                                                                 other   -> True
342 isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
343 isDataTyCon other = False
344
345 isNewTyCon (AlgTyCon {algTyConFlavour = NewTyCon _}) = True 
346 isNewTyCon other                                     = False
347
348 newTyConRep (AlgTyCon {algTyConFlavour = NewTyCon rep}) = Just rep
349 newTyConRep other                                       = Nothing
350
351 -- A "product" tycon
352 --      has *one* constructor, 
353 --      is *not* existential
354 -- but
355 --      may be  DataType or NewType, 
356 --      may be  unboxed or not, 
357 --      may be  recursive or not
358 isProductTyCon (AlgTyCon {dataCons = [data_con]}) = not (isExistentialDataCon data_con)
359 isProductTyCon (TupleTyCon {})                    = True
360 isProductTyCon other                              = False
361
362 isSynTyCon (SynTyCon {}) = True
363 isSynTyCon _             = False
364
365 isEnumerationTyCon (AlgTyCon {algTyConFlavour = EnumTyCon}) = True
366 isEnumerationTyCon other                                    = False
367
368 -- The unit tycon didn't used to be classed as a tuple tycon
369 -- but I thought that was silly so I've undone it
370 -- If it can't be for some reason, it should be a AlgTyCon
371 isTupleTyCon (TupleTyCon {}) = True
372 isTupleTyCon other           = False
373
374 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
375 isUnboxedTupleTyCon other = False
376
377 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
378 isBoxedTupleTyCon other = False
379
380 tupleTyConBoxity tc = tyConBoxed tc
381
382 isRecursiveTyCon (AlgTyCon {algTyConRec = Recursive}) = True
383 isRecursiveTyCon other                                = False
384 \end{code}
385
386 \begin{code}
387 tyConDataCons :: TyCon -> [DataCon]
388 tyConDataCons tycon = ASSERT2( not (null cons), ppr tycon ) cons
389                     where
390                       cons = tyConDataConsIfAvailable tycon
391
392 tyConDataConsIfAvailable (AlgTyCon {dataCons = cons}) = cons    -- Empty for abstract types
393 tyConDataConsIfAvailable (TupleTyCon {dataCon = con}) = [con]
394 tyConDataConsIfAvailable other                        = []
395         -- You may think this last equation should fail,
396         -- but it's quite convenient to return no constructors for
397         -- a synonym; see for example the call in TcTyClsDecls.
398
399 tyConFamilySize  :: TyCon -> Int
400 tyConFamilySize (AlgTyCon {noOfDataCons = n}) = n
401 tyConFamilySize (TupleTyCon {})               = 1
402 #ifdef DEBUG
403 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
404 #endif
405
406 tyConPrimRep :: TyCon -> PrimRep
407 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
408 tyConPrimRep _                                = PtrRep
409 \end{code}
410
411 \begin{code}
412 tyConTheta :: TyCon -> ClassContext
413 tyConTheta (AlgTyCon {algTyConTheta = theta}) = theta
414 -- should ask about anything else
415 \end{code}
416
417 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
418 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
419 actually computed (in another file).
420
421 \begin{code}
422 tyConArgVrcs_maybe :: TyCon -> Maybe ArgVrcs
423
424 tyConArgVrcs_maybe (FunTyCon   {}                     ) = Just [(False,True),(True,False)]
425 tyConArgVrcs_maybe (AlgTyCon   {tyConArgVrcs = oi})     = Just oi
426 tyConArgVrcs_maybe (PrimTyCon  {tyConArgVrcs = oi})     = Just oi
427 tyConArgVrcs_maybe (TupleTyCon {tyConArity = arity   }) = Just (replicate arity (True,False))
428 tyConArgVrcs_maybe (SynTyCon   {tyConArgVrcs = oi })    = Just oi
429 tyConArgVrcs_maybe _                                    = Nothing
430 \end{code}
431
432 \begin{code}
433 getSynTyConDefn :: TyCon -> ([TyVar], Type)
434 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
435 \end{code}
436
437 \begin{code}
438 maybeTyConSingleCon :: TyCon -> Maybe DataCon
439 maybeTyConSingleCon (AlgTyCon {dataCons = [c]})  = Just c
440 maybeTyConSingleCon (AlgTyCon {})                = Nothing
441 maybeTyConSingleCon (TupleTyCon {dataCon = con}) = Just con
442 maybeTyConSingleCon (PrimTyCon {})               = Nothing
443 maybeTyConSingleCon (FunTyCon {})                = Nothing  -- case at funty
444 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $
445                          ppr tc
446 \end{code}
447
448 \begin{code}
449 isClassTyCon :: TyCon -> Bool
450 isClassTyCon (AlgTyCon {algTyConClass = is_class_tycon}) = is_class_tycon
451 isClassTyCon other_tycon                                 = False
452 \end{code}
453
454
455 %************************************************************************
456 %*                                                                      *
457 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
458 %*                                                                      *
459 %************************************************************************
460
461 @TyCon@s are compared by comparing their @Unique@s.
462
463 The strictness analyser needs @Ord@. It is a lexicographic order with
464 the property @(a<=b) || (b<=a)@.
465
466 \begin{code}
467 instance Eq TyCon where
468     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
469     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
470
471 instance Ord TyCon where
472     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
473     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
474     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
475     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
476     compare a b = getUnique a `compare` getUnique b
477
478 instance Uniquable TyCon where
479     getUnique tc = tyConUnique tc
480
481 instance Outputable TyCon where
482     ppr tc  = ppr (getName tc) 
483
484 instance NamedThing TyCon where
485     getName = tyConName
486 \end{code}
487
488
489 %************************************************************************
490 %*                                                                      *
491 \subsection{Kind constructors}
492 %*                                                                      *
493 %************************************************************************
494
495 @matchesTyCon tc1 tc2@ checks whether an appliation
496 (tc1 t1..tn) matches (tc2 t1..tn).  By "matches" we basically mean "equals",
497 except that at the kind level tc2 might have more boxity info than tc1.
498
499 \begin{code}
500 matchesTyCon :: TyCon   -- Expected (e.g. arg type of function)
501              -> TyCon   -- Inferred (e.g. type of actual arg to function)
502              -> Bool
503
504 matchesTyCon tc1 tc2 =  uniq1 == uniq2 || uniq1 == anyBoxConKey
505                      where
506                         uniq1 = tyConUnique tc1
507                         uniq2 = tyConUnique tc2
508 \end{code}
509
510
511