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