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