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