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