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