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