Substantial improvements to coercion optimisation
[ghc-hetmet.git] / compiler / prelude / TysPrim.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1998
3 %
4
5      
6 \section[TysPrim]{Wired-in knowledge about primitive types}
7
8 \begin{code}
9 -- | This module defines TyCons that can't be expressed in Haskell. 
10 --   They are all, therefore, wired-in TyCons.  C.f module TysWiredIn
11 module TysPrim(
12         alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar,
13         alphaTy, betaTy, gammaTy, deltaTy,
14         openAlphaTy, openBetaTy, openAlphaTyVar, openBetaTyVar, openAlphaTyVars,
15
16         primTyCons,
17
18         charPrimTyCon,          charPrimTy,
19         intPrimTyCon,           intPrimTy,
20         wordPrimTyCon,          wordPrimTy,
21         addrPrimTyCon,          addrPrimTy,
22         floatPrimTyCon,         floatPrimTy,
23         doublePrimTyCon,        doublePrimTy,
24
25         statePrimTyCon,         mkStatePrimTy,
26         realWorldTyCon,         realWorldTy, realWorldStatePrimTy,
27
28         arrayPrimTyCon,                 mkArrayPrimTy, 
29         byteArrayPrimTyCon,             byteArrayPrimTy,
30         mutableArrayPrimTyCon,          mkMutableArrayPrimTy,
31         mutableByteArrayPrimTyCon,      mkMutableByteArrayPrimTy,
32         mutVarPrimTyCon,                mkMutVarPrimTy,
33
34         mVarPrimTyCon,                  mkMVarPrimTy,   
35         tVarPrimTyCon,                  mkTVarPrimTy,
36         stablePtrPrimTyCon,             mkStablePtrPrimTy,
37         stableNamePrimTyCon,            mkStableNamePrimTy,
38         bcoPrimTyCon,                   bcoPrimTy,
39         weakPrimTyCon,                  mkWeakPrimTy,
40         threadIdPrimTyCon,              threadIdPrimTy,
41         
42         int32PrimTyCon,         int32PrimTy,
43         word32PrimTyCon,        word32PrimTy,
44
45         int64PrimTyCon,         int64PrimTy,
46         word64PrimTyCon,        word64PrimTy,
47
48         -- * Any
49         anyTyCon, anyType, anyTyConOfKind, anyTypeOfKind
50   ) where
51
52 #include "HsVersions.h"
53
54 import Var              ( TyVar, mkTyVar )
55 import Name             ( Name, BuiltInSyntax(..), mkInternalName, mkWiredInName )
56 import OccName          ( mkTcOcc )
57 import OccName          ( mkTyVarOccFS, mkTcOccFS )
58 import TyCon            ( TyCon, mkPrimTyCon, mkLiftedPrimTyCon, mkAnyTyCon )
59 import Type
60 import Coercion
61 import SrcLoc
62 import Unique           ( mkAlphaTyVarUnique )
63 import PrelNames
64 import FastString
65 import Outputable
66
67 import Data.Char
68 \end{code}
69
70 %************************************************************************
71 %*                                                                      *
72 \subsection{Primitive type constructors}
73 %*                                                                      *
74 %************************************************************************
75
76 \begin{code}
77 primTyCons :: [TyCon]
78 primTyCons 
79   = [ addrPrimTyCon
80     , arrayPrimTyCon
81     , byteArrayPrimTyCon
82     , charPrimTyCon
83     , doublePrimTyCon
84     , floatPrimTyCon
85     , intPrimTyCon
86     , int32PrimTyCon
87     , int64PrimTyCon
88     , bcoPrimTyCon
89     , weakPrimTyCon
90     , mutableArrayPrimTyCon
91     , mutableByteArrayPrimTyCon
92     , mVarPrimTyCon
93     , tVarPrimTyCon
94     , mutVarPrimTyCon
95     , realWorldTyCon
96     , stablePtrPrimTyCon
97     , stableNamePrimTyCon
98     , statePrimTyCon
99     , threadIdPrimTyCon
100     , wordPrimTyCon
101     , word32PrimTyCon
102     , word64PrimTyCon
103     , anyTyCon
104     ]
105
106 mkPrimTc :: FastString -> Unique -> TyCon -> Name
107 mkPrimTc fs unique tycon
108   = mkWiredInName gHC_PRIM (mkTcOccFS fs) 
109                   unique
110                   (ATyCon tycon)        -- Relevant TyCon
111                   UserSyntax            -- None are built-in syntax
112
113 charPrimTyConName, intPrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, realWorldTyConName, arrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName :: Name
114 charPrimTyConName             = mkPrimTc (fsLit "Char#") charPrimTyConKey charPrimTyCon
115 intPrimTyConName              = mkPrimTc (fsLit "Int#") intPrimTyConKey  intPrimTyCon
116 int32PrimTyConName            = mkPrimTc (fsLit "Int32#") int32PrimTyConKey int32PrimTyCon
117 int64PrimTyConName            = mkPrimTc (fsLit "Int64#") int64PrimTyConKey int64PrimTyCon
118 wordPrimTyConName             = mkPrimTc (fsLit "Word#") wordPrimTyConKey wordPrimTyCon
119 word32PrimTyConName           = mkPrimTc (fsLit "Word32#") word32PrimTyConKey word32PrimTyCon
120 word64PrimTyConName           = mkPrimTc (fsLit "Word64#") word64PrimTyConKey word64PrimTyCon
121 addrPrimTyConName             = mkPrimTc (fsLit "Addr#") addrPrimTyConKey addrPrimTyCon
122 floatPrimTyConName            = mkPrimTc (fsLit "Float#") floatPrimTyConKey floatPrimTyCon
123 doublePrimTyConName           = mkPrimTc (fsLit "Double#") doublePrimTyConKey doublePrimTyCon
124 statePrimTyConName            = mkPrimTc (fsLit "State#") statePrimTyConKey statePrimTyCon
125 realWorldTyConName            = mkPrimTc (fsLit "RealWorld") realWorldTyConKey realWorldTyCon
126 arrayPrimTyConName            = mkPrimTc (fsLit "Array#") arrayPrimTyConKey arrayPrimTyCon
127 byteArrayPrimTyConName        = mkPrimTc (fsLit "ByteArray#") byteArrayPrimTyConKey byteArrayPrimTyCon
128 mutableArrayPrimTyConName     = mkPrimTc (fsLit "MutableArray#") mutableArrayPrimTyConKey mutableArrayPrimTyCon
129 mutableByteArrayPrimTyConName = mkPrimTc (fsLit "MutableByteArray#") mutableByteArrayPrimTyConKey mutableByteArrayPrimTyCon
130 mutVarPrimTyConName           = mkPrimTc (fsLit "MutVar#") mutVarPrimTyConKey mutVarPrimTyCon
131 mVarPrimTyConName             = mkPrimTc (fsLit "MVar#") mVarPrimTyConKey mVarPrimTyCon
132 tVarPrimTyConName             = mkPrimTc (fsLit "TVar#") tVarPrimTyConKey tVarPrimTyCon
133 stablePtrPrimTyConName        = mkPrimTc (fsLit "StablePtr#") stablePtrPrimTyConKey stablePtrPrimTyCon
134 stableNamePrimTyConName       = mkPrimTc (fsLit "StableName#") stableNamePrimTyConKey stableNamePrimTyCon
135 bcoPrimTyConName              = mkPrimTc (fsLit "BCO#") bcoPrimTyConKey bcoPrimTyCon
136 weakPrimTyConName             = mkPrimTc (fsLit "Weak#") weakPrimTyConKey weakPrimTyCon
137 threadIdPrimTyConName         = mkPrimTc (fsLit "ThreadId#") threadIdPrimTyConKey threadIdPrimTyCon
138 \end{code}
139
140 %************************************************************************
141 %*                                                                      *
142 \subsection{Support code}
143 %*                                                                      *
144 %************************************************************************
145
146 alphaTyVars is a list of type variables for use in templates: 
147         ["a", "b", ..., "z", "t1", "t2", ... ]
148
149 \begin{code}
150 tyVarList :: Kind -> [TyVar]
151 tyVarList kind = [ mkTyVar (mkInternalName (mkAlphaTyVarUnique u) 
152                                 (mkTyVarOccFS (mkFastString name))
153                                 noSrcSpan) kind
154                  | u <- [2..],
155                    let name | c <= 'z'  = [c]
156                             | otherwise = 't':show u
157                             where c = chr (u-2 + ord 'a')
158                  ]
159
160 alphaTyVars :: [TyVar]
161 alphaTyVars = tyVarList liftedTypeKind
162
163 betaTyVars :: [TyVar]
164 betaTyVars = tail alphaTyVars
165
166 alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar :: TyVar
167 (alphaTyVar:betaTyVar:gammaTyVar:deltaTyVar:_) = alphaTyVars
168
169 alphaTys :: [Type]
170 alphaTys = mkTyVarTys alphaTyVars
171 alphaTy, betaTy, gammaTy, deltaTy :: Type
172 (alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys
173
174         -- openAlphaTyVar is prepared to be instantiated
175         -- to a lifted or unlifted type variable.  It's used for the 
176         -- result type for "error", so that we can have (error Int# "Help")
177 openAlphaTyVars :: [TyVar]
178 openAlphaTyVar, openBetaTyVar :: TyVar
179 openAlphaTyVars@(openAlphaTyVar:openBetaTyVar:_) = tyVarList openTypeKind
180
181 openAlphaTy, openBetaTy :: Type
182 openAlphaTy = mkTyVarTy openAlphaTyVar
183 openBetaTy   = mkTyVarTy openBetaTyVar
184 \end{code}
185
186
187 %************************************************************************
188 %*                                                                      *
189                 Any
190 %*                                                                      *
191 %************************************************************************
192
193 Note [Any types]
194 ~~~~~~~~~~~~~~~~
195 The type constructor Any::* has these properties
196
197   * It is defined in module GHC.Prim, and exported so that it is 
198     available to users.  For this reason it's treated like any other 
199     primitive type:
200       - has a fixed unique, anyTyConKey, 
201       - lives in the global name cache
202       - built with TyCon.PrimTyCon
203
204   * It is lifted, and hence represented by a pointer
205
206   * It is inhabited by at least one value, namely bottom
207
208   * You can unsafely coerce any lifted type to Ayny, and back.
209
210   * It does not claim to be a *data* type, and that's important for
211     the code generator, because the code gen may *enter* a data value
212     but never enters a function value. 
213
214   * It is used to instantiate otherwise un-constrained type variables of kind *
215     For example         length Any []
216     See Note [Strangely-kinded void TyCons]
217
218 In addition, we have a potentially-infinite family of types, one for
219 each kind /other than/ *, needed to instantiate otherwise
220 un-constrained type variables of kinds other than *.  This is a bit
221 like tuples; there is a potentially-infinite family.  They have slightly
222 different characteristics to Any::*:
223   
224   * They are built with TyCon.AnyTyCon
225   * They have non-user-writable names like "Any(*->*)" 
226   * They are not exported by GHC.Prim
227   * They are uninhabited (of course; not kind *)
228   * They have a unique derived from their OccName (see Note [Uniques of Any])
229   * Their Names do not live in the global name cache
230
231 Note [Uniques of Any]
232 ~~~~~~~~~~~~~~~~~~~~~
233 Although Any(*->*), say, doesn't have a binding site, it still needs
234 to have a Unique.  Unlike tuples (which are also an infinite family)
235 there is no convenient way to index them, so we use the Unique from
236 their OccName instead.  That should be unique!  (But in principle we
237 must take care: it does not include the module/package.)
238
239 Note [Strangely-kinded void TyCons]
240 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
241 See Trac #959 for more examples
242
243 When the type checker finds a type variable with no binding, which
244 means it can be instantiated with an arbitrary type, it usually
245 instantiates it to Void.  Eg.
246
247         length []
248 ===>
249         length Any (Nil Any)
250
251 But in really obscure programs, the type variable might have a kind
252 other than *, so we need to invent a suitably-kinded type.
253
254 This commit uses
255         Any for kind *
256         Any(*->*) for kind *->*
257         etc
258
259 \begin{code}
260 anyTyConName :: Name
261 anyTyConName = mkPrimTc (fsLit "Any") anyTyConKey anyTyCon
262
263 anyTyCon :: TyCon
264 anyTyCon = mkLiftedPrimTyCon anyTyConName liftedTypeKind 0 PtrRep
265
266 anyType :: Type
267 anyType = mkTyConApp anyTyCon []
268
269 anyTypeOfKind :: Kind -> Type
270 anyTypeOfKind kind
271   | isLiftedTypeKind kind = anyType
272   | otherwise             = mkTyConApp (mk_any_tycon kind) []
273
274 anyTyConOfKind :: Kind -> TyCon
275 anyTyConOfKind kind 
276   | isLiftedTypeKind kind = anyTyCon
277   | otherwise             = mk_any_tycon kind
278
279 mk_any_tycon :: Kind -> TyCon
280 mk_any_tycon kind    -- Kind other than *
281   = tycon
282   where
283           -- Derive the name from the kind, thus:
284           --     Any(*->*), Any(*->*->*)
285           -- These are names that can't be written by the user,
286           -- and are not allocated in the global name cache
287     str = "Any" ++ showSDoc (pprParendKind kind)
288
289     occ   = mkTcOcc str
290     uniq  = getUnique occ  -- See Note [Uniques of Any]
291     name  = mkWiredInName gHC_PRIM occ uniq (ATyCon tycon) UserSyntax
292     tycon = mkAnyTyCon name kind 
293 \end{code}
294
295
296 %************************************************************************
297 %*                                                                      *
298 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
299 %*                                                                      *
300 %************************************************************************
301
302 \begin{code}
303 -- only used herein
304 pcPrimTyCon :: Name -> Int -> PrimRep -> TyCon
305 pcPrimTyCon name arity rep
306   = mkPrimTyCon name kind arity rep
307   where
308     kind        = mkArrowKinds (replicate arity liftedTypeKind) result_kind
309     result_kind = unliftedTypeKind
310
311 pcPrimTyCon0 :: Name -> PrimRep -> TyCon
312 pcPrimTyCon0 name rep
313   = mkPrimTyCon name result_kind 0 rep
314   where
315     result_kind = unliftedTypeKind
316
317 charPrimTy :: Type
318 charPrimTy      = mkTyConTy charPrimTyCon
319 charPrimTyCon :: TyCon
320 charPrimTyCon   = pcPrimTyCon0 charPrimTyConName WordRep
321
322 intPrimTy :: Type
323 intPrimTy       = mkTyConTy intPrimTyCon
324 intPrimTyCon :: TyCon
325 intPrimTyCon    = pcPrimTyCon0 intPrimTyConName IntRep
326
327 int32PrimTy :: Type
328 int32PrimTy     = mkTyConTy int32PrimTyCon
329 int32PrimTyCon :: TyCon
330 int32PrimTyCon  = pcPrimTyCon0 int32PrimTyConName IntRep
331
332 int64PrimTy :: Type
333 int64PrimTy     = mkTyConTy int64PrimTyCon
334 int64PrimTyCon :: TyCon
335 int64PrimTyCon  = pcPrimTyCon0 int64PrimTyConName Int64Rep
336
337 wordPrimTy :: Type
338 wordPrimTy      = mkTyConTy wordPrimTyCon
339 wordPrimTyCon :: TyCon
340 wordPrimTyCon   = pcPrimTyCon0 wordPrimTyConName WordRep
341
342 word32PrimTy :: Type
343 word32PrimTy    = mkTyConTy word32PrimTyCon
344 word32PrimTyCon :: TyCon
345 word32PrimTyCon = pcPrimTyCon0 word32PrimTyConName WordRep
346
347 word64PrimTy :: Type
348 word64PrimTy    = mkTyConTy word64PrimTyCon
349 word64PrimTyCon :: TyCon
350 word64PrimTyCon = pcPrimTyCon0 word64PrimTyConName Word64Rep
351
352 addrPrimTy :: Type
353 addrPrimTy      = mkTyConTy addrPrimTyCon
354 addrPrimTyCon :: TyCon
355 addrPrimTyCon   = pcPrimTyCon0 addrPrimTyConName AddrRep
356
357 floatPrimTy     :: Type
358 floatPrimTy     = mkTyConTy floatPrimTyCon
359 floatPrimTyCon :: TyCon
360 floatPrimTyCon  = pcPrimTyCon0 floatPrimTyConName FloatRep
361
362 doublePrimTy :: Type
363 doublePrimTy    = mkTyConTy doublePrimTyCon
364 doublePrimTyCon :: TyCon
365 doublePrimTyCon = pcPrimTyCon0 doublePrimTyConName DoubleRep
366 \end{code}
367
368
369 %************************************************************************
370 %*                                                                      *
371 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
372 %*                                                                      *
373 %************************************************************************
374
375 State# is the primitive, unlifted type of states.  It has one type parameter,
376 thus
377         State# RealWorld
378 or
379         State# s
380
381 where s is a type variable. The only purpose of the type parameter is to
382 keep different state threads separate.  It is represented by nothing at all.
383
384 \begin{code}
385 mkStatePrimTy :: Type -> Type
386 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
387 statePrimTyCon :: TyCon
388 statePrimTyCon   = pcPrimTyCon statePrimTyConName 1 VoidRep
389 \end{code}
390
391 RealWorld is deeply magical.  It is *primitive*, but it is not
392 *unlifted* (hence ptrArg).  We never manipulate values of type
393 RealWorld; it's only used in the type system, to parameterise State#.
394
395 \begin{code}
396 realWorldTyCon :: TyCon
397 realWorldTyCon = mkLiftedPrimTyCon realWorldTyConName liftedTypeKind 0 PtrRep
398 realWorldTy :: Type
399 realWorldTy          = mkTyConTy realWorldTyCon
400 realWorldStatePrimTy :: Type
401 realWorldStatePrimTy = mkStatePrimTy realWorldTy        -- State# RealWorld
402 \end{code}
403
404 Note: the ``state-pairing'' types are not truly primitive, so they are
405 defined in \tr{TysWiredIn.lhs}, not here.
406
407
408 %************************************************************************
409 %*                                                                      *
410 \subsection[TysPrim-arrays]{The primitive array types}
411 %*                                                                      *
412 %************************************************************************
413
414 \begin{code}
415 arrayPrimTyCon, mutableArrayPrimTyCon, mutableByteArrayPrimTyCon,
416     byteArrayPrimTyCon :: TyCon
417 arrayPrimTyCon            = pcPrimTyCon  arrayPrimTyConName            1 PtrRep
418 mutableArrayPrimTyCon     = pcPrimTyCon  mutableArrayPrimTyConName     2 PtrRep
419 mutableByteArrayPrimTyCon = pcPrimTyCon  mutableByteArrayPrimTyConName 1 PtrRep
420 byteArrayPrimTyCon        = pcPrimTyCon0 byteArrayPrimTyConName          PtrRep
421
422 mkArrayPrimTy :: Type -> Type
423 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
424 byteArrayPrimTy :: Type
425 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
426 mkMutableArrayPrimTy :: Type -> Type -> Type
427 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
428 mkMutableByteArrayPrimTy :: Type -> Type
429 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
430 \end{code}
431
432 %************************************************************************
433 %*                                                                      *
434 \subsection[TysPrim-mut-var]{The mutable variable type}
435 %*                                                                      *
436 %************************************************************************
437
438 \begin{code}
439 mutVarPrimTyCon :: TyCon
440 mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName 2 PtrRep
441
442 mkMutVarPrimTy :: Type -> Type -> Type
443 mkMutVarPrimTy s elt        = mkTyConApp mutVarPrimTyCon [s, elt]
444 \end{code}
445
446 %************************************************************************
447 %*                                                                      *
448 \subsection[TysPrim-synch-var]{The synchronizing variable type}
449 %*                                                                      *
450 %************************************************************************
451
452 \begin{code}
453 mVarPrimTyCon :: TyCon
454 mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName 2 PtrRep
455
456 mkMVarPrimTy :: Type -> Type -> Type
457 mkMVarPrimTy s elt          = mkTyConApp mVarPrimTyCon [s, elt]
458 \end{code}
459
460 %************************************************************************
461 %*                                                                      *
462 \subsection[TysPrim-stm-var]{The transactional variable type}
463 %*                                                                      *
464 %************************************************************************
465
466 \begin{code}
467 tVarPrimTyCon :: TyCon
468 tVarPrimTyCon = pcPrimTyCon tVarPrimTyConName 2 PtrRep
469
470 mkTVarPrimTy :: Type -> Type -> Type
471 mkTVarPrimTy s elt = mkTyConApp tVarPrimTyCon [s, elt]
472 \end{code}
473
474 %************************************************************************
475 %*                                                                      *
476 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
477 %*                                                                      *
478 %************************************************************************
479
480 \begin{code}
481 stablePtrPrimTyCon :: TyCon
482 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName 1 AddrRep
483
484 mkStablePtrPrimTy :: Type -> Type
485 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
486 \end{code}
487
488 %************************************************************************
489 %*                                                                      *
490 \subsection[TysPrim-stable-names]{The stable-name type}
491 %*                                                                      *
492 %************************************************************************
493
494 \begin{code}
495 stableNamePrimTyCon :: TyCon
496 stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName 1 PtrRep
497
498 mkStableNamePrimTy :: Type -> Type
499 mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty]
500 \end{code}
501
502 %************************************************************************
503 %*                                                                      *
504 \subsection[TysPrim-BCOs]{The ``bytecode object'' type}
505 %*                                                                      *
506 %************************************************************************
507
508 \begin{code}
509 bcoPrimTy    :: Type
510 bcoPrimTy    = mkTyConTy bcoPrimTyCon
511 bcoPrimTyCon :: TyCon
512 bcoPrimTyCon = pcPrimTyCon0 bcoPrimTyConName PtrRep
513 \end{code}
514   
515 %************************************************************************
516 %*                                                                      *
517 \subsection[TysPrim-Weak]{The ``weak pointer'' type}
518 %*                                                                      *
519 %************************************************************************
520
521 \begin{code}
522 weakPrimTyCon :: TyCon
523 weakPrimTyCon = pcPrimTyCon weakPrimTyConName 1 PtrRep
524
525 mkWeakPrimTy :: Type -> Type
526 mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v]
527 \end{code}
528
529 %************************************************************************
530 %*                                                                      *
531 \subsection[TysPrim-thread-ids]{The ``thread id'' type}
532 %*                                                                      *
533 %************************************************************************
534
535 A thread id is represented by a pointer to the TSO itself, to ensure
536 that they are always unique and we can always find the TSO for a given
537 thread id.  However, this has the unfortunate consequence that a
538 ThreadId# for a given thread is treated as a root by the garbage
539 collector and can keep TSOs around for too long.
540
541 Hence the programmer API for thread manipulation uses a weak pointer
542 to the thread id internally.
543
544 \begin{code}
545 threadIdPrimTy :: Type
546 threadIdPrimTy    = mkTyConTy threadIdPrimTyCon
547 threadIdPrimTyCon :: TyCon
548 threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName PtrRep
549 \end{code}