[project @ 1996-06-05 06:44:31 by partain]
[ghc-hetmet.git] / ghc / compiler / prelude / TysWiredIn.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1994-1995
3 %
4 \section[TysWiredIn]{Wired-in knowledge about {\em non-primitive} types}
5
6 This module is about types that can be defined in Haskell, but which
7 must be wired into the compiler nonetheless.
8
9 This module tracks the ``state interface'' document, ``GHC prelude:
10 types and operations.''
11
12 \begin{code}
13 #include "HsVersions.h"
14
15 module TysWiredIn (
16         addrDataCon,
17         addrTy,
18         addrTyCon,
19         boolTy,
20         boolTyCon,
21         charDataCon,
22         charTy,
23         charTyCon,
24         consDataCon,
25         doubleDataCon,
26         doubleTy,
27         doubleTyCon,
28         falseDataCon,
29         floatDataCon,
30         floatTy,
31         floatTyCon,
32         getStatePairingConInfo,
33         intDataCon,
34         intTy,
35         intTyCon,
36         integerTy,
37         integerTyCon,
38         integerDataCon,
39         liftDataCon,
40         liftTyCon,
41         listTyCon,
42         foreignObjTyCon,
43         mkLiftTy,
44         mkListTy,
45         mkPrimIoTy,
46         mkStateTransformerTy,
47         mkTupleTy,
48         nilDataCon,
49         primIoTyCon,
50         realWorldStateTy,
51         return2GMPsTyCon,
52         returnIntAndGMPTyCon,
53         stTyCon,
54         stablePtrTyCon,
55         stateAndAddrPrimTyCon,
56         stateAndArrayPrimTyCon,
57         stateAndByteArrayPrimTyCon,
58         stateAndCharPrimTyCon,
59         stateAndDoublePrimTyCon,
60         stateAndFloatPrimTyCon,
61         stateAndIntPrimTyCon,
62         stateAndForeignObjPrimTyCon,
63         stateAndMutableArrayPrimTyCon,
64         stateAndMutableByteArrayPrimTyCon,
65         stateAndPtrPrimTyCon,
66         stateAndStablePtrPrimTyCon,
67         stateAndSynchVarPrimTyCon,
68         stateAndWordPrimTyCon,
69         stateDataCon,
70         stateTyCon,
71         stringTy,
72         trueDataCon,
73         unitTy,
74         voidTy, voidTyCon,
75         wordDataCon,
76         wordTy,
77         wordTyCon
78
79     ) where
80
81 --ToDo:rm
82 --import Pretty
83 --import Util
84 --import PprType
85 --import PprStyle
86 --import Kind
87
88 IMP_Ubiq()
89 IMPORT_DELOOPER(TyLoop)         ( mkDataCon, StrictnessMark(..) )
90
91 -- friends:
92 import PrelMods
93 import TysPrim
94
95 -- others:
96 import SpecEnv          ( SpecEnv(..) )
97 import Kind             ( mkBoxedTypeKind, mkArrowKind )
98 import Name             ( mkBuiltinName )
99 import SrcLoc           ( mkBuiltinSrcLoc )
100 import TyCon            ( mkDataTyCon, mkTupleTyCon, mkSynTyCon,
101                           NewOrData(..), TyCon
102                         )
103 import Type             ( mkTyConTy, applyTyCon, mkSigmaTy,
104                           mkFunTys, maybeAppTyCon,
105                           GenType(..), ThetaType(..), TauType(..) )
106 import TyVar            ( tyVarKind, alphaTyVar, betaTyVar )
107 import Unique
108 import Util             ( assoc, panic )
109
110 nullSpecEnv =  error "TysWiredIn:nullSpecEnv =  "
111 addOneToSpecEnv =  error "TysWiredIn:addOneToSpecEnv =  "
112 pc_gen_specs = error "TysWiredIn:pc_gen_specs  "
113 mkSpecInfo = error "TysWiredIn:SpecInfo"
114
115 alpha_tyvar       = [alphaTyVar]
116 alpha_ty          = [alphaTy]
117 alpha_beta_tyvars = [alphaTyVar, betaTyVar]
118
119 pcDataTyCon, pcNewTyCon
120         :: Unique{-TyConKey-} -> Module -> FAST_STRING
121         -> [TyVar] -> [Id] -> TyCon
122
123 pcDataTyCon = pc_tycon DataType
124 pcNewTyCon  = pc_tycon NewType
125
126 pc_tycon new_or_data key mod str tyvars cons
127   = mkDataTyCon (mkBuiltinName key mod str) tycon_kind 
128                 tyvars [{-no context-}] cons [{-no derivings-}]
129                 new_or_data
130   where
131     tycon_kind = foldr (mkArrowKind . tyVarKind) mkBoxedTypeKind tyvars
132
133 pcDataCon :: Unique{-DataConKey-} -> Module -> FAST_STRING
134           -> [TyVar] -> ThetaType -> [TauType] -> TyCon -> SpecEnv -> Id
135 pcDataCon key mod str tyvars context arg_tys tycon specenv
136   = mkDataCon (mkBuiltinName key mod str)
137         [ NotMarkedStrict | a <- arg_tys ]
138         [ {- no labelled fields -} ]
139         tyvars context arg_tys tycon
140         -- specenv
141
142 pcGenerateDataSpecs :: Type -> SpecEnv
143 pcGenerateDataSpecs ty
144   = pc_gen_specs False err err err ty
145   where
146     err = panic "PrelUtils:GenerateDataSpecs"
147 \end{code}
148
149 %************************************************************************
150 %*                                                                      *
151 \subsection[TysWiredIn-boxed-prim]{The ``boxed primitive'' types (@Char@, @Int@, etc)}
152 %*                                                                      *
153 %************************************************************************
154
155 \begin{code}
156 -- The Void type is represented as a data type with no constructors
157 -- It's a built in type (i.e. there's no way to define it in Haskell
158 --      the nearest would be
159 --
160 --              data Void =             -- No constructors!
161 --
162 -- It's boxed; there is only one value of this
163 -- type, namely "void", whose semantics is just bottom.
164 voidTy = mkTyConTy voidTyCon
165
166 voidTyCon = pcDataTyCon voidTyConKey pRELUDE_BUILTIN SLIT("Void") [] []
167 \end{code}
168
169 \begin{code}
170 charTy = mkTyConTy charTyCon
171
172 charTyCon = pcDataTyCon charTyConKey pRELUDE_BUILTIN SLIT("Char") [] [charDataCon]
173 charDataCon = pcDataCon charDataConKey pRELUDE_BUILTIN SLIT("C#") [] [] [charPrimTy] charTyCon nullSpecEnv
174 \end{code}
175
176 \begin{code}
177 intTy = mkTyConTy intTyCon 
178
179 intTyCon = pcDataTyCon intTyConKey pRELUDE_BUILTIN SLIT("Int") [] [intDataCon]
180 intDataCon = pcDataCon intDataConKey pRELUDE_BUILTIN SLIT("I#") [] [] [intPrimTy] intTyCon nullSpecEnv
181 \end{code}
182
183 \begin{code}
184 wordTy = mkTyConTy wordTyCon
185
186 wordTyCon = pcDataTyCon wordTyConKey pRELUDE_BUILTIN SLIT("_Word") [] [wordDataCon]
187 wordDataCon = pcDataCon wordDataConKey pRELUDE_BUILTIN SLIT("W#") [] [] [wordPrimTy] wordTyCon nullSpecEnv
188 \end{code}
189
190 \begin{code}
191 addrTy = mkTyConTy addrTyCon
192
193 addrTyCon = pcDataTyCon addrTyConKey pRELUDE_BUILTIN SLIT("_Addr") [] [addrDataCon]
194 addrDataCon = pcDataCon addrDataConKey pRELUDE_BUILTIN SLIT("A#") [] [] [addrPrimTy] addrTyCon nullSpecEnv
195 \end{code}
196
197 \begin{code}
198 floatTy = mkTyConTy floatTyCon
199
200 floatTyCon = pcDataTyCon floatTyConKey pRELUDE_BUILTIN SLIT("Float") [] [floatDataCon]
201 floatDataCon = pcDataCon floatDataConKey pRELUDE_BUILTIN SLIT("F#") [] [] [floatPrimTy] floatTyCon nullSpecEnv
202 \end{code}
203
204 \begin{code}
205 doubleTy = mkTyConTy doubleTyCon
206
207 doubleTyCon = pcDataTyCon doubleTyConKey pRELUDE_BUILTIN SLIT("Double") [] [doubleDataCon]
208 doubleDataCon = pcDataCon doubleDataConKey pRELUDE_BUILTIN SLIT("D#") [] [] [doublePrimTy] doubleTyCon nullSpecEnv
209 \end{code}
210
211 \begin{code}
212 mkStateTy ty     = applyTyCon stateTyCon [ty]
213 realWorldStateTy = mkStateTy realWorldTy -- a common use
214
215 stateTyCon = pcDataTyCon stateTyConKey pRELUDE_BUILTIN SLIT("_State") alpha_tyvar [stateDataCon]
216 stateDataCon
217   = pcDataCon stateDataConKey pRELUDE_BUILTIN SLIT("S#")
218         alpha_tyvar [] [mkStatePrimTy alphaTy] stateTyCon nullSpecEnv
219 \end{code}
220
221 \begin{code}
222 stablePtrTyCon
223   = pcDataTyCon stablePtrTyConKey gLASGOW_MISC SLIT("_StablePtr")
224         alpha_tyvar [stablePtrDataCon]
225   where
226     stablePtrDataCon
227       = pcDataCon stablePtrDataConKey gLASGOW_MISC SLIT("_StablePtr")
228             alpha_tyvar [] [mkStablePtrPrimTy alphaTy] stablePtrTyCon nullSpecEnv
229 \end{code}
230
231 \begin{code}
232 foreignObjTyCon
233   = pcDataTyCon foreignObjTyConKey gLASGOW_MISC SLIT("_ForeignObj")
234         [] [foreignObjDataCon]
235   where
236     foreignObjDataCon
237       = pcDataCon foreignObjDataConKey gLASGOW_MISC SLIT("_ForeignObj")
238             [] [] [foreignObjPrimTy] foreignObjTyCon nullSpecEnv
239 \end{code}
240
241 %************************************************************************
242 %*                                                                      *
243 \subsection[TysWiredIn-Integer]{@Integer@ and its related ``pairing'' types}
244 %*                                                                      *
245 %************************************************************************
246
247 @Integer@ and its pals are not really primitive.  @Integer@ itself, first:
248 \begin{code}
249 integerTy :: GenType t u
250 integerTy    = mkTyConTy integerTyCon
251
252 integerTyCon = pcDataTyCon integerTyConKey pRELUDE_BUILTIN SLIT("Integer") [] [integerDataCon]
253
254 integerDataCon = pcDataCon integerDataConKey pRELUDE_BUILTIN SLIT("J#")
255                 [] [] [intPrimTy, intPrimTy, byteArrayPrimTy] integerTyCon nullSpecEnv
256 \end{code}
257
258 And the other pairing types:
259 \begin{code}
260 return2GMPsTyCon = pcDataTyCon return2GMPsTyConKey
261         pRELUDE_BUILTIN SLIT("_Return2GMPs") [] [return2GMPsDataCon]
262
263 return2GMPsDataCon
264   = pcDataCon return2GMPsDataConKey pRELUDE_BUILTIN SLIT("_Return2GMPs") [] []
265         [intPrimTy, intPrimTy, byteArrayPrimTy,
266          intPrimTy, intPrimTy, byteArrayPrimTy] return2GMPsTyCon nullSpecEnv
267
268 returnIntAndGMPTyCon = pcDataTyCon returnIntAndGMPTyConKey
269         pRELUDE_BUILTIN SLIT("_ReturnIntAndGMP") [] [returnIntAndGMPDataCon]
270
271 returnIntAndGMPDataCon
272   = pcDataCon returnIntAndGMPDataConKey pRELUDE_BUILTIN SLIT("_ReturnIntAndGMP") [] []
273         [intPrimTy, intPrimTy, intPrimTy, byteArrayPrimTy] returnIntAndGMPTyCon nullSpecEnv
274 \end{code}
275
276 %************************************************************************
277 %*                                                                      *
278 \subsection[TysWiredIn-state-pairing]{``State-pairing'' types}
279 %*                                                                      *
280 %************************************************************************
281
282 These boring types pair a \tr{State#} with another primitive type.
283 They are not really primitive, so they are given here, not in
284 \tr{TysPrim.lhs}.
285
286 We fish one of these \tr{StateAnd<blah>#} things with
287 @getStatePairingConInfo@ (given a little way down).
288
289 \begin{code}
290 stateAndPtrPrimTyCon
291   = pcDataTyCon stateAndPtrPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndPtr#")
292                 alpha_beta_tyvars [stateAndPtrPrimDataCon]
293 stateAndPtrPrimDataCon
294   = pcDataCon stateAndPtrPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndPtr#")
295                 alpha_beta_tyvars [] [mkStatePrimTy alphaTy, betaTy]
296                 stateAndPtrPrimTyCon nullSpecEnv
297
298 stateAndCharPrimTyCon
299   = pcDataTyCon stateAndCharPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndChar#")
300                 alpha_tyvar [stateAndCharPrimDataCon]
301 stateAndCharPrimDataCon
302   = pcDataCon stateAndCharPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndChar#")
303                 alpha_tyvar [] [mkStatePrimTy alphaTy, charPrimTy]
304                 stateAndCharPrimTyCon nullSpecEnv
305
306 stateAndIntPrimTyCon
307   = pcDataTyCon stateAndIntPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndInt#")
308                 alpha_tyvar [stateAndIntPrimDataCon]
309 stateAndIntPrimDataCon
310   = pcDataCon stateAndIntPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndInt#")
311                 alpha_tyvar [] [mkStatePrimTy alphaTy, intPrimTy]
312                 stateAndIntPrimTyCon nullSpecEnv
313
314 stateAndWordPrimTyCon
315   = pcDataTyCon stateAndWordPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndWord#")
316                 alpha_tyvar [stateAndWordPrimDataCon]
317 stateAndWordPrimDataCon
318   = pcDataCon stateAndWordPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndWord#")
319                 alpha_tyvar [] [mkStatePrimTy alphaTy, wordPrimTy]
320                 stateAndWordPrimTyCon nullSpecEnv
321
322 stateAndAddrPrimTyCon
323   = pcDataTyCon stateAndAddrPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndAddr#")
324                 alpha_tyvar [stateAndAddrPrimDataCon]
325 stateAndAddrPrimDataCon
326   = pcDataCon stateAndAddrPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndAddr#")
327                 alpha_tyvar [] [mkStatePrimTy alphaTy, addrPrimTy]
328                 stateAndAddrPrimTyCon nullSpecEnv
329
330 stateAndStablePtrPrimTyCon
331   = pcDataTyCon stateAndStablePtrPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndStablePtr#")
332                 alpha_beta_tyvars [stateAndStablePtrPrimDataCon]
333 stateAndStablePtrPrimDataCon
334   = pcDataCon stateAndStablePtrPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndStablePtr#")
335                 alpha_beta_tyvars []
336                 [mkStatePrimTy alphaTy, applyTyCon stablePtrPrimTyCon [betaTy]]
337                 stateAndStablePtrPrimTyCon nullSpecEnv
338
339 stateAndForeignObjPrimTyCon
340   = pcDataTyCon stateAndForeignObjPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndForeignObj#")
341                 alpha_tyvar [stateAndForeignObjPrimDataCon]
342 stateAndForeignObjPrimDataCon
343   = pcDataCon stateAndForeignObjPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndForeignObj#")
344                 alpha_tyvar []
345                 [mkStatePrimTy alphaTy, applyTyCon foreignObjPrimTyCon []]
346                 stateAndForeignObjPrimTyCon nullSpecEnv
347
348 stateAndFloatPrimTyCon
349   = pcDataTyCon stateAndFloatPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndFloat#")
350                 alpha_tyvar [stateAndFloatPrimDataCon]
351 stateAndFloatPrimDataCon
352   = pcDataCon stateAndFloatPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndFloat#")
353                 alpha_tyvar [] [mkStatePrimTy alphaTy, floatPrimTy]
354                 stateAndFloatPrimTyCon nullSpecEnv
355
356 stateAndDoublePrimTyCon
357   = pcDataTyCon stateAndDoublePrimTyConKey pRELUDE_BUILTIN SLIT("StateAndDouble#")
358                 alpha_tyvar [stateAndDoublePrimDataCon]
359 stateAndDoublePrimDataCon
360   = pcDataCon stateAndDoublePrimDataConKey pRELUDE_BUILTIN SLIT("StateAndDouble#")
361                 alpha_tyvar [] [mkStatePrimTy alphaTy, doublePrimTy]
362                 stateAndDoublePrimTyCon nullSpecEnv
363 \end{code}
364
365 \begin{code}
366 stateAndArrayPrimTyCon
367   = pcDataTyCon stateAndArrayPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndArray#")
368                 alpha_beta_tyvars [stateAndArrayPrimDataCon]
369 stateAndArrayPrimDataCon
370   = pcDataCon stateAndArrayPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndArray#")
371                 alpha_beta_tyvars [] [mkStatePrimTy alphaTy, mkArrayPrimTy betaTy]
372                 stateAndArrayPrimTyCon nullSpecEnv
373
374 stateAndMutableArrayPrimTyCon
375   = pcDataTyCon stateAndMutableArrayPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndMutableArray#")
376                 alpha_beta_tyvars [stateAndMutableArrayPrimDataCon]
377 stateAndMutableArrayPrimDataCon
378   = pcDataCon stateAndMutableArrayPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndMutableArray#")
379                 alpha_beta_tyvars [] [mkStatePrimTy alphaTy, mkMutableArrayPrimTy alphaTy betaTy]
380                 stateAndMutableArrayPrimTyCon nullSpecEnv
381
382 stateAndByteArrayPrimTyCon
383   = pcDataTyCon stateAndByteArrayPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndByteArray#")
384                 alpha_tyvar [stateAndByteArrayPrimDataCon]
385 stateAndByteArrayPrimDataCon
386   = pcDataCon stateAndByteArrayPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndByteArray#")
387                 alpha_tyvar [] [mkStatePrimTy alphaTy, byteArrayPrimTy]
388                 stateAndByteArrayPrimTyCon nullSpecEnv
389
390 stateAndMutableByteArrayPrimTyCon
391   = pcDataTyCon stateAndMutableByteArrayPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndMutableByteArray#")
392                 alpha_tyvar [stateAndMutableByteArrayPrimDataCon]
393 stateAndMutableByteArrayPrimDataCon
394   = pcDataCon stateAndMutableByteArrayPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndMutableByteArray#")
395                 alpha_tyvar [] [mkStatePrimTy alphaTy, applyTyCon mutableByteArrayPrimTyCon alpha_ty]
396                 stateAndMutableByteArrayPrimTyCon nullSpecEnv
397
398 stateAndSynchVarPrimTyCon
399   = pcDataTyCon stateAndSynchVarPrimTyConKey pRELUDE_BUILTIN SLIT("StateAndSynchVar#")
400                 alpha_beta_tyvars [stateAndSynchVarPrimDataCon]
401 stateAndSynchVarPrimDataCon
402   = pcDataCon stateAndSynchVarPrimDataConKey pRELUDE_BUILTIN SLIT("StateAndSynchVar#")
403                 alpha_beta_tyvars [] [mkStatePrimTy alphaTy, mkSynchVarPrimTy alphaTy betaTy]
404                 stateAndSynchVarPrimTyCon nullSpecEnv
405 \end{code}
406
407 The ccall-desugaring mechanism uses this function to figure out how to
408 rebox the result.  It's really a HACK, especially the part about
409 how many types to drop from \tr{tys_applied}.
410
411 \begin{code}
412 getStatePairingConInfo
413         :: Type -- primitive type
414         -> (Id,         -- state pair constructor for prim type
415             Type)       -- type of state pair
416
417 getStatePairingConInfo prim_ty
418   = case (maybeAppTyCon prim_ty) of
419       Nothing -> panic "getStatePairingConInfo:1"
420       Just (prim_tycon, tys_applied) ->
421         let
422             (pair_con, pair_tycon, num_tys) = assoc "getStatePairingConInfo" tbl prim_tycon
423             pair_ty = applyTyCon pair_tycon (realWorldTy : drop num_tys tys_applied)
424         in
425         (pair_con, pair_ty)
426   where
427     tbl = [
428         (charPrimTyCon, (stateAndCharPrimDataCon, stateAndCharPrimTyCon, 0)),
429         (intPrimTyCon, (stateAndIntPrimDataCon, stateAndIntPrimTyCon, 0)),
430         (wordPrimTyCon, (stateAndWordPrimDataCon, stateAndWordPrimTyCon, 0)),
431         (addrPrimTyCon, (stateAndAddrPrimDataCon, stateAndAddrPrimTyCon, 0)),
432         (stablePtrPrimTyCon, (stateAndStablePtrPrimDataCon, stateAndStablePtrPrimTyCon, 0)),
433         (foreignObjPrimTyCon, (stateAndForeignObjPrimDataCon, stateAndForeignObjPrimTyCon, 0)),
434         (floatPrimTyCon, (stateAndFloatPrimDataCon, stateAndFloatPrimTyCon, 0)),
435         (doublePrimTyCon, (stateAndDoublePrimDataCon, stateAndDoublePrimTyCon, 0)),
436         (arrayPrimTyCon, (stateAndArrayPrimDataCon, stateAndArrayPrimTyCon, 0)),
437         (mutableArrayPrimTyCon, (stateAndMutableArrayPrimDataCon, stateAndMutableArrayPrimTyCon, 1)),
438         (byteArrayPrimTyCon, (stateAndByteArrayPrimDataCon, stateAndByteArrayPrimTyCon, 0)),
439         (mutableByteArrayPrimTyCon, (stateAndMutableByteArrayPrimDataCon, stateAndMutableByteArrayPrimTyCon, 1)),
440         (synchVarPrimTyCon, (stateAndSynchVarPrimDataCon, stateAndSynchVarPrimTyCon, 1))
441         -- (PtrPrimTyCon, (stateAndPtrPrimDataCon, stateAndPtrPrimTyCon, 0)),
442         ]
443 \end{code}
444
445 %************************************************************************
446 %*                                                                      *
447 \subsection[TysWiredIn-ST]{The basic @_ST@ state-transformer type}
448 %*                                                                      *
449 %************************************************************************
450
451 This is really just an ordinary synonym, except it is ABSTRACT.
452
453 \begin{code}
454 mkStateTransformerTy s a = applyTyCon stTyCon [s, a]
455
456 stTyCon = pcNewTyCon stTyConKey pRELUDE SLIT("_ST") alpha_beta_tyvars [stDataCon]
457   where
458     ty = mkFunTys [mkStateTy alphaTy] (mkTupleTy 2 [betaTy, mkStateTy alphaTy])
459
460     stDataCon = pcDataCon stDataConKey pRELUDE SLIT("_ST")
461                         alpha_beta_tyvars [] [ty] stTyCon nullSpecEnv
462 \end{code}
463
464 %************************************************************************
465 %*                                                                      *
466 \subsection[TysWiredIn-IO]{The @PrimIO@ and @IO@ monadic-I/O types}
467 %*                                                                      *
468 %************************************************************************
469
470 @PrimIO@ and @IO@ really are just plain synonyms.
471
472 \begin{code}
473 mkPrimIoTy a = applyTyCon primIoTyCon [a]
474
475 primIoTyCon = pcNewTyCon primIoTyConKey pRELUDE SLIT("_PrimIO") alpha_tyvar [primIoDataCon]
476   where
477     ty = mkFunTys [mkStateTy realWorldTy] (mkTupleTy 2 [alphaTy, mkStateTy realWorldTy])
478
479     primIoDataCon = pcDataCon primIoDataConKey pRELUDE SLIT("_PrimIO")
480                         alpha_tyvar [] [ty] primIoTyCon nullSpecEnv
481 \end{code}
482
483 %************************************************************************
484 %*                                                                      *
485 \subsection[TysWiredIn-Bool]{The @Bool@ type}
486 %*                                                                      *
487 %************************************************************************
488
489 An ordinary enumeration type, but deeply wired in.  There are no
490 magical operations on @Bool@ (just the regular Prelude code).
491
492 {\em BEGIN IDLE SPECULATION BY SIMON}
493
494 This is not the only way to encode @Bool@.  A more obvious coding makes
495 @Bool@ just a boxed up version of @Bool#@, like this:
496 \begin{verbatim}
497 type Bool# = Int#
498 data Bool = MkBool Bool#
499 \end{verbatim}
500
501 Unfortunately, this doesn't correspond to what the Report says @Bool@
502 looks like!  Furthermore, we get slightly less efficient code (I
503 think) with this coding. @gtInt@ would look like this:
504
505 \begin{verbatim}
506 gtInt :: Int -> Int -> Bool
507 gtInt x y = case x of I# x# ->
508             case y of I# y# ->
509             case (gtIntPrim x# y#) of
510                 b# -> MkBool b#
511 \end{verbatim}
512
513 Notice that the result of the @gtIntPrim@ comparison has to be turned
514 into an integer (here called @b#@), and returned in a @MkBool@ box.
515
516 The @if@ expression would compile to this:
517 \begin{verbatim}
518 case (gtInt x y) of
519   MkBool b# -> case b# of { 1# -> e1; 0# -> e2 }
520 \end{verbatim}
521
522 I think this code is a little less efficient than the previous code,
523 but I'm not certain.  At all events, corresponding with the Report is
524 important.  The interesting thing is that the language is expressive
525 enough to describe more than one alternative; and that a type doesn't
526 necessarily need to be a straightforwardly boxed version of its
527 primitive counterpart.
528
529 {\em END IDLE SPECULATION BY SIMON}
530
531 \begin{code}
532 boolTy = mkTyConTy boolTyCon
533
534 boolTyCon = pcDataTyCon boolTyConKey pRELUDE SLIT("Bool") [] [falseDataCon, trueDataCon]
535
536 falseDataCon = pcDataCon falseDataConKey pRELUDE SLIT("False") [] [] [] boolTyCon nullSpecEnv
537 trueDataCon  = pcDataCon trueDataConKey  pRELUDE SLIT("True")  [] [] [] boolTyCon nullSpecEnv
538 \end{code}
539
540 %************************************************************************
541 %*                                                                      *
542 \subsection[TysWiredIn-List]{The @List@ type (incl ``build'' magic)}
543 %*                                                                      *
544 %************************************************************************
545
546 Special syntax, deeply wired in, but otherwise an ordinary algebraic
547 data type:
548 \begin{verbatim}
549 data List a = Nil | a : (List a)
550 ToDo: data [] a = [] | a : (List a)
551 ToDo: data () = ()
552       data (,,) a b c = (,,) a b c
553 \end{verbatim}
554
555 \begin{code}
556 mkListTy :: GenType t u -> GenType t u
557 mkListTy ty = applyTyCon listTyCon [ty]
558
559 alphaListTy = mkSigmaTy alpha_tyvar [] (applyTyCon listTyCon alpha_ty)
560
561 listTyCon = pcDataTyCon listTyConKey pRELUDE_BUILTIN SLIT("[]") 
562                         alpha_tyvar [nilDataCon, consDataCon]
563
564 nilDataCon  = pcDataCon nilDataConKey  pRELUDE_BUILTIN SLIT("[]") alpha_tyvar [] [] listTyCon
565                 (pcGenerateDataSpecs alphaListTy)
566 consDataCon = pcDataCon consDataConKey pRELUDE_BUILTIN SLIT(":")
567                 alpha_tyvar [] [alphaTy, applyTyCon listTyCon alpha_ty] listTyCon
568                 (pcGenerateDataSpecs alphaListTy)
569 -- Interesting: polymorphic recursion would help here.
570 -- We can't use (mkListTy alphaTy) in the defn of consDataCon, else mkListTy
571 -- gets the over-specific type (Type -> Type)
572 \end{code}
573
574 %************************************************************************
575 %*                                                                      *
576 \subsection[TysWiredIn-Tuples]{The @Tuple@ types}
577 %*                                                                      *
578 %************************************************************************
579
580 The tuple types are definitely magic, because they form an infinite
581 family.
582
583 \begin{itemize}
584 \item
585 They have a special family of type constructors, of type @TyCon@
586 These contain the tycon arity, but don't require a Unique.
587
588 \item
589 They have a special family of constructors, of type
590 @Id@. Again these contain their arity but don't need a Unique.
591
592 \item
593 There should be a magic way of generating the info tables and
594 entry code for all tuples.
595
596 But at the moment we just compile a Haskell source
597 file\srcloc{lib/prelude/...} containing declarations like:
598 \begin{verbatim}
599 data Tuple0             = Tup0
600 data Tuple2  a b        = Tup2  a b
601 data Tuple3  a b c      = Tup3  a b c
602 data Tuple4  a b c d    = Tup4  a b c d
603 ...
604 \end{verbatim}
605 The print-names associated with the magic @Id@s for tuple constructors
606 ``just happen'' to be the same as those generated by these
607 declarations.
608
609 \item
610 The instance environment should have a magic way to know
611 that each tuple type is an instances of classes @Eq@, @Ix@, @Ord@ and
612 so on. \ToDo{Not implemented yet.}
613
614 \item
615 There should also be a way to generate the appropriate code for each
616 of these instances, but (like the info tables and entry code) it is
617 done by enumeration\srcloc{lib/prelude/InTup?.hs}.
618 \end{itemize}
619
620 \begin{code}
621 mkTupleTy :: Int -> [GenType t u] -> GenType t u
622
623 mkTupleTy arity tys = applyTyCon (mkTupleTyCon arity) tys
624
625 unitTy    = mkTupleTy 0 []
626 \end{code}
627
628 %************************************************************************
629 %*                                                                      *
630 \subsection[TysWiredIn-_Lift]{@_Lift@ type: to support array indexing}
631 %*                                                                      *
632 %************************************************************************
633
634 Again, deeply turgid: \tr{data _Lift a = _Lift a}.
635
636 \begin{code}
637 mkLiftTy ty = applyTyCon liftTyCon [ty]
638
639 {-
640 mkLiftTy ty
641   = mkSigmaTy tvs theta (applyTyCon liftTyCon [tau])
642   where
643     (tvs, theta, tau) = splitSigmaTy ty
644
645 isLiftTy ty
646   = case (maybeAppDataTyConExpandingDicts tau) of
647       Just (tycon, tys, _) -> tycon == liftTyCon
648       Nothing -> False
649   where
650     (tvs, theta, tau) = splitSigmaTy ty
651 -}
652
653
654 alphaLiftTy = mkSigmaTy alpha_tyvar [] (applyTyCon liftTyCon alpha_ty)
655
656 liftTyCon
657   = pcDataTyCon liftTyConKey pRELUDE_BUILTIN SLIT("_Lift") alpha_tyvar [liftDataCon]
658
659 liftDataCon
660   = pcDataCon liftDataConKey pRELUDE_BUILTIN SLIT("_Lift")
661                 alpha_tyvar [] alpha_ty liftTyCon
662                 ((pcGenerateDataSpecs alphaLiftTy) `addOneToSpecEnv`
663                  (mkSpecInfo [Just realWorldStatePrimTy] 0 bottom))
664   where
665     bottom = panic "liftDataCon:State# _RealWorld"
666 \end{code}
667
668
669 %************************************************************************
670 %*                                                                      *
671 \subsection[TysWiredIn-for-convenience]{Types wired in for convenience (e.g., @String@)}
672 %*                                                                      *
673 %************************************************************************
674
675 \begin{code}
676 stringTy = mkListTy charTy
677 \end{code}