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