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