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