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