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