[project @ 2002-07-31 12:17:35 by simonmar]
[ghc-hetmet.git] / ghc / 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 This module tracks the ``state interface'' document, ``GHC prelude:
7 types and operations.''
8
9 \begin{code}
10 module TysPrim(
11         alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar,
12         alphaTy, betaTy, gammaTy, deltaTy,
13         openAlphaTy, openAlphaTyVar, openAlphaTyVars,
14
15         primTyCons,
16
17         charPrimTyCon,          charPrimTy,
18         intPrimTyCon,           intPrimTy,
19         wordPrimTyCon,          wordPrimTy,
20         addrPrimTyCon,          addrPrimTy,
21         floatPrimTyCon,         floatPrimTy,
22         doublePrimTyCon,        doublePrimTy,
23
24         statePrimTyCon,         mkStatePrimTy,
25         realWorldTyCon,         realWorldTy, realWorldStatePrimTy,
26
27         arrayPrimTyCon,                 mkArrayPrimTy, 
28         byteArrayPrimTyCon,             byteArrayPrimTy,
29         mutableArrayPrimTyCon,          mkMutableArrayPrimTy,
30         mutableByteArrayPrimTyCon,      mkMutableByteArrayPrimTy,
31         mutVarPrimTyCon,                mkMutVarPrimTy,
32
33         mVarPrimTyCon,                  mkMVarPrimTy,   
34         stablePtrPrimTyCon,             mkStablePtrPrimTy,
35         stableNamePrimTyCon,            mkStableNamePrimTy,
36         bcoPrimTyCon,                   bcoPrimTy,
37         weakPrimTyCon,                  mkWeakPrimTy,
38         foreignObjPrimTyCon,            foreignObjPrimTy,
39         threadIdPrimTyCon,              threadIdPrimTy,
40         
41         int32PrimTyCon,         int32PrimTy,
42         word32PrimTyCon,        word32PrimTy,
43
44         int64PrimTyCon,         int64PrimTy,
45         word64PrimTyCon,        word64PrimTy
46   ) where
47
48 #include "HsVersions.h"
49
50 import Var              ( TyVar, mkTyVar )
51 import Name             ( Name, mkInternalName )
52 import OccName          ( mkVarOcc )
53 import PrimRep          ( PrimRep(..) )
54 import TyCon            ( TyCon, ArgVrcs, mkPrimTyCon, mkLiftedPrimTyCon )
55 import Type             ( mkTyConApp, mkTyConTy, mkTyVarTys, mkTyVarTy,
56                           unliftedTypeKind, liftedTypeKind, openTypeKind, 
57                           Kind, mkArrowKinds
58                         )
59 import SrcLoc           ( noSrcLoc )
60 import Unique           ( mkAlphaTyVarUnique )
61 import PrelNames
62 import FastString       ( mkFastString )
63 import Outputable
64
65 import Char             ( ord, chr )
66 \end{code}
67
68 %************************************************************************
69 %*                                                                      *
70 \subsection{Primitive type constructors}
71 %*                                                                      *
72 %************************************************************************
73
74 \begin{code}
75 primTyCons :: [TyCon]
76 primTyCons 
77   = [ addrPrimTyCon
78     , arrayPrimTyCon
79     , byteArrayPrimTyCon
80     , charPrimTyCon
81     , doublePrimTyCon
82     , floatPrimTyCon
83     , intPrimTyCon
84     , int32PrimTyCon
85     , int64PrimTyCon
86     , foreignObjPrimTyCon
87     , bcoPrimTyCon
88     , weakPrimTyCon
89     , mutableArrayPrimTyCon
90     , mutableByteArrayPrimTyCon
91     , mVarPrimTyCon
92     , mutVarPrimTyCon
93     , realWorldTyCon
94     , stablePtrPrimTyCon
95     , stableNamePrimTyCon
96     , statePrimTyCon
97     , threadIdPrimTyCon
98     , wordPrimTyCon
99     , word32PrimTyCon
100     , word64PrimTyCon
101     ]
102 \end{code}
103
104
105 %************************************************************************
106 %*                                                                      *
107 \subsection{Support code}
108 %*                                                                      *
109 %************************************************************************
110
111 alphaTyVars is a list of type variables for use in templates: 
112         ["a", "b", ..., "z", "t1", "t2", ... ]
113
114 \begin{code}
115 tyVarList :: Kind -> [TyVar]
116 tyVarList kind = [ mkTyVar (mkInternalName (mkAlphaTyVarUnique u) 
117                                 (mkVarOcc (mkFastString name))
118                                 noSrcLoc) kind
119                  | u <- [2..],
120                    let name | c <= 'z'  = [c]
121                             | otherwise = 't':show u
122                             where c = chr (u-2 + ord 'a')
123                  ]
124
125 alphaTyVars :: [TyVar]
126 alphaTyVars = tyVarList liftedTypeKind
127
128 betaTyVars = tail alphaTyVars
129
130 alphaTyVar, betaTyVar, gammaTyVar :: TyVar
131 (alphaTyVar:betaTyVar:gammaTyVar:deltaTyVar:_) = alphaTyVars
132
133 alphaTys = mkTyVarTys alphaTyVars
134 (alphaTy:betaTy:gammaTy:deltaTy:_) = alphaTys
135
136         -- openAlphaTyVar is prepared to be instantiated
137         -- to a lifted or unlifted type variable.  It's used for the 
138         -- result type for "error", so that we can have (error Int# "Help")
139 openAlphaTyVars :: [TyVar]
140 openAlphaTyVars@(openAlphaTyVar:_) = tyVarList openTypeKind
141
142 openAlphaTy = mkTyVarTy openAlphaTyVar
143
144 vrcPos,vrcZero :: (Bool,Bool)
145 vrcPos  = (True,False)
146 vrcZero = (False,False)
147
148 vrcsP,vrcsZ,vrcsZP :: ArgVrcs
149 vrcsP  = [vrcPos]
150 vrcsZ  = [vrcZero]
151 vrcsZP = [vrcZero,vrcPos]
152 \end{code}
153
154
155 %************************************************************************
156 %*                                                                      *
157 \subsection[TysPrim-basic]{Basic primitive types (@Char#@, @Int#@, etc.)}
158 %*                                                                      *
159 %************************************************************************
160
161 \begin{code}
162 -- only used herein
163 pcPrimTyCon :: Name -> ArgVrcs -> PrimRep -> TyCon
164 pcPrimTyCon name arg_vrcs rep
165   = mkPrimTyCon name kind arity arg_vrcs rep
166   where
167     arity       = length arg_vrcs
168     kind        = mkArrowKinds (replicate arity liftedTypeKind) result_kind
169     result_kind = unliftedTypeKind -- all primitive types are unlifted
170
171 pcPrimTyCon0 :: Name -> PrimRep -> TyCon
172 pcPrimTyCon0 name rep
173   = mkPrimTyCon name result_kind 0 [] rep
174   where
175     result_kind = unliftedTypeKind -- all primitive types are unlifted
176
177 charPrimTy      = mkTyConTy charPrimTyCon
178 charPrimTyCon   = pcPrimTyCon0 charPrimTyConName CharRep
179
180 intPrimTy       = mkTyConTy intPrimTyCon
181 intPrimTyCon    = pcPrimTyCon0 intPrimTyConName IntRep
182
183 int32PrimTy     = mkTyConTy int32PrimTyCon
184 int32PrimTyCon  = pcPrimTyCon0 int32PrimTyConName Int32Rep
185
186 int64PrimTy     = mkTyConTy int64PrimTyCon
187 int64PrimTyCon  = pcPrimTyCon0 int64PrimTyConName Int64Rep
188
189 wordPrimTy      = mkTyConTy wordPrimTyCon
190 wordPrimTyCon   = pcPrimTyCon0 wordPrimTyConName WordRep
191
192 word32PrimTy    = mkTyConTy word32PrimTyCon
193 word32PrimTyCon = pcPrimTyCon0 word32PrimTyConName Word32Rep
194
195 word64PrimTy    = mkTyConTy word64PrimTyCon
196 word64PrimTyCon = pcPrimTyCon0 word64PrimTyConName Word64Rep
197
198 addrPrimTy      = mkTyConTy addrPrimTyCon
199 addrPrimTyCon   = pcPrimTyCon0 addrPrimTyConName AddrRep
200
201 floatPrimTy     = mkTyConTy floatPrimTyCon
202 floatPrimTyCon  = pcPrimTyCon0 floatPrimTyConName FloatRep
203
204 doublePrimTy    = mkTyConTy doublePrimTyCon
205 doublePrimTyCon = pcPrimTyCon0 doublePrimTyConName DoubleRep
206 \end{code}
207
208
209 %************************************************************************
210 %*                                                                      *
211 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
212 %*                                                                      *
213 %************************************************************************
214
215 State# is the primitive, unlifted type of states.  It has one type parameter,
216 thus
217         State# RealWorld
218 or
219         State# s
220
221 where s is a type variable. The only purpose of the type parameter is to
222 keep different state threads separate.  It is represented by nothing at all.
223
224 \begin{code}
225 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
226 statePrimTyCon   = pcPrimTyCon statePrimTyConName vrcsZ VoidRep
227 \end{code}
228
229 RealWorld is deeply magical.  It is *primitive*, but it is not
230 *unlifted* (hence PrimPtrRep).  We never manipulate values of type
231 RealWorld; it's only used in the type system, to parameterise State#.
232
233 \begin{code}
234 realWorldTyCon = mkLiftedPrimTyCon realWorldTyConName liftedTypeKind 0 [] PrimPtrRep
235 realWorldTy          = mkTyConTy realWorldTyCon
236 realWorldStatePrimTy = mkStatePrimTy realWorldTy        -- State# RealWorld
237 \end{code}
238
239 Note: the ``state-pairing'' types are not truly primitive, so they are
240 defined in \tr{TysWiredIn.lhs}, not here.
241
242
243 %************************************************************************
244 %*                                                                      *
245 \subsection[TysPrim-arrays]{The primitive array types}
246 %*                                                                      *
247 %************************************************************************
248
249 \begin{code}
250 arrayPrimTyCon            = pcPrimTyCon  arrayPrimTyConName            vrcsP  ArrayRep
251 mutableArrayPrimTyCon     = pcPrimTyCon  mutableArrayPrimTyConName     vrcsZP ArrayRep
252 mutableByteArrayPrimTyCon = pcPrimTyCon  mutableByteArrayPrimTyConName vrcsZ  ByteArrayRep
253 byteArrayPrimTyCon        = pcPrimTyCon0 byteArrayPrimTyConName               ByteArrayRep
254
255 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
256 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
257 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
258 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
259 \end{code}
260
261 %************************************************************************
262 %*                                                                      *
263 \subsection[TysPrim-mut-var]{The mutable variable type}
264 %*                                                                      *
265 %************************************************************************
266
267 \begin{code}
268 mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName vrcsZP PrimPtrRep
269
270 mkMutVarPrimTy s elt        = mkTyConApp mutVarPrimTyCon [s, elt]
271 \end{code}
272
273 %************************************************************************
274 %*                                                                      *
275 \subsection[TysPrim-synch-var]{The synchronizing variable type}
276 %*                                                                      *
277 %************************************************************************
278
279 \begin{code}
280 mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName vrcsZP PrimPtrRep
281
282 mkMVarPrimTy s elt          = mkTyConApp mVarPrimTyCon [s, elt]
283 \end{code}
284
285 %************************************************************************
286 %*                                                                      *
287 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
288 %*                                                                      *
289 %************************************************************************
290
291 \begin{code}
292 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName vrcsP StablePtrRep
293
294 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
295 \end{code}
296
297 %************************************************************************
298 %*                                                                      *
299 \subsection[TysPrim-stable-names]{The stable-name type}
300 %*                                                                      *
301 %************************************************************************
302
303 \begin{code}
304 stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName vrcsP StableNameRep
305
306 mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty]
307 \end{code}
308
309 %************************************************************************
310 %*                                                                      *
311 \subsection[TysPrim-foreign-objs]{The ``foreign object'' type}
312 %*                                                                      *
313 %************************************************************************
314
315 A Foreign Object is just a boxed, unlifted, Addr#.  They're needed
316 because finalisers (weak pointers) can't watch Addr#s, they can only
317 watch heap-resident objects.  
318
319 We can't use a lifted Addr# (such as Addr) because race conditions
320 could bite us.  For example, if the program deconstructed the Addr
321 before passing its contents to a ccall, and a weak pointer was
322 watching the Addr, the weak pointer might deduce that the Addr was
323 dead before it really was.
324
325 \begin{code}
326 foreignObjPrimTy    = mkTyConTy foreignObjPrimTyCon
327 foreignObjPrimTyCon = pcPrimTyCon0 foreignObjPrimTyConName ForeignObjRep
328 \end{code}
329   
330 %************************************************************************
331 %*                                                                      *
332 \subsection[TysPrim-BCOs]{The ``bytecode object'' type}
333 %*                                                                      *
334 %************************************************************************
335
336 \begin{code}
337 bcoPrimTy    = mkTyConTy bcoPrimTyCon
338 bcoPrimTyCon = pcPrimTyCon0 bcoPrimTyConName BCORep
339 \end{code}
340   
341 %************************************************************************
342 %*                                                                      *
343 \subsection[TysPrim-Weak]{The ``weak pointer'' type}
344 %*                                                                      *
345 %************************************************************************
346
347 \begin{code}
348 weakPrimTyCon = pcPrimTyCon weakPrimTyConName vrcsP WeakPtrRep
349
350 mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v]
351 \end{code}
352
353 %************************************************************************
354 %*                                                                      *
355 \subsection[TysPrim-thread-ids]{The ``thread id'' type}
356 %*                                                                      *
357 %************************************************************************
358
359 A thread id is represented by a pointer to the TSO itself, to ensure
360 that they are always unique and we can always find the TSO for a given
361 thread id.  However, this has the unfortunate consequence that a
362 ThreadId# for a given thread is treated as a root by the garbage
363 collector and can keep TSOs around for too long.
364
365 Hence the programmer API for thread manipulation uses a weak pointer
366 to the thread id internally.
367
368 \begin{code}
369 threadIdPrimTy    = mkTyConTy threadIdPrimTyCon
370 threadIdPrimTyCon = pcPrimTyCon0 threadIdPrimTyConName ThreadIdRep
371 \end{code}