[project @ 2005-10-14 11:22:41 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, 
16         isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
17         isEnumerationTyCon, 
18         isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity,
19         isRecursiveTyCon, newTyConRep, newTyConRhs, newTyConRhs_maybe, isHiBootTyCon,
20
21         makeTyConAbstract, isAbstractTyCon,
22
23         mkForeignTyCon, isForeignTyCon,
24
25         mkAlgTyCon,
26         mkClassTyCon,
27         mkFunTyCon,
28         mkPrimTyCon,
29         mkLiftedPrimTyCon,
30         mkTupleTyCon,
31         mkSynTyCon,
32
33         tyConName,
34         tyConKind,
35         tyConUnique,
36         tyConTyVars,
37         tyConArgVrcs,
38         algTyConRhs, tyConDataCons, tyConDataCons_maybe, tyConFamilySize,
39         tyConSelIds,
40         tyConStupidTheta,
41         tyConArity,
42         isClassTyCon, tyConClass_maybe,
43         getSynTyConDefn,
44         tyConExtName,           -- External name for foreign types
45
46         maybeTyConSingleCon,
47
48         -- Generics
49         tyConHasGenerics
50 ) where
51
52 #include "HsVersions.h"
53
54 import {-# SOURCE #-} TypeRep ( Type, PredType )
55  -- Should just be Type(Type), but this fails due to bug present up to
56  -- and including 4.02 involving slurping of hi-boot files.  Bug is now fixed.
57
58 import {-# SOURCE #-} DataCon ( DataCon, isVanillaDataCon )
59
60
61 import Var              ( TyVar, Id )
62 import Class            ( Class )
63 import Kind             ( Kind )
64 import BasicTypes       ( Arity, RecFlag(..), Boxity(..), isBoxed )
65 import Name             ( Name, nameUnique, NamedThing(getName) )
66 import PrelNames        ( Unique, Uniquable(..) )
67 import Maybes           ( orElse )
68 import Util             ( equalLength )
69 import Outputable
70 import FastString
71 \end{code}
72
73 %************************************************************************
74 %*                                                                      *
75 \subsection{The data type}
76 %*                                                                      *
77 %************************************************************************
78
79 \begin{code}
80 data TyCon
81   = FunTyCon {
82         tyConUnique :: Unique,
83         tyConName   :: Name,
84         tyConKind   :: Kind,
85         tyConArity  :: Arity
86     }
87
88
89   | AlgTyCon {          -- Data type, and newtype decls.
90                         -- All lifted, all boxed
91         tyConUnique :: Unique,
92         tyConName   :: Name,
93         tyConKind   :: Kind,
94         tyConArity  :: Arity,
95         
96         tyConTyVars :: [TyVar],         -- Scopes over (a) the [PredType] in AlgTyConRhs.DataTyCon
97                                         --             (b) the cached types in AlgTyConRhs.NewTyCon
98                                         -- But not over the data constructors
99         argVrcs     :: ArgVrcs,
100
101         algTcSelIds :: [Id],            -- Its record selectors (empty if none): 
102
103         algTcStupidTheta :: [PredType], -- The "stupid theta" for the data type
104                                         -- (always empty for GADTs)
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         [DataCon]       -- The constructors; can be empty if the user declares
172                         --   the type to have no constructors
173                         -- INVARIANT: Kept in order of increasing tag
174                         --            (see the tag assignment in DataCon.mkDataCon)
175         Bool            -- Cached: True <=> an enumeration type
176                         --         Includes data types with no constructors.
177
178   | NewTyCon            -- Newtypes always have exactly one constructor
179         DataCon         -- The unique constructor; it has no existentials
180         Type            -- Cached: the argument type of the constructor
181                         --  = the representation type of the tycon
182
183         Type            -- Cached: the *ultimate* representation type
184                         -- By 'ultimate' I mean that the rep type is not itself
185                         -- a newtype or type synonym.
186                         -- The rep type isn't entirely simple:
187                         --  for a recursive newtype we pick () as the rep type
188                         --      newtype T = MkT T
189                         --
190                         -- The rep type has free type variables the tyConTyVars
191                         -- Thus:
192                         --      newtype T a = MkT [(a,Int)]
193                         -- The rep type is [(a,Int)]
194         -- NB: the rep type isn't necessarily the original RHS of the
195         --     newtype decl, because the rep type looks through other
196         --     newtypes.
197
198 visibleDataCons :: AlgTyConRhs -> [DataCon]
199 visibleDataCons AbstractTyCon    = []
200 visibleDataCons (DataTyCon cs _) = cs
201 visibleDataCons (NewTyCon c _ _) = [c]
202 \end{code}
203
204 %************************************************************************
205 %*                                                                      *
206 \subsection{PrimRep}
207 %*                                                                      *
208 %************************************************************************
209
210 A PrimRep is an abstraction of a type.  It contains information that
211 the code generator needs in order to pass arguments, return results,
212 and store values of this type.
213
214 A PrimRep is somewhat similar to a CgRep (see codeGen/SMRep) and a
215 MachRep (see cmm/MachOp), although each of these types has a distinct
216 and clearly defined purpose:
217
218   - A PrimRep is a CgRep + information about signedness + information
219     about primitive pointers (AddrRep).  Signedness and primitive
220     pointers are required when passing a primitive type to a foreign
221     function, but aren't needed for call/return conventions of Haskell
222     functions.
223
224   - A MachRep is a basic machine type (non-void, doesn't contain
225     information on pointerhood or signedness, but contains some
226     reps that don't have corresponding Haskell types).
227
228 \begin{code}
229 data PrimRep
230   = VoidRep
231   | PtrRep
232   | IntRep              -- signed, word-sized
233   | WordRep             -- unsinged, word-sized
234   | Int64Rep            -- signed, 64 bit (32-bit words only)
235   | Word64Rep           -- unsigned, 64 bit (32-bit words only)
236   | AddrRep             -- a pointer, but not to a Haskell value
237   | FloatRep
238   | DoubleRep
239 \end{code}
240
241 %************************************************************************
242 %*                                                                      *
243 \subsection{TyCon Construction}
244 %*                                                                      *
245 %************************************************************************
246
247 Note: the TyCon constructors all take a Kind as one argument, even though
248 they could, in principle, work out their Kind from their other arguments.
249 But to do so they need functions from Types, and that makes a nasty
250 module mutual-recursion.  And they aren't called from many places.
251 So we compromise, and move their Kind calculation to the call site.
252
253 \begin{code}
254 mkFunTyCon :: Name -> Kind -> TyCon
255 mkFunTyCon name kind 
256   = FunTyCon { 
257         tyConUnique = nameUnique name,
258         tyConName   = name,
259         tyConKind   = kind,
260         tyConArity  = 2
261     }
262
263 -- This is the making of a TyCon. Just the same as the old mkAlgTyCon,
264 -- but now you also have to pass in the generic information about the type
265 -- constructor - you can get hold of it easily (see Generics module)
266 mkAlgTyCon name kind tyvars argvrcs stupid rhs sel_ids is_rec gen_info
267   = AlgTyCon {  
268         tyConName        = name,
269         tyConUnique      = nameUnique name,
270         tyConKind        = kind,
271         tyConArity       = length tyvars,
272         tyConTyVars      = tyvars,
273         argVrcs          = argvrcs,
274         algTcStupidTheta = stupid,
275         algTcRhs         = rhs,
276         algTcSelIds      = sel_ids,
277         algTcClass       = Nothing,
278         algTcRec         = is_rec,
279         hasGenerics = gen_info
280     }
281
282 mkClassTyCon name kind tyvars argvrcs rhs clas is_rec
283   = AlgTyCon {  
284         tyConName        = name,
285         tyConUnique      = nameUnique name,
286         tyConKind        = kind,
287         tyConArity       = length tyvars,
288         tyConTyVars      = tyvars,
289         argVrcs          = argvrcs,
290         algTcStupidTheta = [],
291         algTcRhs         = rhs,
292         algTcSelIds      = [],
293         algTcClass       = Just clas,
294         algTcRec         = is_rec,
295         hasGenerics = False
296     }
297
298
299 mkTupleTyCon name kind arity tyvars con boxed gen_info
300   = TupleTyCon {
301         tyConUnique = nameUnique name,
302         tyConName = name,
303         tyConKind = kind,
304         tyConArity = arity,
305         tyConBoxed = boxed,
306         tyConTyVars = tyvars,
307         dataCon = con,
308         hasGenerics = gen_info
309     }
310
311 -- Foreign-imported (.NET) type constructors are represented
312 -- as primitive, but *lifted*, TyCons for now. They are lifted
313 -- because the Haskell type T representing the (foreign) .NET
314 -- type T is actually implemented (in ILX) as a thunk<T>
315 mkForeignTyCon name ext_name kind arity arg_vrcs
316   = PrimTyCon {
317         tyConName    = name,
318         tyConUnique  = nameUnique name,
319         tyConKind    = kind,
320         tyConArity   = arity,
321         argVrcs      = arg_vrcs,
322         primTyConRep = PtrRep, -- they all do
323         isUnLifted   = False,
324         tyConExtName = ext_name
325     }
326
327
328 -- most Prim tycons are lifted
329 mkPrimTyCon name kind arity arg_vrcs rep
330   = mkPrimTyCon' name kind arity arg_vrcs rep True  
331
332 -- but RealWorld is lifted
333 mkLiftedPrimTyCon name kind arity arg_vrcs rep
334   = mkPrimTyCon' name kind arity arg_vrcs rep False
335
336 mkPrimTyCon' name kind arity arg_vrcs rep is_unlifted
337   = PrimTyCon {
338         tyConName    = name,
339         tyConUnique  = nameUnique name,
340         tyConKind    = kind,
341         tyConArity   = arity,
342         argVrcs      = arg_vrcs,
343         primTyConRep = rep,
344         isUnLifted   = is_unlifted,
345         tyConExtName = Nothing
346     }
347
348 mkSynTyCon name kind tyvars rhs argvrcs
349   = SynTyCon {  
350         tyConName = name,
351         tyConUnique = nameUnique name,
352         tyConKind = kind,
353         tyConArity = length tyvars,
354         tyConTyVars = tyvars,
355         synTyConDefn = rhs,
356         argVrcs      = argvrcs
357     }
358 \end{code}
359
360 \begin{code}
361 isFunTyCon :: TyCon -> Bool
362 isFunTyCon (FunTyCon {}) = True
363 isFunTyCon _             = False
364
365 isAbstractTyCon :: TyCon -> Bool
366 isAbstractTyCon (AlgTyCon { algTcRhs = AbstractTyCon }) = True
367 isAbstractTyCon _ = False
368
369 makeTyConAbstract :: TyCon -> TyCon
370 makeTyConAbstract tc@(AlgTyCon {}) = tc { algTcRhs = AbstractTyCon }
371 makeTyConAbstract tc = pprPanic "makeTyConAbstract" (ppr tc)
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 tc@(AlgTyCon {algTcRhs = rhs})  
397   = case rhs of
398         DataTyCon _ _  -> True
399         NewTyCon _ _ _ -> False
400         AbstractTyCon  -> pprPanic "isDataTyCon" (ppr tc)
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 --
437 -- NB: when compiling Data.Tuple, the tycons won't reply True to
438 -- isTupleTyCon, becuase they are built as AlgTyCons.  However they
439 -- get spat into the interface file as tuple tycons, so I don't think
440 -- it matters.
441 isTupleTyCon (TupleTyCon {}) = True
442 isTupleTyCon other           = False
443
444 isUnboxedTupleTyCon :: TyCon -> Bool
445 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
446 isUnboxedTupleTyCon other = False
447
448 isBoxedTupleTyCon :: TyCon -> Bool
449 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
450 isBoxedTupleTyCon other = False
451
452 tupleTyConBoxity tc = tyConBoxed tc
453
454 isRecursiveTyCon :: TyCon -> Bool
455 isRecursiveTyCon (AlgTyCon {algTcRec = Recursive}) = True
456 isRecursiveTyCon other                                = False
457
458 isHiBootTyCon :: TyCon -> Bool
459 -- Used for knot-tying in hi-boot files
460 isHiBootTyCon (AlgTyCon {algTcRhs = AbstractTyCon}) = True
461 isHiBootTyCon other                                 = False
462
463 isForeignTyCon :: TyCon -> Bool
464 -- isForeignTyCon identifies foreign-imported type constructors
465 isForeignTyCon (PrimTyCon {tyConExtName = Just _}) = True
466 isForeignTyCon other                               = False
467 \end{code}
468
469 \begin{code}
470 tyConHasGenerics :: TyCon -> Bool
471 tyConHasGenerics (AlgTyCon {hasGenerics = hg})   = hg
472 tyConHasGenerics (TupleTyCon {hasGenerics = hg}) = hg
473 tyConHasGenerics other                           = False        -- Synonyms
474
475 tyConDataCons :: TyCon -> [DataCon]
476 -- It's convenient for tyConDataCons to return the
477 -- empty list for type synonyms etc
478 tyConDataCons tycon = tyConDataCons_maybe tycon `orElse` []
479
480 tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
481 tyConDataCons_maybe (AlgTyCon {algTcRhs = DataTyCon cons _}) = Just cons
482 tyConDataCons_maybe (AlgTyCon {algTcRhs = NewTyCon con _ _}) = Just [con]
483 tyConDataCons_maybe (TupleTyCon {dataCon = con})             = Just [con]
484 tyConDataCons_maybe other                                    = Nothing
485
486 tyConFamilySize  :: TyCon -> Int
487 tyConFamilySize (AlgTyCon {algTcRhs = DataTyCon cons _}) = length cons
488 tyConFamilySize (AlgTyCon {algTcRhs = NewTyCon _ _ _})   = 1
489 tyConFamilySize (TupleTyCon {})                          = 1
490 #ifdef DEBUG
491 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
492 #endif
493
494 tyConSelIds :: TyCon -> [Id]
495 tyConSelIds (AlgTyCon {algTcSelIds = fs}) = fs
496 tyConSelIds other_tycon                   = []
497
498 algTyConRhs :: TyCon -> AlgTyConRhs
499 algTyConRhs (AlgTyCon {algTcRhs = rhs})  = rhs
500 algTyConRhs (TupleTyCon {dataCon = con}) = DataTyCon [con] False
501 algTyConRhs other = pprPanic "algTyConRhs" (ppr other)
502 \end{code}
503
504 \begin{code}
505 newTyConRhs :: TyCon -> ([TyVar], Type)
506 newTyConRhs (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon _ rhs _}) = (tvs, rhs)
507 newTyConRhs tycon = pprPanic "newTyConRhs" (ppr tycon)
508
509 newTyConRhs_maybe :: TyCon 
510                   -> [Type]                     -- Args to tycon
511                   -> Maybe ([(TyVar,Type)],     -- Substitution
512                             Type)               -- Body type (not yet substituted)
513 -- Non-recursive newtypes are transparent to Core; 
514 -- Given an application to some types, return Just (tenv, ty)
515 -- if it's a saturated, non-recursive newtype.
516 newTyConRhs_maybe (AlgTyCon {tyConTyVars = tvs, 
517                              algTcRec = NonRecursive,   -- Not recursive
518                              algTcRhs = NewTyCon _ rhs _}) tys
519    | tvs `equalLength` tys      -- Saturated
520    = Just (tvs `zip` tys, rhs)
521         
522 newTyConRhs_maybe other_tycon tys = Nothing
523
524
525 newTyConRep :: TyCon -> ([TyVar], Type)
526 newTyConRep (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon _ _ rep}) = (tvs, rep)
527 newTyConRep tycon = pprPanic "newTyConRep" (ppr tycon)
528
529 tyConPrimRep :: TyCon -> PrimRep
530 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
531 tyConPrimRep tc = ASSERT(not (isUnboxedTupleTyCon tc)) PtrRep
532 \end{code}
533
534 \begin{code}
535 tyConStupidTheta :: TyCon -> [PredType]
536 tyConStupidTheta (AlgTyCon {algTcStupidTheta = stupid}) = stupid
537 tyConStupidTheta (TupleTyCon {})                        = []
538 tyConStupidTheta tycon = pprPanic "tyConStupidTheta" (ppr tycon)
539 \end{code}
540
541 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
542 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
543 actually computed (in another file).
544
545 \begin{code}
546 tyConArgVrcs :: TyCon -> ArgVrcs
547 tyConArgVrcs (FunTyCon   {})                   = [(False,True),(True,False)]
548 tyConArgVrcs (AlgTyCon   {argVrcs = oi})       = oi
549 tyConArgVrcs (PrimTyCon  {argVrcs = oi})       = oi
550 tyConArgVrcs (TupleTyCon {tyConArity = arity}) = (replicate arity (True,False))
551 tyConArgVrcs (SynTyCon   {argVrcs = oi})       = oi
552 \end{code}
553
554 \begin{code}
555 getSynTyConDefn :: TyCon -> ([TyVar], Type)
556 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
557 getSynTyConDefn tycon = pprPanic "getSynTyConDefn" (ppr tycon)
558 \end{code}
559
560 \begin{code}
561 maybeTyConSingleCon :: TyCon -> Maybe DataCon
562 maybeTyConSingleCon (AlgTyCon {algTcRhs = DataTyCon [c] _}) = Just c
563 maybeTyConSingleCon (AlgTyCon {algTcRhs = NewTyCon c _ _})  = Just c
564 maybeTyConSingleCon (AlgTyCon {})                           = Nothing
565 maybeTyConSingleCon (TupleTyCon {dataCon = con})            = Just con
566 maybeTyConSingleCon (PrimTyCon {})                          = Nothing
567 maybeTyConSingleCon (FunTyCon {})                           = Nothing  -- case at funty
568 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ppr tc
569 \end{code}
570
571 \begin{code}
572 isClassTyCon :: TyCon -> Bool
573 isClassTyCon (AlgTyCon {algTcClass = Just _}) = True
574 isClassTyCon other_tycon                         = False
575
576 tyConClass_maybe :: TyCon -> Maybe Class
577 tyConClass_maybe (AlgTyCon {algTcClass = maybe_clas}) = maybe_clas
578 tyConClass_maybe ther_tycon                              = Nothing
579 \end{code}
580
581
582 %************************************************************************
583 %*                                                                      *
584 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
585 %*                                                                      *
586 %************************************************************************
587
588 @TyCon@s are compared by comparing their @Unique@s.
589
590 The strictness analyser needs @Ord@. It is a lexicographic order with
591 the property @(a<=b) || (b<=a)@.
592
593 \begin{code}
594 instance Eq TyCon where
595     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
596     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
597
598 instance Ord TyCon where
599     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
600     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
601     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
602     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
603     compare a b = getUnique a `compare` getUnique b
604
605 instance Uniquable TyCon where
606     getUnique tc = tyConUnique tc
607
608 instance Outputable TyCon where
609     ppr tc  = ppr (getName tc) 
610
611 instance NamedThing TyCon where
612     getName = tyConName
613 \end{code}