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