Follow OccName changes in TysPrim
[ghc-hetmet.git] / compiler / prelude / TysPrim.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1998
3 %
4 \section[TysPrim]{Wired-in knowledge about primitive types}
5
6 \begin{code}
7 module TysPrim(
8         alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar,
9         alphaTy, betaTy, gammaTy, deltaTy,
10         openAlphaTy, openBetaTy, openAlphaTyVar, openBetaTyVar, openAlphaTyVars,
11
12         primTyCons,
13
14         charPrimTyCon,          charPrimTy,
15         intPrimTyCon,           intPrimTy,
16         wordPrimTyCon,          wordPrimTy,
17         addrPrimTyCon,          addrPrimTy,
18         floatPrimTyCon,         floatPrimTy,
19         doublePrimTyCon,        doublePrimTy,
20
21         statePrimTyCon,         mkStatePrimTy,
22         realWorldTyCon,         realWorldTy, realWorldStatePrimTy,
23
24         arrayPrimTyCon,                 mkArrayPrimTy, 
25         byteArrayPrimTyCon,             byteArrayPrimTy,
26         mutableArrayPrimTyCon,          mkMutableArrayPrimTy,
27         mutableByteArrayPrimTyCon,      mkMutableByteArrayPrimTy,
28         mutVarPrimTyCon,                mkMutVarPrimTy,
29
30         mVarPrimTyCon,                  mkMVarPrimTy,   
31         tVarPrimTyCon,                  mkTVarPrimTy,
32         stablePtrPrimTyCon,             mkStablePtrPrimTy,
33         stableNamePrimTyCon,            mkStableNamePrimTy,
34         bcoPrimTyCon,                   bcoPrimTy,
35         weakPrimTyCon,                  mkWeakPrimTy,
36         threadIdPrimTyCon,              threadIdPrimTy,
37         
38         int32PrimTyCon,         int32PrimTy,
39         word32PrimTyCon,        word32PrimTy,
40
41         int64PrimTyCon,         int64PrimTy,
42         word64PrimTyCon,        word64PrimTy,
43
44         anyPrimTyCon, anyPrimTy, anyPrimTyCon1, mkAnyPrimTyCon
45   ) where
46
47 #include "HsVersions.h"
48
49 import Var              ( TyVar, mkTyVar )
50 import Name             ( Name, BuiltInSyntax(..), mkInternalName, mkWiredInName )
51 import OccName          ( mkTyVarOccFS, mkTcOccFS )
52 import TyCon            ( TyCon, mkPrimTyCon, mkLiftedPrimTyCon,
53                           PrimRep(..) )
54 import Type
55 import SrcLoc
56 import Unique           ( mkAlphaTyVarUnique, pprUnique )
57 import PrelNames
58 import StaticFlags
59 import FastString
60 import Outputable
61
62 import Char             ( ord, chr )
63 \end{code}
64
65 %************************************************************************
66 %*                                                                      *
67 \subsection{Primitive type constructors}
68 %*                                                                      *
69 %************************************************************************
70
71 \begin{code}
72 primTyCons :: [TyCon]
73 primTyCons 
74   = [ addrPrimTyCon
75     , arrayPrimTyCon
76     , byteArrayPrimTyCon
77     , charPrimTyCon
78     , doublePrimTyCon
79     , floatPrimTyCon
80     , intPrimTyCon
81     , int32PrimTyCon
82     , int64PrimTyCon
83     , bcoPrimTyCon
84     , weakPrimTyCon
85     , mutableArrayPrimTyCon
86     , mutableByteArrayPrimTyCon
87     , mVarPrimTyCon
88     , tVarPrimTyCon
89     , mutVarPrimTyCon
90     , realWorldTyCon
91     , stablePtrPrimTyCon
92     , stableNamePrimTyCon
93     , statePrimTyCon
94     , threadIdPrimTyCon
95     , wordPrimTyCon
96     , word32PrimTyCon
97     , word64PrimTyCon
98     , anyPrimTyCon, anyPrimTyCon1
99     ]
100
101 mkPrimTc :: FastString -> Unique -> TyCon -> Name
102 mkPrimTc fs unique tycon
103   = mkWiredInName gHC_PRIM (mkTcOccFS fs) 
104                   unique
105                   (ATyCon tycon)        -- Relevant TyCon
106                   UserSyntax            -- None are built-in syntax
107
108 charPrimTyConName, intPrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, realWorldTyConName, arrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName, anyPrimTyConName, anyPrimTyCon1Name :: Name
109 charPrimTyConName             = mkPrimTc (fsLit "Char#") charPrimTyConKey charPrimTyCon
110 intPrimTyConName              = mkPrimTc (fsLit "Int#") intPrimTyConKey  intPrimTyCon
111 int32PrimTyConName            = mkPrimTc (fsLit "Int32#") int32PrimTyConKey int32PrimTyCon
112 int64PrimTyConName            = mkPrimTc (fsLit "Int64#") int64PrimTyConKey int64PrimTyCon
113 wordPrimTyConName             = mkPrimTc (fsLit "Word#") wordPrimTyConKey wordPrimTyCon
114 word32PrimTyConName           = mkPrimTc (fsLit "Word32#") word32PrimTyConKey word32PrimTyCon
115 word64PrimTyConName           = mkPrimTc (fsLit "Word64#") word64PrimTyConKey word64PrimTyCon
116 addrPrimTyConName             = mkPrimTc (fsLit "Addr#") addrPrimTyConKey addrPrimTyCon
117 floatPrimTyConName            = mkPrimTc (fsLit "Float#") floatPrimTyConKey floatPrimTyCon
118 doublePrimTyConName           = mkPrimTc (fsLit "Double#") doublePrimTyConKey doublePrimTyCon
119 statePrimTyConName            = mkPrimTc (fsLit "State#") statePrimTyConKey statePrimTyCon
120 realWorldTyConName            = mkPrimTc (fsLit "RealWorld") realWorldTyConKey realWorldTyCon
121 arrayPrimTyConName            = mkPrimTc (fsLit "Array#") arrayPrimTyConKey arrayPrimTyCon
122 byteArrayPrimTyConName        = mkPrimTc (fsLit "ByteArray#") byteArrayPrimTyConKey byteArrayPrimTyCon
123 mutableArrayPrimTyConName     = mkPrimTc (fsLit "MutableArray#") mutableArrayPrimTyConKey mutableArrayPrimTyCon
124 mutableByteArrayPrimTyConName = mkPrimTc (fsLit "MutableByteArray#") mutableByteArrayPrimTyConKey mutableByteArrayPrimTyCon
125 mutVarPrimTyConName           = mkPrimTc (fsLit "MutVar#") mutVarPrimTyConKey mutVarPrimTyCon
126 mVarPrimTyConName             = mkPrimTc (fsLit "MVar#") mVarPrimTyConKey mVarPrimTyCon
127 tVarPrimTyConName             = mkPrimTc (fsLit "TVar#") tVarPrimTyConKey tVarPrimTyCon
128 stablePtrPrimTyConName        = mkPrimTc (fsLit "StablePtr#") stablePtrPrimTyConKey stablePtrPrimTyCon
129 stableNamePrimTyConName       = mkPrimTc (fsLit "StableName#") stableNamePrimTyConKey stableNamePrimTyCon
130 bcoPrimTyConName              = mkPrimTc (fsLit "BCO#") bcoPrimTyConKey bcoPrimTyCon
131 weakPrimTyConName             = mkPrimTc (fsLit "Weak#") weakPrimTyConKey weakPrimTyCon
132 threadIdPrimTyConName         = mkPrimTc (fsLit "ThreadId#") threadIdPrimTyConKey threadIdPrimTyCon
133 anyPrimTyConName              = mkPrimTc (fsLit "Any") anyPrimTyConKey anyPrimTyCon
134 anyPrimTyCon1Name             = mkPrimTc (fsLit "Any1") anyPrimTyCon1Key anyPrimTyCon
135 \end{code}
136
137 %************************************************************************
138 %*                                                                      *
139 \subsection{Support code}
140 %*                                                                      *
141 %************************************************************************
142
143 alphaTyVars is a list of type variables for use in templates: 
144         ["a", "b", ..., "z", "t1", "t2", ... ]
145
146 \begin{code}
147 tyVarList :: Kind -> [TyVar]
148 tyVarList kind = [ mkTyVar (mkInternalName (mkAlphaTyVarUnique u) 
149                                 (mkTyVarOccFS (mkFastString name))
150                                 noSrcSpan) kind
151                  | u <- [2..],
152                    let name | c <= 'z'  = [c]
153                             | otherwise = 't':show u
154                             where c = chr (u-2 + ord 'a')
155                  ]
156
157 alphaTyVars :: [TyVar]
158 alphaTyVars = tyVarList liftedTypeKind
159
160 betaTyVars :: [TyVar]
161 betaTyVars = tail alphaTyVars
162
163 alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar :: TyVar
164 (alphaTyVar:betaTyVar:gammaTyVar:deltaTyVar:_) = alphaTyVars
165
166 alphaTys :: [Type]
167 alphaTys = mkTyVarTys alphaTyVars
168 alphaTy, betaTy, gammaTy, deltaTy :: Type
169 (alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys
170
171         -- openAlphaTyVar is prepared to be instantiated
172         -- to a lifted or unlifted type variable.  It's used for the 
173         -- result type for "error", so that we can have (error Int# "Help")
174 openAlphaTyVars :: [TyVar]
175 openAlphaTyVar, openBetaTyVar :: TyVar
176 openAlphaTyVars@(openAlphaTyVar:openBetaTyVar:_) = tyVarList openTypeKind
177
178 openAlphaTy, openBetaTy :: Type
179 openAlphaTy = mkTyVarTy openAlphaTyVar
180 openBetaTy   = mkTyVarTy openBetaTyVar
181 \end{code}
182
183
184 %************************************************************************
185 %*                                                                      *
186 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
187 %*                                                                      *
188 %************************************************************************
189
190 \begin{code}
191 -- only used herein
192 pcPrimTyCon :: Name -> Int -> PrimRep -> TyCon
193 pcPrimTyCon name arity rep
194   = mkPrimTyCon name kind arity rep
195   where
196     kind        = mkArrowKinds (replicate arity liftedTypeKind) result_kind
197     result_kind = unliftedTypeKind
198
199 pcPrimTyCon0 :: Name -> PrimRep -> TyCon
200 pcPrimTyCon0 name rep
201   = mkPrimTyCon name result_kind 0 rep
202   where
203     result_kind = unliftedTypeKind
204
205 charPrimTy :: Type
206 charPrimTy      = mkTyConTy charPrimTyCon
207 charPrimTyCon :: TyCon
208 charPrimTyCon   = pcPrimTyCon0 charPrimTyConName WordRep
209
210 intPrimTy :: Type
211 intPrimTy       = mkTyConTy intPrimTyCon
212 intPrimTyCon :: TyCon
213 intPrimTyCon    = pcPrimTyCon0 intPrimTyConName IntRep
214
215 int32PrimTy :: Type
216 int32PrimTy     = mkTyConTy int32PrimTyCon
217 int32PrimTyCon :: TyCon
218 int32PrimTyCon  = pcPrimTyCon0 int32PrimTyConName IntRep
219
220 int64PrimTy :: Type
221 int64PrimTy     = mkTyConTy int64PrimTyCon
222 int64PrimTyCon :: TyCon
223 int64PrimTyCon  = pcPrimTyCon0 int64PrimTyConName Int64Rep
224
225 wordPrimTy :: Type
226 wordPrimTy      = mkTyConTy wordPrimTyCon
227 wordPrimTyCon :: TyCon
228 wordPrimTyCon   = pcPrimTyCon0 wordPrimTyConName WordRep
229
230 word32PrimTy :: Type
231 word32PrimTy    = mkTyConTy word32PrimTyCon
232 word32PrimTyCon :: TyCon
233 word32PrimTyCon = pcPrimTyCon0 word32PrimTyConName WordRep
234
235 word64PrimTy :: Type
236 word64PrimTy    = mkTyConTy word64PrimTyCon
237 word64PrimTyCon :: TyCon
238 word64PrimTyCon = pcPrimTyCon0 word64PrimTyConName Word64Rep
239
240 addrPrimTy :: Type
241 addrPrimTy      = mkTyConTy addrPrimTyCon
242 addrPrimTyCon :: TyCon
243 addrPrimTyCon   = pcPrimTyCon0 addrPrimTyConName AddrRep
244
245 floatPrimTy     :: Type
246 floatPrimTy     = mkTyConTy floatPrimTyCon
247 floatPrimTyCon :: TyCon
248 floatPrimTyCon  = pcPrimTyCon0 floatPrimTyConName FloatRep
249
250 doublePrimTy :: Type
251 doublePrimTy    = mkTyConTy doublePrimTyCon
252 doublePrimTyCon :: TyCon
253 doublePrimTyCon = pcPrimTyCon0 doublePrimTyConName DoubleRep
254 \end{code}
255
256
257 %************************************************************************
258 %*                                                                      *
259 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
260 %*                                                                      *
261 %************************************************************************
262
263 State# is the primitive, unlifted type of states.  It has one type parameter,
264 thus
265         State# RealWorld
266 or
267         State# s
268
269 where s is a type variable. The only purpose of the type parameter is to
270 keep different state threads separate.  It is represented by nothing at all.
271
272 \begin{code}
273 mkStatePrimTy :: Type -> Type
274 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
275 statePrimTyCon :: TyCon
276 statePrimTyCon   = pcPrimTyCon statePrimTyConName 1 VoidRep
277 \end{code}
278
279 RealWorld is deeply magical.  It is *primitive*, but it is not
280 *unlifted* (hence ptrArg).  We never manipulate values of type
281 RealWorld; it's only used in the type system, to parameterise State#.
282
283 \begin{code}
284 realWorldTyCon :: TyCon
285 realWorldTyCon = mkLiftedPrimTyCon realWorldTyConName liftedTypeKind 0 PtrRep
286 realWorldTy :: Type
287 realWorldTy          = mkTyConTy realWorldTyCon
288 realWorldStatePrimTy :: Type
289 realWorldStatePrimTy = mkStatePrimTy realWorldTy        -- State# RealWorld
290 \end{code}
291
292 Note: the ``state-pairing'' types are not truly primitive, so they are
293 defined in \tr{TysWiredIn.lhs}, not here.
294
295
296 %************************************************************************
297 %*                                                                      *
298                 Any
299 %*                                                                      *
300 %************************************************************************
301
302 The type constructor Any is type to which you can unsafely coerce any
303 lifted type, and back. 
304
305   * It is lifted, and hence represented by a pointer
306
307   * It does not claim to be a *data* type, and that's important for
308     the code generator, because the code gen may *enter* a data value
309     but never enters a function value.  
310
311 It's also used to instantiate un-constrained type variables after type
312 checking.  For example
313         length Any []
314 Annoyingly, we sometimes need Anys of other kinds, such as (*->*) etc.
315 This is a bit like tuples.   We define a couple of useful ones here,
316 and make others up on the fly.  If any of these others end up being exported
317 into interface files, we'll get a crash; at least until we add interface-file
318 syntax to support them.
319
320 \begin{code}
321 anyPrimTy :: Type
322 anyPrimTy = mkTyConApp anyPrimTyCon []
323
324 anyPrimTyCon :: TyCon   -- Kind *
325 anyPrimTyCon = mkLiftedPrimTyCon anyPrimTyConName liftedTypeKind 0 PtrRep
326
327 anyPrimTyCon1 :: TyCon  -- Kind *->*
328 anyPrimTyCon1 = mkLiftedPrimTyCon anyPrimTyCon1Name kind 0 PtrRep
329   where
330     kind = mkArrowKind liftedTypeKind liftedTypeKind
331                                   
332 mkAnyPrimTyCon :: Unique -> Kind -> TyCon
333 -- Grotesque hack alert: the client gives the unique; so equality won't work
334 mkAnyPrimTyCon unique kind 
335   = WARN( opt_PprStyle_Debug, ptext (sLit "Urk! Inventing strangely-kinded Any TyCon:") <+> ppr unique <+> ppr kind )
336         -- See Note [Strangely-kinded void TyCons] in TcHsSyn
337     tycon
338   where
339      name  = mkPrimTc (mkFastString ("Any" ++ showSDoc (pprUnique unique))) unique tycon
340      tycon = mkLiftedPrimTyCon name kind 0 PtrRep
341 \end{code}
342
343
344 %************************************************************************
345 %*                                                                      *
346 \subsection[TysPrim-arrays]{The primitive array types}
347 %*                                                                      *
348 %************************************************************************
349
350 \begin{code}
351 arrayPrimTyCon, mutableArrayPrimTyCon, mutableByteArrayPrimTyCon,
352     byteArrayPrimTyCon :: TyCon
353 arrayPrimTyCon            = pcPrimTyCon  arrayPrimTyConName            1 PtrRep
354 mutableArrayPrimTyCon     = pcPrimTyCon  mutableArrayPrimTyConName     2 PtrRep
355 mutableByteArrayPrimTyCon = pcPrimTyCon  mutableByteArrayPrimTyConName 1 PtrRep
356 byteArrayPrimTyCon        = pcPrimTyCon0 byteArrayPrimTyConName          PtrRep
357
358 mkArrayPrimTy :: Type -> Type
359 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
360 byteArrayPrimTy :: Type
361 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
362 mkMutableArrayPrimTy :: Type -> Type -> Type
363 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
364 mkMutableByteArrayPrimTy :: Type -> Type
365 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
366 \end{code}
367
368 %************************************************************************
369 %*                                                                      *
370 \subsection[TysPrim-mut-var]{The mutable variable type}
371 %*                                                                      *
372 %************************************************************************
373
374 \begin{code}
375 mutVarPrimTyCon :: TyCon
376 mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName 2 PtrRep
377
378 mkMutVarPrimTy :: Type -> Type -> Type
379 mkMutVarPrimTy s elt        = mkTyConApp mutVarPrimTyCon [s, elt]
380 \end{code}
381
382 %************************************************************************
383 %*                                                                      *
384 \subsection[TysPrim-synch-var]{The synchronizing variable type}
385 %*                                                                      *
386 %************************************************************************
387
388 \begin{code}
389 mVarPrimTyCon :: TyCon
390 mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName 2 PtrRep
391
392 mkMVarPrimTy :: Type -> Type -> Type
393 mkMVarPrimTy s elt          = mkTyConApp mVarPrimTyCon [s, elt]
394 \end{code}
395
396 %************************************************************************
397 %*                                                                      *
398 \subsection[TysPrim-stm-var]{The transactional variable type}
399 %*                                                                      *
400 %************************************************************************
401
402 \begin{code}
403 tVarPrimTyCon :: TyCon
404 tVarPrimTyCon = pcPrimTyCon tVarPrimTyConName 2 PtrRep
405
406 mkTVarPrimTy :: Type -> Type -> Type
407 mkTVarPrimTy s elt = mkTyConApp tVarPrimTyCon [s, elt]
408 \end{code}
409
410 %************************************************************************
411 %*                                                                      *
412 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
413 %*                                                                      *
414 %************************************************************************
415
416 \begin{code}
417 stablePtrPrimTyCon :: TyCon
418 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName 1 AddrRep
419
420 mkStablePtrPrimTy :: Type -> Type
421 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
422 \end{code}
423
424 %************************************************************************
425 %*                                                                      *
426 \subsection[TysPrim-stable-names]{The stable-name type}
427 %*                                                                      *
428 %************************************************************************
429
430 \begin{code}
431 stableNamePrimTyCon :: TyCon
432 stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName 1 PtrRep
433
434 mkStableNamePrimTy :: Type -> Type
435 mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty]
436 \end{code}
437
438 %************************************************************************
439 %*                                                                      *
440 \subsection[TysPrim-BCOs]{The ``bytecode object'' type}
441 %*                                                                      *
442 %************************************************************************
443
444 \begin{code}
445 bcoPrimTy    :: Type
446 bcoPrimTy    = mkTyConTy bcoPrimTyCon
447 bcoPrimTyCon :: TyCon
448 bcoPrimTyCon = pcPrimTyCon0 bcoPrimTyConName PtrRep
449 \end{code}
450   
451 %************************************************************************
452 %*                                                                      *
453 \subsection[TysPrim-Weak]{The ``weak pointer'' type}
454 %*                                                                      *
455 %************************************************************************
456
457 \begin{code}
458 weakPrimTyCon :: TyCon
459 weakPrimTyCon = pcPrimTyCon weakPrimTyConName 1 PtrRep
460
461 mkWeakPrimTy :: Type -> Type
462 mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v]
463 \end{code}
464
465 %************************************************************************
466 %*                                                                      *
467 \subsection[TysPrim-thread-ids]{The ``thread id'' type}
468 %*                                                                      *
469 %************************************************************************
470
471 A thread id is represented by a pointer to the TSO itself, to ensure
472 that they are always unique and we can always find the TSO for a given
473 thread id.  However, this has the unfortunate consequence that a
474 ThreadId# for a given thread is treated as a root by the garbage
475 collector and can keep TSOs around for too long.
476
477 Hence the programmer API for thread manipulation uses a weak pointer
478 to the thread id internally.
479
480 \begin{code}
481 threadIdPrimTy :: Type
482 threadIdPrimTy    = mkTyConTy threadIdPrimTyCon
483 threadIdPrimTyCon :: TyCon
484 threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName PtrRep
485 \end{code}