[project @ 2000-11-07 15:21:38 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                           unboxedTypeKind, boxedTypeKind, 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 boxedTypeKind
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 boxed or unboxed 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 boxedTypeKind)) result_kind
154     result_kind | isFollowableRep rep = boxedTypeKind   -- Represented by a GC-ish ptr
155                 | otherwise           = unboxedTypeKind -- Represented by a non-ptr
156
157 charPrimTy      = mkTyConTy charPrimTyCon
158 charPrimTyCon   = pcPrimTyCon charPrimTyConName 0 [] CharRep
159
160 intPrimTy       = mkTyConTy intPrimTyCon
161 intPrimTyCon    = pcPrimTyCon intPrimTyConName 0 [] IntRep
162
163 int64PrimTy     = mkTyConTy int64PrimTyCon
164 int64PrimTyCon  = pcPrimTyCon int64PrimTyConName 0 [] Int64Rep
165
166 wordPrimTy      = mkTyConTy wordPrimTyCon
167 wordPrimTyCon   = pcPrimTyCon wordPrimTyConName 0 [] WordRep
168
169 word64PrimTy    = mkTyConTy word64PrimTyCon
170 word64PrimTyCon = pcPrimTyCon word64PrimTyConName 0 [] Word64Rep
171
172 addrPrimTy      = mkTyConTy addrPrimTyCon
173 addrPrimTyCon   = pcPrimTyCon addrPrimTyConName 0 [] AddrRep
174
175 floatPrimTy     = mkTyConTy floatPrimTyCon
176 floatPrimTyCon  = pcPrimTyCon floatPrimTyConName 0 [] FloatRep
177
178 doublePrimTy    = mkTyConTy doublePrimTyCon
179 doublePrimTyCon = pcPrimTyCon doublePrimTyConName 0 [] DoubleRep
180 \end{code}
181
182
183 %************************************************************************
184 %*                                                                      *
185 \subsection[TysPrim-state]{The @State#@ type (and @_RealWorld@ types)}
186 %*                                                                      *
187 %************************************************************************
188
189 State# is the primitive, unboxed type of states.  It has one type parameter,
190 thus
191         State# RealWorld
192 or
193         State# s
194
195 where s is a type variable. The only purpose of the type parameter is to
196 keep different state threads separate.  It is represented by nothing at all.
197
198 \begin{code}
199 mkStatePrimTy ty = mkTyConApp statePrimTyCon [ty]
200 statePrimTyCon   = pcPrimTyCon statePrimTyConName 1 vrcsZ VoidRep
201 \end{code}
202
203 @_RealWorld@ is deeply magical.  It {\em is primitive}, but it
204 {\em is not unboxed} (hence PtrRep).
205 We never manipulate values of type RealWorld; it's only used in the type
206 system, to parameterise State#.
207
208 \begin{code}
209 realWorldTy          = mkTyConTy realWorldTyCon
210 realWorldTyCon       = pcPrimTyCon realWorldTyConName 0 [] PrimPtrRep
211 realWorldStatePrimTy = mkStatePrimTy realWorldTy        -- State# RealWorld
212 \end{code}
213
214 Note: the ``state-pairing'' types are not truly primitive, so they are
215 defined in \tr{TysWiredIn.lhs}, not here.
216
217
218 %************************************************************************
219 %*                                                                      *
220 \subsection[TysPrim-arrays]{The primitive array types}
221 %*                                                                      *
222 %************************************************************************
223
224 \begin{code}
225 arrayPrimTyCon            = pcPrimTyCon arrayPrimTyConName            1 vrcsP  ArrayRep
226 byteArrayPrimTyCon        = pcPrimTyCon byteArrayPrimTyConName        0 []     ByteArrayRep
227 mutableArrayPrimTyCon     = pcPrimTyCon mutableArrayPrimTyConName     2 vrcsZP ArrayRep
228 mutableByteArrayPrimTyCon = pcPrimTyCon mutableByteArrayPrimTyConName 1 vrcsZ  ByteArrayRep
229
230 mkArrayPrimTy elt           = mkTyConApp arrayPrimTyCon [elt]
231 byteArrayPrimTy             = mkTyConTy byteArrayPrimTyCon
232 mkMutableArrayPrimTy s elt  = mkTyConApp mutableArrayPrimTyCon [s, elt]
233 mkMutableByteArrayPrimTy s  = mkTyConApp mutableByteArrayPrimTyCon [s]
234 \end{code}
235
236 %************************************************************************
237 %*                                                                      *
238 \subsection[TysPrim-mut-var]{The mutable variable type}
239 %*                                                                      *
240 %************************************************************************
241
242 \begin{code}
243 mutVarPrimTyCon = pcPrimTyCon mutVarPrimTyConName 2 vrcsZP PrimPtrRep
244
245 mkMutVarPrimTy s elt        = mkTyConApp mutVarPrimTyCon [s, elt]
246 \end{code}
247
248 %************************************************************************
249 %*                                                                      *
250 \subsection[TysPrim-synch-var]{The synchronizing variable type}
251 %*                                                                      *
252 %************************************************************************
253
254 \begin{code}
255 mVarPrimTyCon = pcPrimTyCon mVarPrimTyConName 2 vrcsZP PrimPtrRep
256
257 mkMVarPrimTy s elt          = mkTyConApp mVarPrimTyCon [s, elt]
258 \end{code}
259
260 %************************************************************************
261 %*                                                                      *
262 \subsection[TysPrim-stable-ptrs]{The stable-pointer type}
263 %*                                                                      *
264 %************************************************************************
265
266 \begin{code}
267 stablePtrPrimTyCon = pcPrimTyCon stablePtrPrimTyConName 1 vrcsP StablePtrRep
268
269 mkStablePtrPrimTy ty = mkTyConApp stablePtrPrimTyCon [ty]
270 \end{code}
271
272 %************************************************************************
273 %*                                                                      *
274 \subsection[TysPrim-stable-names]{The stable-name type}
275 %*                                                                      *
276 %************************************************************************
277
278 \begin{code}
279 stableNamePrimTyCon = pcPrimTyCon stableNamePrimTyConName 1 vrcsP StableNameRep
280
281 mkStableNamePrimTy ty = mkTyConApp stableNamePrimTyCon [ty]
282 \end{code}
283
284 %************************************************************************
285 %*                                                                      *
286 \subsection[TysPrim-foreign-objs]{The ``foreign object'' type}
287 %*                                                                      *
288 %************************************************************************
289
290 A Foreign Object is just a boxed, unlifted, Addr#.  They're needed
291 because finalisers (weak pointers) can't watch Addr#s, they can only
292 watch heap-resident objects.  
293
294 We can't use a lifted Addr# (such as Addr) because race conditions
295 could bite us.  For example, if the program deconstructed the Addr
296 before passing its contents to a ccall, and a weak pointer was
297 watching the Addr, the weak pointer might deduce that the Addr was
298 dead before it really was.
299
300 \begin{code}
301 foreignObjPrimTy    = mkTyConTy foreignObjPrimTyCon
302 foreignObjPrimTyCon = pcPrimTyCon foreignObjPrimTyConName 0 [] ForeignObjRep
303 \end{code}
304   
305 %************************************************************************
306 %*                                                                      *
307 \subsection[TysPrim-BCOs]{The ``bytecode object'' type}
308 %*                                                                      *
309 %************************************************************************
310
311 \begin{code}
312 bcoPrimTy    = mkTyConTy bcoPrimTyCon
313 bcoPrimTyCon = pcPrimTyCon bcoPrimTyConName 0 [] BCORep
314 \end{code}
315   
316 %************************************************************************
317 %*                                                                      *
318 \subsection[TysPrim-Weak]{The ``weak pointer'' type}
319 %*                                                                      *
320 %************************************************************************
321
322 \begin{code}
323 weakPrimTyCon = pcPrimTyCon weakPrimTyConName 1 vrcsP WeakPtrRep
324
325 mkWeakPrimTy v = mkTyConApp weakPrimTyCon [v]
326 \end{code}
327
328 %************************************************************************
329 %*                                                                      *
330 \subsection[TysPrim-thread-ids]{The ``thread id'' type}
331 %*                                                                      *
332 %************************************************************************
333
334 A thread id is represented by a pointer to the TSO itself, to ensure
335 that they are always unique and we can always find the TSO for a given
336 thread id.  However, this has the unfortunate consequence that a
337 ThreadId# for a given thread is treated as a root by the garbage
338 collector and can keep TSOs around for too long.
339
340 Hence the programmer API for thread manipulation uses a weak pointer
341 to the thread id internally.
342
343 \begin{code}
344 threadIdPrimTy    = mkTyConTy threadIdPrimTyCon
345 threadIdPrimTyCon = pcPrimTyCon threadIdPrimTyConName 0 [] ThreadIdRep
346 \end{code}
347
348 %************************************************************************
349 %*                                                                      *
350 \subsection[TysPrim-PrimRep]{Making types from PrimReps}
351 %*                                                                      *
352 %************************************************************************
353
354 Each of the primitive types from this module is equivalent to a
355 PrimRep (see PrimRep.lhs).  The following function returns the
356 primitive TyCon for a given PrimRep.
357
358 \begin{code}
359 primRepTyCon CharRep   = charPrimTyCon
360 primRepTyCon Int8Rep   = charPrimTyCon
361 primRepTyCon IntRep    = intPrimTyCon
362 primRepTyCon WordRep   = wordPrimTyCon
363 primRepTyCon Int64Rep  = int64PrimTyCon
364 primRepTyCon Word64Rep = word64PrimTyCon
365 primRepTyCon AddrRep   = addrPrimTyCon
366 primRepTyCon FloatRep  = floatPrimTyCon
367 primRepTyCon DoubleRep = doublePrimTyCon
368 primRepTyCon StablePtrRep  = stablePtrPrimTyCon
369 primRepTyCon ForeignObjRep = foreignObjPrimTyCon
370 primRepTyCon WeakPtrRep = weakPrimTyCon
371 primRepTyCon other     = pprPanic "primRepTyCon" (ppr other)
372 \end{code}