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