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