Tidy up AnyTyCon stuff
[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, 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, 
237   - both wrt each other, because their strings differ
238
239   - and wrt any other Name, because Names get uniques with 
240     various 'char' tags, but the OccName of Any will 
241     get a Unique built with mkTcOccUnique, which has a particular 'char' 
242     tag; see Unique.mkTcOccUnique!
243
244 Note [Strangely-kinded void TyCons]
245 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
246 See Trac #959 for more examples
247
248 When the type checker finds a type variable with no binding, which
249 means it can be instantiated with an arbitrary type, it usually
250 instantiates it to Void.  Eg.
251
252         length []
253 ===>
254         length Any (Nil Any)
255
256 But in really obscure programs, the type variable might have a kind
257 other than *, so we need to invent a suitably-kinded type.
258
259 This commit uses
260         Any for kind *
261         Any(*->*) for kind *->*
262         etc
263
264 \begin{code}
265 anyTyConName :: Name
266 anyTyConName = mkPrimTc (fsLit "Any") anyTyConKey anyTyCon
267
268 anyTyCon :: TyCon
269 anyTyCon = mkLiftedPrimTyCon anyTyConName liftedTypeKind 0 PtrRep
270
271 anyTypeOfKind :: Kind -> Type
272 anyTypeOfKind kind = mkTyConApp (anyTyConOfKind kind) []
273
274 anyTyConOfKind :: Kind -> TyCon
275 -- Map all superkinds of liftedTypeKind to liftedTypeKind
276 anyTyConOfKind kind 
277   | liftedTypeKind `isSubKind` kind = anyTyCon
278   | otherwise                       = tycon
279   where
280           -- Derive the name from the kind, thus:
281           --     Any(*->*), Any(*->*->*)
282           -- These are names that can't be written by the user,
283           -- and are not allocated in the global name cache
284     str = "Any" ++ showSDoc (pprParendKind kind)
285
286     occ   = mkTcOcc str
287     uniq  = getUnique occ  -- See Note [Uniques of Any]
288     name  = mkWiredInName gHC_PRIM occ uniq (ATyCon tycon) UserSyntax
289     tycon = mkAnyTyCon name kind 
290 \end{code}
291
292
293 %************************************************************************
294 %*                                                                      *
295 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
296 %*                                                                      *
297 %************************************************************************
298
299 \begin{code}
300 -- only used herein
301 pcPrimTyCon :: Name -> Int -> PrimRep -> TyCon
302 pcPrimTyCon name arity rep
303   = mkPrimTyCon name kind arity rep
304   where
305     kind        = mkArrowKinds (replicate arity liftedTypeKind) result_kind
306     result_kind = unliftedTypeKind
307
308 pcPrimTyCon0 :: Name -> PrimRep -> TyCon
309 pcPrimTyCon0 name rep
310   = mkPrimTyCon name result_kind 0 rep
311   where
312     result_kind = unliftedTypeKind
313
314 charPrimTy :: Type
315 charPrimTy      = mkTyConTy charPrimTyCon
316 charPrimTyCon :: TyCon
317 charPrimTyCon   = pcPrimTyCon0 charPrimTyConName WordRep
318
319 intPrimTy :: Type
320 intPrimTy       = mkTyConTy intPrimTyCon
321 intPrimTyCon :: TyCon
322 intPrimTyCon    = pcPrimTyCon0 intPrimTyConName IntRep
323
324 int32PrimTy :: Type
325 int32PrimTy     = mkTyConTy int32PrimTyCon
326 int32PrimTyCon :: TyCon
327 int32PrimTyCon  = pcPrimTyCon0 int32PrimTyConName IntRep
328
329 int64PrimTy :: Type
330 int64PrimTy     = mkTyConTy int64PrimTyCon
331 int64PrimTyCon :: TyCon
332 int64PrimTyCon  = pcPrimTyCon0 int64PrimTyConName Int64Rep
333
334 wordPrimTy :: Type
335 wordPrimTy      = mkTyConTy wordPrimTyCon
336 wordPrimTyCon :: TyCon
337 wordPrimTyCon   = pcPrimTyCon0 wordPrimTyConName WordRep
338
339 word32PrimTy :: Type
340 word32PrimTy    = mkTyConTy word32PrimTyCon
341 word32PrimTyCon :: TyCon
342 word32PrimTyCon = pcPrimTyCon0 word32PrimTyConName WordRep
343
344 word64PrimTy :: Type
345 word64PrimTy    = mkTyConTy word64PrimTyCon
346 word64PrimTyCon :: TyCon
347 word64PrimTyCon = pcPrimTyCon0 word64PrimTyConName Word64Rep
348
349 addrPrimTy :: Type
350 addrPrimTy      = mkTyConTy addrPrimTyCon
351 addrPrimTyCon :: TyCon
352 addrPrimTyCon   = pcPrimTyCon0 addrPrimTyConName AddrRep
353
354 floatPrimTy     :: Type
355 floatPrimTy     = mkTyConTy floatPrimTyCon
356 floatPrimTyCon :: TyCon
357 floatPrimTyCon  = pcPrimTyCon0 floatPrimTyConName FloatRep
358
359 doublePrimTy :: Type
360 doublePrimTy    = mkTyConTy doublePrimTyCon
361 doublePrimTyCon :: TyCon
362 doublePrimTyCon = pcPrimTyCon0 doublePrimTyConName DoubleRep
363 \end{code}
364
365
366 %************************************************************************
367 %*                                                                      *
368 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
369 %*                                                                      *
370 %************************************************************************
371
372 State# is the primitive, unlifted type of states.  It has one type parameter,
373 thus
374         State# RealWorld
375 or
376         State# s
377
378 where s is a type variable. The only purpose of the type parameter is to
379 keep different state threads separate.  It is represented by nothing at all.
380
381 \begin{code}
382 mkStatePrimTy :: Type -> Type
383 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
384 statePrimTyCon :: TyCon
385 statePrimTyCon   = pcPrimTyCon statePrimTyConName 1 VoidRep
386 \end{code}
387
388 RealWorld is deeply magical.  It is *primitive*, but it is not
389 *unlifted* (hence ptrArg).  We never manipulate values of type
390 RealWorld; it's only used in the type system, to parameterise State#.
391
392 \begin{code}
393 realWorldTyCon :: TyCon
394 realWorldTyCon = mkLiftedPrimTyCon realWorldTyConName liftedTypeKind 0 PtrRep
395 realWorldTy :: Type
396 realWorldTy          = mkTyConTy realWorldTyCon
397 realWorldStatePrimTy :: Type
398 realWorldStatePrimTy = mkStatePrimTy realWorldTy        -- State# RealWorld
399 \end{code}
400
401 Note: the ``state-pairing'' types are not truly primitive, so they are
402 defined in \tr{TysWiredIn.lhs}, not here.
403
404
405 %************************************************************************
406 %*                                                                      *
407 \subsection[TysPrim-arrays]{The primitive array types}
408 %*                                                                      *
409 %************************************************************************
410
411 \begin{code}
412 arrayPrimTyCon, mutableArrayPrimTyCon, mutableByteArrayPrimTyCon,
413     byteArrayPrimTyCon :: TyCon
414 arrayPrimTyCon            = pcPrimTyCon  arrayPrimTyConName            1 PtrRep
415 mutableArrayPrimTyCon     = pcPrimTyCon  mutableArrayPrimTyConName     2 PtrRep
416 mutableByteArrayPrimTyCon = pcPrimTyCon  mutableByteArrayPrimTyConName 1 PtrRep
417 byteArrayPrimTyCon        = pcPrimTyCon0 byteArrayPrimTyConName          PtrRep
418
419 mkArrayPrimTy :: Type -> Type
420 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
421 byteArrayPrimTy :: Type
422 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
423 mkMutableArrayPrimTy :: Type -> Type -> Type
424 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
425 mkMutableByteArrayPrimTy :: Type -> Type
426 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
427 \end{code}
428
429 %************************************************************************
430 %*                                                                      *
431 \subsection[TysPrim-mut-var]{The mutable variable type}
432 %*                                                                      *
433 %************************************************************************
434
435 \begin{code}
436 mutVarPrimTyCon :: TyCon
437 mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName 2 PtrRep
438
439 mkMutVarPrimTy :: Type -> Type -> Type
440 mkMutVarPrimTy s elt        = mkTyConApp mutVarPrimTyCon [s, elt]
441 \end{code}
442
443 %************************************************************************
444 %*                                                                      *
445 \subsection[TysPrim-synch-var]{The synchronizing variable type}
446 %*                                                                      *
447 %************************************************************************
448
449 \begin{code}
450 mVarPrimTyCon :: TyCon
451 mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName 2 PtrRep
452
453 mkMVarPrimTy :: Type -> Type -> Type
454 mkMVarPrimTy s elt          = mkTyConApp mVarPrimTyCon [s, elt]
455 \end{code}
456
457 %************************************************************************
458 %*                                                                      *
459 \subsection[TysPrim-stm-var]{The transactional variable type}
460 %*                                                                      *
461 %************************************************************************
462
463 \begin{code}
464 tVarPrimTyCon :: TyCon
465 tVarPrimTyCon = pcPrimTyCon tVarPrimTyConName 2 PtrRep
466
467 mkTVarPrimTy :: Type -> Type -> Type
468 mkTVarPrimTy s elt = mkTyConApp tVarPrimTyCon [s, elt]
469 \end{code}
470
471 %************************************************************************
472 %*                                                                      *
473 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
474 %*                                                                      *
475 %************************************************************************
476
477 \begin{code}
478 stablePtrPrimTyCon :: TyCon
479 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName 1 AddrRep
480
481 mkStablePtrPrimTy :: Type -> Type
482 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
483 \end{code}
484
485 %************************************************************************
486 %*                                                                      *
487 \subsection[TysPrim-stable-names]{The stable-name type}
488 %*                                                                      *
489 %************************************************************************
490
491 \begin{code}
492 stableNamePrimTyCon :: TyCon
493 stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName 1 PtrRep
494
495 mkStableNamePrimTy :: Type -> Type
496 mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty]
497 \end{code}
498
499 %************************************************************************
500 %*                                                                      *
501 \subsection[TysPrim-BCOs]{The ``bytecode object'' type}
502 %*                                                                      *
503 %************************************************************************
504
505 \begin{code}
506 bcoPrimTy    :: Type
507 bcoPrimTy    = mkTyConTy bcoPrimTyCon
508 bcoPrimTyCon :: TyCon
509 bcoPrimTyCon = pcPrimTyCon0 bcoPrimTyConName PtrRep
510 \end{code}
511   
512 %************************************************************************
513 %*                                                                      *
514 \subsection[TysPrim-Weak]{The ``weak pointer'' type}
515 %*                                                                      *
516 %************************************************************************
517
518 \begin{code}
519 weakPrimTyCon :: TyCon
520 weakPrimTyCon = pcPrimTyCon weakPrimTyConName 1 PtrRep
521
522 mkWeakPrimTy :: Type -> Type
523 mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v]
524 \end{code}
525
526 %************************************************************************
527 %*                                                                      *
528 \subsection[TysPrim-thread-ids]{The ``thread id'' type}
529 %*                                                                      *
530 %************************************************************************
531
532 A thread id is represented by a pointer to the TSO itself, to ensure
533 that they are always unique and we can always find the TSO for a given
534 thread id.  However, this has the unfortunate consequence that a
535 ThreadId# for a given thread is treated as a root by the garbage
536 collector and can keep TSOs around for too long.
537
538 Hence the programmer API for thread manipulation uses a weak pointer
539 to the thread id internally.
540
541 \begin{code}
542 threadIdPrimTy :: Type
543 threadIdPrimTy    = mkTyConTy threadIdPrimTyCon
544 threadIdPrimTyCon :: TyCon
545 threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName PtrRep
546 \end{code}