[project @ 1999-01-27 14:51:14 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, KindCon, SuperKindCon,
9
10         isFunTyCon, isUnLiftedTyCon, isBoxedTyCon, isProductTyCon,
11         isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon,
12         isEnumerationTyCon, isTupleTyCon, isUnboxedTupleTyCon,
13
14         mkAlgTyCon,
15         mkFunTyCon,
16         mkPrimTyCon,
17         mkTupleTyCon,
18         mkSynTyCon,
19         mkKindCon,
20         mkSuperKindCon,
21
22         setTyConName,
23
24         tyConKind,
25         tyConUnique,
26         tyConTyVars,
27         tyConDataCons,
28         tyConFamilySize,
29         tyConDerivings,
30         tyConTheta,
31         tyConPrimRep,
32         tyConArity,
33         tyConClass_maybe,
34         getSynTyConDefn,
35
36         maybeTyConSingleCon,
37
38         matchesTyCon
39 ) where
40
41 #include "HsVersions.h"
42
43 import {-# SOURCE #-} Type  ( Type, Kind, SuperKind )
44 import {-# SOURCE #-} DataCon ( DataCon )
45
46 import Class            ( Class )
47 import Var              ( TyVar )
48 import BasicTypes       ( Arity, NewOrData(..), RecFlag(..) )
49 import Maybes
50 import Name             ( Name, nameUnique, NamedThing(getName) )
51 import Unique           ( Unique, Uniquable(..), anyBoxConKey )
52 import PrimRep          ( PrimRep(..), isFollowableRep )
53 import Outputable
54 \end{code}
55
56 %************************************************************************
57 %*                                                                      *
58 \subsection{The data type}
59 %*                                                                      *
60 %************************************************************************
61
62 \begin{code}
63 type KindCon      = TyCon
64 type SuperKindCon = TyCon
65
66 data TyCon
67   = FunTyCon {
68         tyConUnique :: Unique,
69         tyConName   :: Name,
70         tyConKind   :: Kind,
71         tyConArity  :: Arity
72     }
73
74
75   | AlgTyCon {          -- Tuples, data type, and newtype decls.
76                         -- All lifted, all boxed
77         tyConUnique :: Unique,
78         tyConName   :: Name,
79         tyConKind   :: Kind,
80         tyConArity  :: Arity,
81         
82         tyConTyVars     :: [TyVar],
83         dataTyConTheta  :: [(Class,[Type])],
84
85         dataCons :: [DataCon],
86                 -- Its data constructors, with fully polymorphic types
87                 --      This list can be empty, when we import a data type abstractly,
88                 --      either (a) the interface is hand-written and doesn't give
89                 --                 the constructors, or
90                 --             (b) in a quest for fast compilation we don't import 
91                 --                 the constructors
92
93         dataTyConDerivings   :: [Class],        -- Classes which have derived instances
94
95         dataTyConClass_maybe :: (Maybe Class),  -- Nothing for ordinary types; 
96                                                 -- Just c for the type constructor
97                                                 -- for dictionaries of class c.
98         algTyConFlavour :: NewOrData,
99         algTyConRec     :: RecFlag              -- Tells whether the data type is part of 
100                                                 -- a mutually-recursive group or not
101     }
102
103   | PrimTyCon {         -- Primitive types; cannot be defined in Haskell
104                         -- NB: All of these guys are *unlifted*, but not all are *unboxed*
105         tyConUnique  :: Unique,
106         tyConName    :: Name,
107         tyConKind    :: Kind,
108         tyConArity   :: Arity,
109         primTyConRep :: PrimRep
110     }
111
112   | TupleTyCon {
113
114         tyConUnique :: Unique,
115         tyConName   :: Name,
116         tyConKind   :: Kind,
117         tyConArity  :: Arity,
118         tyConBoxed  :: Bool,            -- True for boxed; False for unboxed
119         tyConTyVars :: [TyVar],
120         dataCon     :: DataCon
121     }
122
123   | SynTyCon {
124         tyConUnique :: Unique,
125         tyConName   :: Name,
126         tyConKind   :: Kind,
127         tyConArity  :: Arity,
128
129         tyConTyVars :: [TyVar],         -- Bound tyvars
130         synTyConDefn :: Type            -- Right-hand side, mentioning these type vars.
131                                         -- Acts as a template for the expansion when
132                                         -- the tycon is applied to some types.
133     }
134
135   | KindCon {           -- Type constructor at the kind level
136         tyConUnique :: Unique,
137         tyConName   :: Name,
138         tyConKind   :: SuperKind,
139         tyConArity  :: Arity
140     }
141
142   | SuperKindCon        {               -- The type of kind variables or boxity variables,
143         tyConUnique :: Unique,
144         tyConName   :: Name
145     }
146 \end{code}
147
148 %************************************************************************
149 %*                                                                      *
150 \subsection{TyCon Construction}
151 %*                                                                      *
152 %************************************************************************
153
154 Note: the TyCon constructors all take a Kind as one argument, even though
155 they could, in principle, work out their Kind from their other arguments.
156 But to do so they need functions from Types, and that makes a nasty
157 module mutual-recursion.  And they aren't called from many places.
158 So we compromise, and move their Kind calculation to the call site.
159
160 \begin{code}
161 mkSuperKindCon :: Name -> SuperKindCon
162 mkSuperKindCon name = SuperKindCon {
163                         tyConUnique = nameUnique name,
164                         tyConName = name
165                       }
166
167 mkKindCon :: Name -> SuperKind -> KindCon
168 mkKindCon name kind
169   = KindCon { 
170         tyConUnique = nameUnique name,
171         tyConName = name,
172         tyConArity = 0,
173         tyConKind = kind
174      }
175
176 mkFunTyCon :: Name -> Kind -> TyCon
177 mkFunTyCon name kind 
178   = FunTyCon { 
179         tyConUnique = nameUnique name,
180         tyConName   = name,
181         tyConKind   = kind,
182         tyConArity  = 2
183     }
184                             
185 mkAlgTyCon name kind tyvars theta cons derivs maybe_clas flavour rec
186   = AlgTyCon {  
187         tyConName = name,
188         tyConUnique = nameUnique name,
189         tyConKind = kind,
190         tyConArity = length tyvars,
191         tyConTyVars = tyvars,
192         dataTyConTheta = theta,
193         dataCons = cons,
194         dataTyConDerivings = derivs,
195         dataTyConClass_maybe = maybe_clas,
196         algTyConFlavour = flavour,
197         algTyConRec = rec
198     }
199
200 mkTupleTyCon name kind arity tyvars con boxed
201   = TupleTyCon {
202         tyConUnique = nameUnique name,
203         tyConName = name,
204         tyConKind = kind,
205         tyConArity = arity,
206         tyConBoxed = boxed,
207         tyConTyVars = tyvars,
208         dataCon = con
209     }
210
211 mkPrimTyCon name kind arity rep 
212   = PrimTyCon {
213         tyConName = name,
214         tyConUnique = nameUnique name,
215         tyConKind = kind,
216         tyConArity = arity,
217         primTyConRep = rep
218     }
219
220 mkSynTyCon name kind arity tyvars rhs 
221   = SynTyCon {  
222         tyConName = name,
223         tyConUnique = nameUnique name,
224         tyConKind = kind,
225         tyConArity = arity,
226         tyConTyVars = tyvars,
227         synTyConDefn = rhs
228     }
229
230 setTyConName tc name = tc {tyConName = name, tyConUnique = nameUnique name}
231 \end{code}
232
233 \begin{code}
234 isFunTyCon (FunTyCon {}) = True
235 isFunTyCon _             = False
236
237 isPrimTyCon (PrimTyCon {}) = True
238 isPrimTyCon _              = False
239
240 isUnLiftedTyCon (PrimTyCon {}) = True
241 isUnLiftedTyCon (TupleTyCon { tyConBoxed = False }) = True
242 isUnLiftedTyCon _              = False
243
244 -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon
245 isBoxedTyCon (AlgTyCon {}) = True
246 isBoxedTyCon (FunTyCon {}) = True
247 isBoxedTyCon (TupleTyCon {tyConBoxed = boxed}) = boxed
248 isBoxedTyCon (PrimTyCon {primTyConRep = rep}) = isFollowableRep rep
249
250 -- isAlgTyCon returns True for both @data@ and @newtype@
251 isAlgTyCon (AlgTyCon {})   = True
252 isAlgTyCon (TupleTyCon {}) = True
253 isAlgTyCon other           = False
254
255 -- isDataTyCon returns False for @newtype@ and for unboxed tuples
256 isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data})  = case new_or_data of
257                                                                 NewType -> False
258                                                                 other   -> True
259 isDataTyCon (TupleTyCon {tyConBoxed = True}) = True     
260 isDataTyCon other = False
261
262 isNewTyCon (AlgTyCon {algTyConFlavour = NewType}) = True 
263 isNewTyCon other                                  = False
264
265 -- A "product" tycon is non-recursive and has one constructor,
266 -- whether DataType or NewType
267 isProductTyCon (AlgTyCon {dataCons = [c], algTyConRec = NonRecursive}) = True
268 isProductTyCon (TupleTyCon {}) = True
269 isProductTyCon other = False
270
271 isSynTyCon (SynTyCon {}) = True
272 isSynTyCon _             = False
273
274 isEnumerationTyCon (AlgTyCon {algTyConFlavour = EnumType}) = True
275 isEnumerationTyCon other                                   = False
276
277 -- The unit tycon isn't classed as a tuple tycon
278 isTupleTyCon (TupleTyCon {tyConArity = arity, tyConBoxed = True}) = arity >= 2
279 isTupleTyCon other = False
280
281 isUnboxedTupleTyCon (TupleTyCon {tyConBoxed = False}) = True
282 isUnboxedTupleTyCon other = False
283 \end{code}
284
285 \begin{code}
286 tyConDataCons :: TyCon -> [DataCon]
287 tyConDataCons (AlgTyCon {dataCons = cons}) = cons
288 tyConDataCons (TupleTyCon {dataCon = con}) = [con]
289 tyConDataCons other                        = []
290         -- You may think this last equation should fail,
291         -- but it's quite convenient to return no constructors for
292         -- a synonym; see for example the call in TcTyClsDecls.
293
294 tyConFamilySize  :: TyCon -> Int
295 tyConFamilySize (AlgTyCon {dataCons = cons}) = length cons
296 tyConFamilySize (TupleTyCon {}) = 1
297 #ifdef DEBUG
298 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other)
299 #endif
300
301 tyConPrimRep :: TyCon -> PrimRep
302 tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep
303 tyConPrimRep _                                = PtrRep
304 \end{code}
305
306 \begin{code}
307 tyConDerivings :: TyCon -> [Class]
308 tyConDerivings (AlgTyCon {dataTyConDerivings = derivs}) = derivs
309 tyConDerivings other                                    = []
310 \end{code}
311
312 \begin{code}
313 tyConTheta :: TyCon -> [(Class, [Type])]
314 tyConTheta (AlgTyCon {dataTyConTheta = theta}) = theta
315 -- should ask about anything else
316 \end{code}
317
318 \begin{code}
319 getSynTyConDefn :: TyCon -> ([TyVar], Type)
320 getSynTyConDefn (SynTyCon {tyConTyVars = tyvars, synTyConDefn = ty}) = (tyvars,ty)
321 \end{code}
322
323 \begin{code}
324 maybeTyConSingleCon :: TyCon -> Maybe DataCon
325 maybeTyConSingleCon (AlgTyCon {dataCons = [c]})  = Just c
326 maybeTyConSingleCon (AlgTyCon {})                = Nothing
327 maybeTyConSingleCon (TupleTyCon {dataCon = con}) = Just con
328 maybeTyConSingleCon (PrimTyCon {})               = Nothing
329 maybeTyConSingleCon other = panic (showSDoc (ppr other))
330 \end{code}
331
332 \begin{code}
333 tyConClass_maybe :: TyCon -> Maybe Class
334 tyConClass_maybe (AlgTyCon {dataTyConClass_maybe = maybe_cls}) = maybe_cls
335 tyConClass_maybe other_tycon                                   = Nothing
336 \end{code}
337
338
339 %************************************************************************
340 %*                                                                      *
341 \subsection[TyCon-instances]{Instance declarations for @TyCon@}
342 %*                                                                      *
343 %************************************************************************
344
345 @TyCon@s are compared by comparing their @Unique@s.
346
347 The strictness analyser needs @Ord@. It is a lexicographic order with
348 the property @(a<=b) || (b<=a)@.
349
350 \begin{code}
351 instance Eq TyCon where
352     a == b = case (a `compare` b) of { EQ -> True;   _ -> False }
353     a /= b = case (a `compare` b) of { EQ -> False;  _ -> True  }
354
355 instance Ord TyCon where
356     a <= b = case (a `compare` b) of { LT -> True;  EQ -> True;  GT -> False }
357     a <  b = case (a `compare` b) of { LT -> True;  EQ -> False; GT -> False }
358     a >= b = case (a `compare` b) of { LT -> False; EQ -> True;  GT -> True  }
359     a >  b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True  }
360     compare a b = getUnique a `compare` getUnique b
361
362 instance Uniquable TyCon where
363     getUnique tc = tyConUnique tc
364
365 instance Outputable TyCon where
366     ppr tc  = ppr (getName tc)
367
368 instance NamedThing TyCon where
369     getName = tyConName
370 \end{code}
371
372
373 %************************************************************************
374 %*                                                                      *
375 \subsection{Kind constructors}
376 %*                                                                      *
377 %************************************************************************
378
379 @matchesTyCon tc1 tc2@ checks whether an appliation
380 (tc1 t1..tn) matches (tc2 t1..tn).  By "matches" we basically mean "equals",
381 except that at the kind level tc2 might have more boxity info than tc1.
382
383 \begin{code}
384 matchesTyCon :: TyCon   -- Expected (e.g. arg type of function)
385              -> TyCon   -- Inferred (e.g. type of actual arg to function)
386              -> Bool
387
388 matchesTyCon tc1 tc2 =  uniq1 == uniq2 || uniq1 == anyBoxConKey
389                      where
390                         uniq1 = tyConUnique tc1
391                         uniq2 = tyConUnique tc2
392 \end{code}