Trim unused imports detected by new unused-import code
[ghc-hetmet.git] / compiler / prelude / TysPrim.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1998
3 %
4 \section[TysPrim]{Wired-in knowledge about primitive types}
5
6 \begin{code}
7 module TysPrim(
8         alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar,
9         alphaTy, betaTy, gammaTy, deltaTy,
10         openAlphaTy, openBetaTy, openAlphaTyVar, openBetaTyVar, openAlphaTyVars,
11
12         primTyCons,
13
14         charPrimTyCon,          charPrimTy,
15         intPrimTyCon,           intPrimTy,
16         wordPrimTyCon,          wordPrimTy,
17         addrPrimTyCon,          addrPrimTy,
18         floatPrimTyCon,         floatPrimTy,
19         doublePrimTyCon,        doublePrimTy,
20
21         statePrimTyCon,         mkStatePrimTy,
22         realWorldTyCon,         realWorldTy, realWorldStatePrimTy,
23
24         arrayPrimTyCon,                 mkArrayPrimTy, 
25         byteArrayPrimTyCon,             byteArrayPrimTy,
26         mutableArrayPrimTyCon,          mkMutableArrayPrimTy,
27         mutableByteArrayPrimTyCon,      mkMutableByteArrayPrimTy,
28         mutVarPrimTyCon,                mkMutVarPrimTy,
29
30         mVarPrimTyCon,                  mkMVarPrimTy,   
31         tVarPrimTyCon,                  mkTVarPrimTy,
32         stablePtrPrimTyCon,             mkStablePtrPrimTy,
33         stableNamePrimTyCon,            mkStableNamePrimTy,
34         bcoPrimTyCon,                   bcoPrimTy,
35         weakPrimTyCon,                  mkWeakPrimTy,
36         threadIdPrimTyCon,              threadIdPrimTy,
37         
38         int32PrimTyCon,         int32PrimTy,
39         word32PrimTyCon,        word32PrimTy,
40
41         int64PrimTyCon,         int64PrimTy,
42         word64PrimTyCon,        word64PrimTy,
43
44         anyPrimTyCon, anyPrimTy, anyPrimTyCon1, mkAnyPrimTyCon
45   ) where
46
47 #include "HsVersions.h"
48
49 import Var              ( TyVar, mkTyVar )
50 import Name             ( Name, BuiltInSyntax(..), mkInternalName, mkWiredInName )
51 import OccName          ( mkTyVarOccFS, mkTcOccFS )
52 import TyCon            ( TyCon, mkPrimTyCon, mkLiftedPrimTyCon )
53 import Type
54 import SrcLoc
55 import Unique           ( mkAlphaTyVarUnique, pprUnique )
56 import PrelNames
57 import StaticFlags
58 import FastString
59 import Outputable
60
61 import Char             ( ord, chr )
62 \end{code}
63
64 %************************************************************************
65 %*                                                                      *
66 \subsection{Primitive type constructors}
67 %*                                                                      *
68 %************************************************************************
69
70 \begin{code}
71 primTyCons :: [TyCon]
72 primTyCons 
73   = [ addrPrimTyCon
74     , arrayPrimTyCon
75     , byteArrayPrimTyCon
76     , charPrimTyCon
77     , doublePrimTyCon
78     , floatPrimTyCon
79     , intPrimTyCon
80     , int32PrimTyCon
81     , int64PrimTyCon
82     , bcoPrimTyCon
83     , weakPrimTyCon
84     , mutableArrayPrimTyCon
85     , mutableByteArrayPrimTyCon
86     , mVarPrimTyCon
87     , tVarPrimTyCon
88     , mutVarPrimTyCon
89     , realWorldTyCon
90     , stablePtrPrimTyCon
91     , stableNamePrimTyCon
92     , statePrimTyCon
93     , threadIdPrimTyCon
94     , wordPrimTyCon
95     , word32PrimTyCon
96     , word64PrimTyCon
97     , anyPrimTyCon, anyPrimTyCon1
98     ]
99
100 mkPrimTc :: FastString -> Unique -> TyCon -> Name
101 mkPrimTc fs unique tycon
102   = mkWiredInName gHC_PRIM (mkTcOccFS fs) 
103                   unique
104                   (ATyCon tycon)        -- Relevant TyCon
105                   UserSyntax            -- None are built-in syntax
106
107 charPrimTyConName, intPrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, realWorldTyConName, arrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName, anyPrimTyConName, anyPrimTyCon1Name :: Name
108 charPrimTyConName             = mkPrimTc (fsLit "Char#") charPrimTyConKey charPrimTyCon
109 intPrimTyConName              = mkPrimTc (fsLit "Int#") intPrimTyConKey  intPrimTyCon
110 int32PrimTyConName            = mkPrimTc (fsLit "Int32#") int32PrimTyConKey int32PrimTyCon
111 int64PrimTyConName            = mkPrimTc (fsLit "Int64#") int64PrimTyConKey int64PrimTyCon
112 wordPrimTyConName             = mkPrimTc (fsLit "Word#") wordPrimTyConKey wordPrimTyCon
113 word32PrimTyConName           = mkPrimTc (fsLit "Word32#") word32PrimTyConKey word32PrimTyCon
114 word64PrimTyConName           = mkPrimTc (fsLit "Word64#") word64PrimTyConKey word64PrimTyCon
115 addrPrimTyConName             = mkPrimTc (fsLit "Addr#") addrPrimTyConKey addrPrimTyCon
116 floatPrimTyConName            = mkPrimTc (fsLit "Float#") floatPrimTyConKey floatPrimTyCon
117 doublePrimTyConName           = mkPrimTc (fsLit "Double#") doublePrimTyConKey doublePrimTyCon
118 statePrimTyConName            = mkPrimTc (fsLit "State#") statePrimTyConKey statePrimTyCon
119 realWorldTyConName            = mkPrimTc (fsLit "RealWorld") realWorldTyConKey realWorldTyCon
120 arrayPrimTyConName            = mkPrimTc (fsLit "Array#") arrayPrimTyConKey arrayPrimTyCon
121 byteArrayPrimTyConName        = mkPrimTc (fsLit "ByteArray#") byteArrayPrimTyConKey byteArrayPrimTyCon
122 mutableArrayPrimTyConName     = mkPrimTc (fsLit "MutableArray#") mutableArrayPrimTyConKey mutableArrayPrimTyCon
123 mutableByteArrayPrimTyConName = mkPrimTc (fsLit "MutableByteArray#") mutableByteArrayPrimTyConKey mutableByteArrayPrimTyCon
124 mutVarPrimTyConName           = mkPrimTc (fsLit "MutVar#") mutVarPrimTyConKey mutVarPrimTyCon
125 mVarPrimTyConName             = mkPrimTc (fsLit "MVar#") mVarPrimTyConKey mVarPrimTyCon
126 tVarPrimTyConName             = mkPrimTc (fsLit "TVar#") tVarPrimTyConKey tVarPrimTyCon
127 stablePtrPrimTyConName        = mkPrimTc (fsLit "StablePtr#") stablePtrPrimTyConKey stablePtrPrimTyCon
128 stableNamePrimTyConName       = mkPrimTc (fsLit "StableName#") stableNamePrimTyConKey stableNamePrimTyCon
129 bcoPrimTyConName              = mkPrimTc (fsLit "BCO#") bcoPrimTyConKey bcoPrimTyCon
130 weakPrimTyConName             = mkPrimTc (fsLit "Weak#") weakPrimTyConKey weakPrimTyCon
131 threadIdPrimTyConName         = mkPrimTc (fsLit "ThreadId#") threadIdPrimTyConKey threadIdPrimTyCon
132 anyPrimTyConName              = mkPrimTc (fsLit "Any") anyPrimTyConKey anyPrimTyCon
133 anyPrimTyCon1Name             = mkPrimTc (fsLit "Any1") anyPrimTyCon1Key anyPrimTyCon
134 \end{code}
135
136 %************************************************************************
137 %*                                                                      *
138 \subsection{Support code}
139 %*                                                                      *
140 %************************************************************************
141
142 alphaTyVars is a list of type variables for use in templates: 
143         ["a", "b", ..., "z", "t1", "t2", ... ]
144
145 \begin{code}
146 tyVarList :: Kind -> [TyVar]
147 tyVarList kind = [ mkTyVar (mkInternalName (mkAlphaTyVarUnique u) 
148                                 (mkTyVarOccFS (mkFastString name))
149                                 noSrcSpan) kind
150                  | u <- [2..],
151                    let name | c <= 'z'  = [c]
152                             | otherwise = 't':show u
153                             where c = chr (u-2 + ord 'a')
154                  ]
155
156 alphaTyVars :: [TyVar]
157 alphaTyVars = tyVarList liftedTypeKind
158
159 betaTyVars :: [TyVar]
160 betaTyVars = tail alphaTyVars
161
162 alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar :: TyVar
163 (alphaTyVar:betaTyVar:gammaTyVar:deltaTyVar:_) = alphaTyVars
164
165 alphaTys :: [Type]
166 alphaTys = mkTyVarTys alphaTyVars
167 alphaTy, betaTy, gammaTy, deltaTy :: Type
168 (alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys
169
170         -- openAlphaTyVar is prepared to be instantiated
171         -- to a lifted or unlifted type variable.  It's used for the 
172         -- result type for "error", so that we can have (error Int# "Help")
173 openAlphaTyVars :: [TyVar]
174 openAlphaTyVar, openBetaTyVar :: TyVar
175 openAlphaTyVars@(openAlphaTyVar:openBetaTyVar:_) = tyVarList openTypeKind
176
177 openAlphaTy, openBetaTy :: Type
178 openAlphaTy = mkTyVarTy openAlphaTyVar
179 openBetaTy   = mkTyVarTy openBetaTyVar
180 \end{code}
181
182
183 %************************************************************************
184 %*                                                                      *
185 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
186 %*                                                                      *
187 %************************************************************************
188
189 \begin{code}
190 -- only used herein
191 pcPrimTyCon :: Name -> Int -> PrimRep -> TyCon
192 pcPrimTyCon name arity rep
193   = mkPrimTyCon name kind arity rep
194   where
195     kind        = mkArrowKinds (replicate arity liftedTypeKind) result_kind
196     result_kind = unliftedTypeKind
197
198 pcPrimTyCon0 :: Name -> PrimRep -> TyCon
199 pcPrimTyCon0 name rep
200   = mkPrimTyCon name result_kind 0 rep
201   where
202     result_kind = unliftedTypeKind
203
204 charPrimTy :: Type
205 charPrimTy      = mkTyConTy charPrimTyCon
206 charPrimTyCon :: TyCon
207 charPrimTyCon   = pcPrimTyCon0 charPrimTyConName WordRep
208
209 intPrimTy :: Type
210 intPrimTy       = mkTyConTy intPrimTyCon
211 intPrimTyCon :: TyCon
212 intPrimTyCon    = pcPrimTyCon0 intPrimTyConName IntRep
213
214 int32PrimTy :: Type
215 int32PrimTy     = mkTyConTy int32PrimTyCon
216 int32PrimTyCon :: TyCon
217 int32PrimTyCon  = pcPrimTyCon0 int32PrimTyConName IntRep
218
219 int64PrimTy :: Type
220 int64PrimTy     = mkTyConTy int64PrimTyCon
221 int64PrimTyCon :: TyCon
222 int64PrimTyCon  = pcPrimTyCon0 int64PrimTyConName Int64Rep
223
224 wordPrimTy :: Type
225 wordPrimTy      = mkTyConTy wordPrimTyCon
226 wordPrimTyCon :: TyCon
227 wordPrimTyCon   = pcPrimTyCon0 wordPrimTyConName WordRep
228
229 word32PrimTy :: Type
230 word32PrimTy    = mkTyConTy word32PrimTyCon
231 word32PrimTyCon :: TyCon
232 word32PrimTyCon = pcPrimTyCon0 word32PrimTyConName WordRep
233
234 word64PrimTy :: Type
235 word64PrimTy    = mkTyConTy word64PrimTyCon
236 word64PrimTyCon :: TyCon
237 word64PrimTyCon = pcPrimTyCon0 word64PrimTyConName Word64Rep
238
239 addrPrimTy :: Type
240 addrPrimTy      = mkTyConTy addrPrimTyCon
241 addrPrimTyCon :: TyCon
242 addrPrimTyCon   = pcPrimTyCon0 addrPrimTyConName AddrRep
243
244 floatPrimTy     :: Type
245 floatPrimTy     = mkTyConTy floatPrimTyCon
246 floatPrimTyCon :: TyCon
247 floatPrimTyCon  = pcPrimTyCon0 floatPrimTyConName FloatRep
248
249 doublePrimTy :: Type
250 doublePrimTy    = mkTyConTy doublePrimTyCon
251 doublePrimTyCon :: TyCon
252 doublePrimTyCon = pcPrimTyCon0 doublePrimTyConName DoubleRep
253 \end{code}
254
255
256 %************************************************************************
257 %*                                                                      *
258 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
259 %*                                                                      *
260 %************************************************************************
261
262 State# is the primitive, unlifted type of states.  It has one type parameter,
263 thus
264         State# RealWorld
265 or
266         State# s
267
268 where s is a type variable. The only purpose of the type parameter is to
269 keep different state threads separate.  It is represented by nothing at all.
270
271 \begin{code}
272 mkStatePrimTy :: Type -> Type
273 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
274 statePrimTyCon :: TyCon
275 statePrimTyCon   = pcPrimTyCon statePrimTyConName 1 VoidRep
276 \end{code}
277
278 RealWorld is deeply magical.  It is *primitive*, but it is not
279 *unlifted* (hence ptrArg).  We never manipulate values of type
280 RealWorld; it's only used in the type system, to parameterise State#.
281
282 \begin{code}
283 realWorldTyCon :: TyCon
284 realWorldTyCon = mkLiftedPrimTyCon realWorldTyConName liftedTypeKind 0 PtrRep
285 realWorldTy :: Type
286 realWorldTy          = mkTyConTy realWorldTyCon
287 realWorldStatePrimTy :: Type
288 realWorldStatePrimTy = mkStatePrimTy realWorldTy        -- State# RealWorld
289 \end{code}
290
291 Note: the ``state-pairing'' types are not truly primitive, so they are
292 defined in \tr{TysWiredIn.lhs}, not here.
293
294
295 %************************************************************************
296 %*                                                                      *
297                 Any
298 %*                                                                      *
299 %************************************************************************
300
301 The type constructor Any is type to which you can unsafely coerce any
302 lifted type, and back. 
303
304   * It is lifted, and hence represented by a pointer
305
306   * It does not claim to be a *data* type, and that's important for
307     the code generator, because the code gen may *enter* a data value
308     but never enters a function value.  
309
310 It's also used to instantiate un-constrained type variables after type
311 checking.  For example
312         length Any []
313 Annoyingly, we sometimes need Anys of other kinds, such as (*->*) etc.
314 This is a bit like tuples.   We define a couple of useful ones here,
315 and make others up on the fly.  If any of these others end up being exported
316 into interface files, we'll get a crash; at least until we add interface-file
317 syntax to support them.
318
319 \begin{code}
320 anyPrimTy :: Type
321 anyPrimTy = mkTyConApp anyPrimTyCon []
322
323 anyPrimTyCon :: TyCon   -- Kind *
324 anyPrimTyCon = mkLiftedPrimTyCon anyPrimTyConName liftedTypeKind 0 PtrRep
325
326 anyPrimTyCon1 :: TyCon  -- Kind *->*
327 anyPrimTyCon1 = mkLiftedPrimTyCon anyPrimTyCon1Name kind 0 PtrRep
328   where
329     kind = mkArrowKind liftedTypeKind liftedTypeKind
330                                   
331 mkAnyPrimTyCon :: Unique -> Kind -> TyCon
332 -- Grotesque hack alert: the client gives the unique; so equality won't work
333 mkAnyPrimTyCon unique kind 
334   = WARN( opt_PprStyle_Debug, ptext (sLit "Urk! Inventing strangely-kinded Any TyCon:") <+> ppr unique <+> ppr kind )
335         -- See Note [Strangely-kinded void TyCons] in TcHsSyn
336     tycon
337   where
338      name  = mkPrimTc (mkFastString ("Any" ++ showSDoc (pprUnique unique))) unique tycon
339      tycon = mkLiftedPrimTyCon name kind 0 PtrRep
340 \end{code}
341
342
343 %************************************************************************
344 %*                                                                      *
345 \subsection[TysPrim-arrays]{The primitive array types}
346 %*                                                                      *
347 %************************************************************************
348
349 \begin{code}
350 arrayPrimTyCon, mutableArrayPrimTyCon, mutableByteArrayPrimTyCon,
351     byteArrayPrimTyCon :: TyCon
352 arrayPrimTyCon            = pcPrimTyCon  arrayPrimTyConName            1 PtrRep
353 mutableArrayPrimTyCon     = pcPrimTyCon  mutableArrayPrimTyConName     2 PtrRep
354 mutableByteArrayPrimTyCon = pcPrimTyCon  mutableByteArrayPrimTyConName 1 PtrRep
355 byteArrayPrimTyCon        = pcPrimTyCon0 byteArrayPrimTyConName          PtrRep
356
357 mkArrayPrimTy :: Type -> Type
358 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
359 byteArrayPrimTy :: Type
360 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
361 mkMutableArrayPrimTy :: Type -> Type -> Type
362 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
363 mkMutableByteArrayPrimTy :: Type -> Type
364 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
365 \end{code}
366
367 %************************************************************************
368 %*                                                                      *
369 \subsection[TysPrim-mut-var]{The mutable variable type}
370 %*                                                                      *
371 %************************************************************************
372
373 \begin{code}
374 mutVarPrimTyCon :: TyCon
375 mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName 2 PtrRep
376
377 mkMutVarPrimTy :: Type -> Type -> Type
378 mkMutVarPrimTy s elt        = mkTyConApp mutVarPrimTyCon [s, elt]
379 \end{code}
380
381 %************************************************************************
382 %*                                                                      *
383 \subsection[TysPrim-synch-var]{The synchronizing variable type}
384 %*                                                                      *
385 %************************************************************************
386
387 \begin{code}
388 mVarPrimTyCon :: TyCon
389 mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName 2 PtrRep
390
391 mkMVarPrimTy :: Type -> Type -> Type
392 mkMVarPrimTy s elt          = mkTyConApp mVarPrimTyCon [s, elt]
393 \end{code}
394
395 %************************************************************************
396 %*                                                                      *
397 \subsection[TysPrim-stm-var]{The transactional variable type}
398 %*                                                                      *
399 %************************************************************************
400
401 \begin{code}
402 tVarPrimTyCon :: TyCon
403 tVarPrimTyCon = pcPrimTyCon tVarPrimTyConName 2 PtrRep
404
405 mkTVarPrimTy :: Type -> Type -> Type
406 mkTVarPrimTy s elt = mkTyConApp tVarPrimTyCon [s, elt]
407 \end{code}
408
409 %************************************************************************
410 %*                                                                      *
411 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
412 %*                                                                      *
413 %************************************************************************
414
415 \begin{code}
416 stablePtrPrimTyCon :: TyCon
417 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName 1 AddrRep
418
419 mkStablePtrPrimTy :: Type -> Type
420 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
421 \end{code}
422
423 %************************************************************************
424 %*                                                                      *
425 \subsection[TysPrim-stable-names]{The stable-name type}
426 %*                                                                      *
427 %************************************************************************
428
429 \begin{code}
430 stableNamePrimTyCon :: TyCon
431 stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName 1 PtrRep
432
433 mkStableNamePrimTy :: Type -> Type
434 mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty]
435 \end{code}
436
437 %************************************************************************
438 %*                                                                      *
439 \subsection[TysPrim-BCOs]{The ``bytecode object'' type}
440 %*                                                                      *
441 %************************************************************************
442
443 \begin{code}
444 bcoPrimTy    :: Type
445 bcoPrimTy    = mkTyConTy bcoPrimTyCon
446 bcoPrimTyCon :: TyCon
447 bcoPrimTyCon = pcPrimTyCon0 bcoPrimTyConName PtrRep
448 \end{code}
449   
450 %************************************************************************
451 %*                                                                      *
452 \subsection[TysPrim-Weak]{The ``weak pointer'' type}
453 %*                                                                      *
454 %************************************************************************
455
456 \begin{code}
457 weakPrimTyCon :: TyCon
458 weakPrimTyCon = pcPrimTyCon weakPrimTyConName 1 PtrRep
459
460 mkWeakPrimTy :: Type -> Type
461 mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v]
462 \end{code}
463
464 %************************************************************************
465 %*                                                                      *
466 \subsection[TysPrim-thread-ids]{The ``thread id'' type}
467 %*                                                                      *
468 %************************************************************************
469
470 A thread id is represented by a pointer to the TSO itself, to ensure
471 that they are always unique and we can always find the TSO for a given
472 thread id.  However, this has the unfortunate consequence that a
473 ThreadId# for a given thread is treated as a root by the garbage
474 collector and can keep TSOs around for too long.
475
476 Hence the programmer API for thread manipulation uses a weak pointer
477 to the thread id internally.
478
479 \begin{code}
480 threadIdPrimTy :: Type
481 threadIdPrimTy    = mkTyConTy threadIdPrimTyCon
482 threadIdPrimTyCon :: TyCon
483 threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName PtrRep
484 \end{code}