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