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