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