7d42e1a6e661660bb785d3769495fa45e9317e42
[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 tby 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
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 stupid 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         algTcStupidTheta = stupid,
279         algTcRhs         = rhs,
280         algTcFields      = flds,
281         algTcClass       = Nothing,
282         algTcRec         = is_rec,
283         hasGenerics = gen_info
284     }
285
286 mkClassTyCon name kind tyvars argvrcs rhs clas is_rec
287   = AlgTyCon {  
288         tyConName        = name,
289         tyConUnique      = nameUnique name,
290         tyConKind        = kind,
291         tyConArity       = length tyvars,
292         tyConTyVars      = tyvars,
293         argVrcs          = argvrcs,
294         algTcStupidTheta = [],
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 makeTyConAbstract :: TyCon -> TyCon
374 makeTyConAbstract tc@(AlgTyCon {}) = tc { algTcRhs = AbstractTyCon }
375 makeTyConAbstract tc = pprPanic "makeTyConAbstract" (ppr tc)
376
377 isPrimTyCon :: TyCon -> Bool
378 isPrimTyCon (PrimTyCon {}) = True
379 isPrimTyCon _              = False
380
381 isUnLiftedTyCon :: TyCon -> Bool
382 isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
383 isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity})      = not (isBoxed boxity)
384 isUnLiftedTyCon _                                       = False
385
386 -- isAlgTyCon returns True for both @data@ and @newtype@
387 isAlgTyCon :: TyCon -> Bool
388 isAlgTyCon (AlgTyCon {})   = True
389 isAlgTyCon (TupleTyCon {}) = True
390 isAlgTyCon other           = False
391
392 isDataTyCon :: TyCon -> Bool
393 -- isDataTyCon returns True for data types that are represented by
394 -- heap-allocated constructors.
395 -- These are srcutinised by Core-level @case@ expressions, and they
396 -- get info tables allocated for them.
397 --      True for all @data@ types
398 --      False for newtypes
399 --                unboxed tuples
400 isDataTyCon tc@(AlgTyCon {algTcRhs = rhs})  
401   = case rhs of
402         DataTyCon _ _  -> True
403         NewTyCon _ _ _ -> False
404         AbstractTyCon  -> pprPanic "isDataTyCon" (ppr tc)
405
406 isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
407 isDataTyCon other = False
408
409 isNewTyCon :: TyCon -> Bool
410 isNewTyCon (AlgTyCon {algTcRhs = NewTyCon _ _ _}) = True 
411 isNewTyCon other                                  = False
412
413 isProductTyCon :: TyCon -> Bool
414 -- A "product" tycon
415 --      has *one* constructor, 
416 --      is *not* existential
417 -- but
418 --      may be  DataType or NewType, 
419 --      may be  unboxed or not, 
420 --      may be  recursive or not
421 isProductTyCon tc@(AlgTyCon {}) = case algTcRhs tc of
422                                     DataTyCon [data_con] _ -> isVanillaDataCon data_con
423                                     NewTyCon _ _ _         -> True
424                                     other                  -> False
425 isProductTyCon (TupleTyCon {})  = True   
426 isProductTyCon other            = False
427
428 isSynTyCon :: TyCon -> Bool
429 isSynTyCon (SynTyCon {}) = True
430 isSynTyCon _             = False
431
432 isEnumerationTyCon :: TyCon -> Bool
433 isEnumerationTyCon (AlgTyCon {algTcRhs = DataTyCon _ is_enum}) = is_enum
434 isEnumerationTyCon other                                       = False
435
436 isTupleTyCon :: TyCon -> Bool
437 -- The unit tycon didn't used to be classed as a tuple tycon
438 -- but I thought that was silly so I've undone it
439 -- If it can't be for some reason, it should be a AlgTyCon
440 --
441 -- NB: when compiling Data.Tuple, the tycons won't reply True to
442 -- isTupleTyCon, becuase they are built as AlgTyCons.  However they
443 -- get spat into the interface file as tuple tycons, so I don't think
444 -- it matters.
445 isTupleTyCon (TupleTyCon {}) = True
446 isTupleTyCon other           = False
447
448 isUnboxedTupleTyCon :: TyCon -> Bool
449 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity)
450 isUnboxedTupleTyCon other = False
451
452 isBoxedTupleTyCon :: TyCon -> Bool
453 isBoxedTupleTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity
454 isBoxedTupleTyCon other = False
455
456 tupleTyConBoxity tc = tyConBoxed tc
457
458 isRecursiveTyCon :: TyCon -> Bool
459 isRecursiveTyCon (AlgTyCon {algTcRec = Recursive}) = True
460 isRecursiveTyCon other                                = False
461
462 isHiBootTyCon :: TyCon -> Bool
463 -- Used for knot-tying in hi-boot files
464 isHiBootTyCon (AlgTyCon {algTcRhs = AbstractTyCon}) = True
465 isHiBootTyCon other                                 = False
466
467 isForeignTyCon :: TyCon -> Bool
468 -- isForeignTyCon identifies foreign-imported type constructors
469 isForeignTyCon (PrimTyCon {tyConExtName = Just _}) = True
470 isForeignTyCon other                               = False
471 \end{code}
472
473 \begin{code}
474 tyConHasGenerics :: TyCon -> Bool
475 tyConHasGenerics (AlgTyCon {hasGenerics = hg})   = hg
476 tyConHasGenerics (TupleTyCon {hasGenerics = hg}) = hg
477 tyConHasGenerics other                           = False        -- Synonyms
478
479 tyConDataCons :: TyCon -> [DataCon]
480 -- It's convenient for tyConDataCons to return the
481 -- empty list for type synonyms etc
482 tyConDataCons tycon = tyConDataCons_maybe tycon `orElse` []
483
484 tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
485 tyConDataCons_maybe (AlgTyCon {algTcRhs = DataTyCon cons _}) = Just cons
486 tyConDataCons_maybe (AlgTyCon {algTcRhs = NewTyCon con _ _}) = Just [con]
487 tyConDataCons_maybe (TupleTyCon {dataCon = con})             = Just [con]
488 tyConDataCons_maybe other                                    = Nothing
489
490 tyConFamilySize  :: TyCon -> Int
491 tyConFamilySize (AlgTyCon {algTcRhs = DataTyCon cons _}) = length cons
492 tyConFamilySize (AlgTyCon {algTcRhs = NewTyCon _ _ _})   = 1
493 tyConFamilySize (TupleTyCon {})                          = 1
494 #ifdef DEBUG
495 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
496 #endif
497
498 tyConFields :: TyCon -> [(FieldLabel,Type,Id)]
499 tyConFields (AlgTyCon {algTcFields = fs}) = fs
500 tyConFields other_tycon                   = []
501
502 tyConSelIds :: TyCon -> [Id]
503 tyConSelIds tc = [id | (_,_,id) <- tyConFields tc]
504
505 algTyConRhs :: TyCon -> AlgTyConRhs
506 algTyConRhs (AlgTyCon {algTcRhs = rhs})  = rhs
507 algTyConRhs (TupleTyCon {dataCon = con}) = DataTyCon [con] False
508 algTyConRhs other = pprPanic "algTyConRhs" (ppr other)
509 \end{code}
510
511 \begin{code}
512 newTyConRhs :: TyCon -> ([TyVar], Type)
513 newTyConRhs (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon _ rhs _}) = (tvs, rhs)
514 newTyConRhs tycon = pprPanic "newTyConRhs" (ppr tycon)
515
516 newTyConRhs_maybe :: TyCon 
517                   -> [Type]                     -- Args to tycon
518                   -> Maybe ([(TyVar,Type)],     -- Substitution
519                             Type)               -- Body type (not yet substituted)
520 -- Non-recursive newtypes are transparent to Core; 
521 -- Given an application to some types, return Just (tenv, ty)
522 -- if it's a saturated, non-recursive newtype.
523 newTyConRhs_maybe (AlgTyCon {tyConTyVars = tvs, 
524                              algTcRec = NonRecursive,   -- Not recursive
525                              algTcRhs = NewTyCon _ rhs _}) tys
526    | tvs `equalLength` tys      -- Saturated
527    = Just (tvs `zip` tys, rhs)
528         
529 newTyConRhs_maybe other_tycon tys = Nothing
530
531
532 newTyConRep :: TyCon -> ([TyVar], Type)
533 newTyConRep (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon _ _ rep}) = (tvs, rep)
534 newTyConRep tycon = pprPanic "newTyConRep" (ppr tycon)
535
536 tyConPrimRep :: TyCon -> PrimRep
537 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
538 tyConPrimRep tc = ASSERT(not (isUnboxedTupleTyCon tc)) PtrRep
539 \end{code}
540
541 \begin{code}
542 tyConStupidTheta :: TyCon -> [PredType]
543 tyConStupidTheta (AlgTyCon {algTcStupidTheta = stupid}) = stupid
544 tyConStupidTheta (TupleTyCon {})                        = []
545 tyConStupidTheta tycon = pprPanic "tyConStupidTheta" (ppr tycon)
546 \end{code}
547
548 @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for
549 each tyvar, if available.  See @calcAlgTyConArgVrcs@ for how this is
550 actually computed (in another file).
551
552 \begin{code}
553 tyConArgVrcs :: TyCon -> ArgVrcs
554 tyConArgVrcs (FunTyCon   {})                   = [(False,True),(True,False)]
555 tyConArgVrcs (AlgTyCon   {argVrcs = oi})       = oi
556 tyConArgVrcs (PrimTyCon  {argVrcs = oi})       = oi
557 tyConArgVrcs (TupleTyCon {tyConArity = arity}) = (replicate arity (True,False))
558 tyConArgVrcs (SynTyCon   {argVrcs = oi})       = oi
559 \end{code}
560
561 \begin{code}
562 getSynTyConDefn :: TyCon -> ([TyVar], Type)
563 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
564 getSynTyConDefn tycon = pprPanic "getSynTyConDefn" (ppr tycon)
565 \end{code}
566
567 \begin{code}
568 maybeTyConSingleCon :: TyCon -> Maybe DataCon
569 maybeTyConSingleCon (AlgTyCon {algTcRhs = DataTyCon [c] _}) = Just c
570 maybeTyConSingleCon (AlgTyCon {algTcRhs = NewTyCon c _ _})  = Just c
571 maybeTyConSingleCon (AlgTyCon {})                           = Nothing
572 maybeTyConSingleCon (TupleTyCon {dataCon = con})            = Just con
573 maybeTyConSingleCon (PrimTyCon {})                          = Nothing
574 maybeTyConSingleCon (FunTyCon {})                           = Nothing  -- case at funty
575 maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ppr tc
576 \end{code}
577
578 \begin{code}
579 isClassTyCon :: TyCon -> Bool
580 isClassTyCon (AlgTyCon {algTcClass = Just _}) = True
581 isClassTyCon other_tycon                         = False
582
583 tyConClass_maybe :: TyCon -> Maybe Class
584 tyConClass_maybe (AlgTyCon {algTcClass = maybe_clas}) = maybe_clas
585 tyConClass_maybe ther_tycon                              = Nothing
586 \end{code}
587
588
589 %************************************************************************
590 %*                                                                      *
591 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
592 %*                                                                      *
593 %************************************************************************
594
595 @TyCon@s are compared by comparing their @Unique@s.
596
597 The strictness analyser needs @Ord@. It is a lexicographic order with
598 the property @(a<=b) || (b<=a)@.
599
600 \begin{code}
601 instance Eq TyCon where
602     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
603     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
604
605 instance Ord TyCon where
606     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
607     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
608     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
609     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
610     compare a b = getUnique a `compare` getUnique b
611
612 instance Uniquable TyCon where
613     getUnique tc = tyConUnique tc
614
615 instance Outputable TyCon where
616     ppr tc  = ppr (getName tc) 
617
618 instance NamedThing TyCon where
619     getName = tyConName
620 \end{code}