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