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