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