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