merge GHC HEAD
[ghc-hetmet.git] / compiler / prelude / TysWiredIn.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1994-1998
3 %
4 \section[TysWiredIn]{Wired-in knowledge about {\em non-primitive} types}
5
6 \begin{code}
7 -- | This module is about types that can be defined in Haskell, but which
8 --   must be wired into the compiler nonetheless.  C.f module TysPrim
9 module TysWiredIn (
10         -- * All wired in things
11         wiredInTyCons, 
12
13         -- * Bool
14         boolTy, boolTyCon, boolTyCon_RDR, boolTyConName,
15         trueDataCon,  trueDataConId,  true_RDR,
16         falseDataCon, falseDataConId, false_RDR,
17
18         -- * Char
19         charTyCon, charDataCon, charTyCon_RDR,
20         charTy, stringTy, charTyConName,
21
22         -- * Double
23         doubleTyCon, doubleDataCon, doubleTy, doubleTyConName, 
24         
25         -- * Float
26         floatTyCon, floatDataCon, floatTy, floatTyConName,
27
28         -- * Int
29         intTyCon, intDataCon, intTyCon_RDR, intDataCon_RDR, intTyConName,
30         intTy,
31
32         -- * Word
33         wordTyCon, wordDataCon, wordTyConName, wordTy,
34
35         -- * List
36         listTyCon, nilDataCon, consDataCon,
37         listTyCon_RDR, consDataCon_RDR, listTyConName,
38         mkListTy,
39
40         -- * Tuples
41         mkTupleTy, mkBoxedTupleTy,
42         tupleTyCon, tupleCon, 
43         unitTyCon, unitDataCon, unitDataConId, pairTyCon, 
44         unboxedSingletonTyCon, unboxedSingletonDataCon,
45         unboxedPairTyCon, unboxedPairDataCon,
46
47         -- * Unit
48         unitTy,
49
50         -- * Heterogeneous Metaprogramming
51         mkHetMetCodeTypeTy,
52         hetMetCodeTypeTyConName,
53         hetMetCodeTypeTyCon,     isHetMetCodeTypeTyCon,
54         hetMetCodeTypeTyCon_RDR,
55
56         -- * Parallel arrays
57         mkPArrTy,
58         parrTyCon, parrFakeCon, isPArrTyCon, isPArrFakeCon,
59         parrTyCon_RDR, parrTyConName
60     ) where
61
62 #include "HsVersions.h"
63
64 import {-# SOURCE #-} MkId( mkDataConIds )
65
66 -- friends:
67 import PrelNames
68 import TysPrim
69
70 -- others:
71 import Constants        ( mAX_TUPLE_SIZE )
72 import Module           ( Module )
73 import DataCon          ( DataCon, mkDataCon, dataConWorkId, dataConSourceArity )
74 import Var
75 import TyCon
76 import TypeRep
77 import RdrName
78 import Name
79 import BasicTypes       ( Arity, RecFlag(..), Boxity(..), isBoxed, HsBang(..) )
80 import Unique           ( incrUnique, mkTupleTyConUnique,
81                           mkTupleDataConUnique, mkPArrDataConUnique )
82 import Data.Array
83 import FastString
84 import Outputable
85
86 alpha_tyvar :: [TyVar]
87 alpha_tyvar = [alphaTyVar]
88
89 alpha_ty :: [Type]
90 alpha_ty = [alphaTy]
91 \end{code}
92
93
94 %************************************************************************
95 %*                                                                      *
96 \subsection{Wired in type constructors}
97 %*                                                                      *
98 %************************************************************************
99
100 If you change which things are wired in, make sure you change their
101 names in PrelNames, so they use wTcQual, wDataQual, etc
102
103 \begin{code}
104 wiredInTyCons :: [TyCon]        -- Excludes tuples
105 -- This list is used only to define PrelInfo.wiredInThings
106
107 -- It does not need to include kind constructors, because
108 -- all that wiredInThings does is to initialise the Name table,
109 -- and kind constructors don't appear in source code.
110
111 wiredInTyCons = [ unitTyCon     -- Not treated like other tuples, because
112                                 -- it's defined in GHC.Base, and there's only
113                                 -- one of it.  We put it in wiredInTyCons so
114                                 -- that it'll pre-populate the name cache, so
115                                 -- the special case in lookupOrigNameCache 
116                                 -- doesn't need to look out for it
117               , boolTyCon
118               , charTyCon
119               , doubleTyCon
120               , floatTyCon
121               , intTyCon
122               , listTyCon
123               , parrTyCon
124               , hetMetCodeTypeTyCon
125               ]
126 \end{code}
127
128 \begin{code}
129 mkWiredInTyConName :: BuiltInSyntax -> Module -> FastString -> Unique -> TyCon -> Name
130 mkWiredInTyConName built_in modu fs unique tycon
131   = mkWiredInName modu (mkTcOccFS fs) unique
132                   (ATyCon tycon)        -- Relevant TyCon
133                   built_in
134
135 mkWiredInDataConName :: BuiltInSyntax -> Module -> FastString -> Unique -> DataCon -> Name
136 mkWiredInDataConName built_in modu fs unique datacon
137   = mkWiredInName modu (mkDataOccFS fs) unique
138                   (ADataCon datacon)    -- Relevant DataCon
139                   built_in
140
141 charTyConName, charDataConName, intTyConName, intDataConName :: Name
142 charTyConName     = mkWiredInTyConName   UserSyntax gHC_TYPES (fsLit "Char") charTyConKey charTyCon
143 charDataConName   = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "C#") charDataConKey charDataCon
144 intTyConName      = mkWiredInTyConName   UserSyntax gHC_TYPES (fsLit "Int") intTyConKey   intTyCon
145 intDataConName    = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "I#") intDataConKey  intDataCon
146
147 boolTyConName, falseDataConName, trueDataConName :: Name
148 boolTyConName     = mkWiredInTyConName   UserSyntax gHC_TYPES (fsLit "Bool") boolTyConKey boolTyCon
149 falseDataConName  = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "False") falseDataConKey falseDataCon
150 trueDataConName   = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "True")  trueDataConKey  trueDataCon
151
152 listTyConName, nilDataConName, consDataConName :: Name
153 listTyConName     = mkWiredInTyConName   BuiltInSyntax gHC_TYPES (fsLit "[]") listTyConKey listTyCon
154 nilDataConName    = mkWiredInDataConName BuiltInSyntax gHC_TYPES (fsLit "[]") nilDataConKey nilDataCon 
155 consDataConName   = mkWiredInDataConName BuiltInSyntax gHC_TYPES (fsLit ":") consDataConKey consDataCon
156
157 floatTyConName, floatDataConName, doubleTyConName, doubleDataConName :: Name
158 floatTyConName     = mkWiredInTyConName   UserSyntax gHC_TYPES (fsLit "Float") floatTyConKey floatTyCon
159 floatDataConName   = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "F#") floatDataConKey floatDataCon
160 doubleTyConName    = mkWiredInTyConName   UserSyntax gHC_TYPES (fsLit "Double") doubleTyConKey doubleTyCon
161 doubleDataConName  = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "D#") doubleDataConKey doubleDataCon
162
163 parrTyConName, parrDataConName :: Name
164 parrTyConName   = mkWiredInTyConName   BuiltInSyntax 
165                     gHC_PARR' (fsLit "[::]") parrTyConKey parrTyCon 
166 parrDataConName = mkWiredInDataConName UserSyntax    
167                     gHC_PARR' (fsLit "PArr") parrDataConKey parrDataCon
168
169 hetMetCodeTypeTyConName :: Name
170 hetMetCodeTypeTyConName = mkWiredInTyConName   BuiltInSyntax gHC_HETMET_CODETYPES (fsLit "<[]>@")      hetMetCodeTypeTyConKey   hetMetCodeTypeTyCon 
171 hetMetCodeTypeDataConName :: Name
172 hetMetCodeTypeDataConName       =
173     mkWiredInDataConName  BuiltInSyntax gHC_HETMET_CODETYPES (fsLit "<[]>")      hetMetCodeTypeDataConKey hetMetCodeTypeDataCon
174
175 boolTyCon_RDR, false_RDR, true_RDR, intTyCon_RDR, charTyCon_RDR,
176     intDataCon_RDR, listTyCon_RDR, consDataCon_RDR, parrTyCon_RDR, hetMetCodeTypeTyCon_RDR :: RdrName
177 boolTyCon_RDR   = nameRdrName boolTyConName
178 false_RDR       = nameRdrName falseDataConName
179 true_RDR        = nameRdrName trueDataConName
180 intTyCon_RDR    = nameRdrName intTyConName
181 charTyCon_RDR   = nameRdrName charTyConName
182 intDataCon_RDR  = nameRdrName intDataConName
183 listTyCon_RDR   = nameRdrName listTyConName
184 consDataCon_RDR = nameRdrName consDataConName
185 parrTyCon_RDR   = nameRdrName parrTyConName
186 hetMetCodeTypeTyCon_RDR = nameRdrName hetMetCodeTypeTyConName
187 \end{code}
188
189
190 %************************************************************************
191 %*                                                                      *
192 \subsection{mkWiredInTyCon}
193 %*                                                                      *
194 %************************************************************************
195
196 \begin{code}
197 pcNonRecDataTyCon :: Name -> [TyVar] -> [DataCon] -> TyCon
198 pcNonRecDataTyCon = pcTyCon False NonRecursive
199 pcRecDataTyCon :: Name -> [TyVar] -> [DataCon] -> TyCon
200 pcRecDataTyCon    = pcTyCon False Recursive
201
202 pcTyCon :: Bool -> RecFlag -> Name -> [TyVar] -> [DataCon] -> TyCon
203 pcTyCon is_enum is_rec name tyvars cons
204   = tycon
205   where
206     tycon = mkAlgTyCon name
207                 (mkArrowKinds (map tyVarKind tyvars) liftedTypeKind)
208                 tyvars
209                 []              -- No stupid theta
210                 (DataTyCon cons is_enum)
211                 NoParentTyCon
212                 is_rec
213                 False           -- Not in GADT syntax
214
215 pcDataCon :: Name -> [TyVar] -> [Type] -> TyCon -> DataCon
216 pcDataCon = pcDataConWithFixity False
217
218 pcDataConWithFixity :: Bool -> Name -> [TyVar] -> [Type] -> TyCon -> DataCon
219 -- The Name should be in the DataName name space; it's the name
220 -- of the DataCon itself.
221 --
222 -- The unique is the first of two free uniques;
223 -- the first is used for the datacon itself,
224 -- the second is used for the "worker name"
225
226 pcDataConWithFixity declared_infix dc_name tyvars arg_tys tycon
227   = data_con
228   where
229     data_con = mkDataCon dc_name declared_infix
230                 (map (const HsNoBang) arg_tys)
231                 []      -- No labelled fields
232                 tyvars
233                 []      -- No existential type variables
234                 []      -- No equality spec
235                 []      -- No theta
236                 arg_tys (mkTyConApp tycon (mkTyVarTys tyvars)) 
237                 tycon
238                 []      -- No stupid theta
239                 (mkDataConIds bogus_wrap_name wrk_name data_con)
240                 
241
242     modu     = ASSERT( isExternalName dc_name ) 
243                nameModule dc_name
244     wrk_occ  = mkDataConWorkerOcc (nameOccName dc_name)
245     wrk_key  = incrUnique (nameUnique dc_name)
246     wrk_name = mkWiredInName modu wrk_occ wrk_key
247                              (AnId (dataConWorkId data_con)) UserSyntax
248     bogus_wrap_name = pprPanic "Wired-in data wrapper id" (ppr dc_name)
249         -- Wired-in types are too simple to need wrappers
250 \end{code}
251
252
253 %************************************************************************
254 %*                                                                      *
255 \subsection[TysWiredIn-tuples]{The tuple types}
256 %*                                                                      *
257 %************************************************************************
258
259 \begin{code}
260 tupleTyCon :: Boxity -> Arity -> TyCon
261 tupleTyCon boxity i | i > mAX_TUPLE_SIZE = fst (mk_tuple boxity i)      -- Build one specially
262 tupleTyCon Boxed   i = fst (boxedTupleArr   ! i)
263 tupleTyCon Unboxed i = fst (unboxedTupleArr ! i)
264
265 tupleCon :: Boxity -> Arity -> DataCon
266 tupleCon boxity i | i > mAX_TUPLE_SIZE = snd (mk_tuple boxity i)        -- Build one specially
267 tupleCon Boxed   i = snd (boxedTupleArr   ! i)
268 tupleCon Unboxed i = snd (unboxedTupleArr ! i)
269
270 boxedTupleArr, unboxedTupleArr :: Array Int (TyCon,DataCon)
271 boxedTupleArr   = listArray (0,mAX_TUPLE_SIZE) [mk_tuple Boxed i | i <- [0..mAX_TUPLE_SIZE]]
272 unboxedTupleArr = listArray (0,mAX_TUPLE_SIZE) [mk_tuple Unboxed i | i <- [0..mAX_TUPLE_SIZE]]
273
274 mk_tuple :: Boxity -> Int -> (TyCon,DataCon)
275 mk_tuple boxity arity = (tycon, tuple_con)
276   where
277         tycon   = mkTupleTyCon tc_name tc_kind arity tyvars tuple_con boxity 
278         modu    = mkTupleModule boxity arity
279         tc_name = mkWiredInName modu (mkTupleOcc tcName boxity arity) tc_uniq
280                                 (ATyCon tycon) BuiltInSyntax
281         tc_kind = mkArrowKinds (map tyVarKind tyvars) res_kind
282         res_kind | isBoxed boxity = liftedTypeKind
283                  | otherwise      = ubxTupleKind
284
285         tyvars   | isBoxed boxity = take arity alphaTyVars
286                  | otherwise      = take arity openAlphaTyVars
287
288         tuple_con = pcDataCon dc_name tyvars tyvar_tys tycon
289         tyvar_tys = mkTyVarTys tyvars
290         dc_name   = mkWiredInName modu (mkTupleOcc dataName boxity arity) dc_uniq
291                                   (ADataCon tuple_con) BuiltInSyntax
292         tc_uniq   = mkTupleTyConUnique   boxity arity
293         dc_uniq   = mkTupleDataConUnique boxity arity
294
295 unitTyCon :: TyCon
296 unitTyCon     = tupleTyCon Boxed 0
297 unitDataCon :: DataCon
298 unitDataCon   = head (tyConDataCons unitTyCon)
299 unitDataConId :: Id
300 unitDataConId = dataConWorkId unitDataCon
301
302 pairTyCon :: TyCon
303 pairTyCon = tupleTyCon Boxed 2
304
305 unboxedSingletonTyCon :: TyCon
306 unboxedSingletonTyCon   = tupleTyCon Unboxed 1
307 unboxedSingletonDataCon :: DataCon
308 unboxedSingletonDataCon = tupleCon   Unboxed 1
309
310 unboxedPairTyCon :: TyCon
311 unboxedPairTyCon   = tupleTyCon Unboxed 2
312 unboxedPairDataCon :: DataCon
313 unboxedPairDataCon = tupleCon   Unboxed 2
314 \end{code}
315
316
317 %************************************************************************
318 %*                                                                      *
319 \subsection[TysWiredIn-boxed-prim]{The ``boxed primitive'' types (@Char@, @Int@, etc)}
320 %*                                                                      *
321 %************************************************************************
322
323 \begin{code}
324 charTy :: Type
325 charTy = mkTyConTy charTyCon
326
327 charTyCon :: TyCon
328 charTyCon   = pcNonRecDataTyCon charTyConName [] [charDataCon]
329 charDataCon :: DataCon
330 charDataCon = pcDataCon charDataConName [] [charPrimTy] charTyCon
331
332 stringTy :: Type
333 stringTy = mkListTy charTy -- convenience only
334 \end{code}
335
336 \begin{code}
337 intTy :: Type
338 intTy = mkTyConTy intTyCon 
339
340 intTyCon :: TyCon
341 intTyCon = pcNonRecDataTyCon intTyConName [] [intDataCon]
342 intDataCon :: DataCon
343 intDataCon = pcDataCon intDataConName [] [intPrimTy] intTyCon
344 \end{code}
345
346 \begin{code}
347 wordTy :: Type
348 wordTy = mkTyConTy wordTyCon 
349
350 wordTyCon :: TyCon
351 wordTyCon = pcNonRecDataTyCon wordTyConName [] [wordDataCon]
352 wordDataCon :: DataCon
353 wordDataCon = pcDataCon wordDataConName [] [wordPrimTy] wordTyCon
354 \end{code}
355
356 \begin{code}
357 floatTy :: Type
358 floatTy = mkTyConTy floatTyCon
359
360 floatTyCon :: TyCon
361 floatTyCon   = pcNonRecDataTyCon floatTyConName   [] [floatDataCon]
362 floatDataCon :: DataCon
363 floatDataCon = pcDataCon         floatDataConName [] [floatPrimTy] floatTyCon
364 \end{code}
365
366 \begin{code}
367 doubleTy :: Type
368 doubleTy = mkTyConTy doubleTyCon
369
370 doubleTyCon :: TyCon
371 doubleTyCon = pcNonRecDataTyCon doubleTyConName [] [doubleDataCon]
372
373 doubleDataCon :: DataCon
374 doubleDataCon = pcDataCon doubleDataConName [] [doublePrimTy] doubleTyCon
375 \end{code}
376
377
378 %************************************************************************
379 %*                                                                      *
380 \subsection[TysWiredIn-Bool]{The @Bool@ type}
381 %*                                                                      *
382 %************************************************************************
383
384 An ordinary enumeration type, but deeply wired in.  There are no
385 magical operations on @Bool@ (just the regular Prelude code).
386
387 {\em BEGIN IDLE SPECULATION BY SIMON}
388
389 This is not the only way to encode @Bool@.  A more obvious coding makes
390 @Bool@ just a boxed up version of @Bool#@, like this:
391 \begin{verbatim}
392 type Bool# = Int#
393 data Bool = MkBool Bool#
394 \end{verbatim}
395
396 Unfortunately, this doesn't correspond to what the Report says @Bool@
397 looks like!  Furthermore, we get slightly less efficient code (I
398 think) with this coding. @gtInt@ would look like this:
399
400 \begin{verbatim}
401 gtInt :: Int -> Int -> Bool
402 gtInt x y = case x of I# x# ->
403             case y of I# y# ->
404             case (gtIntPrim x# y#) of
405                 b# -> MkBool b#
406 \end{verbatim}
407
408 Notice that the result of the @gtIntPrim@ comparison has to be turned
409 into an integer (here called @b#@), and returned in a @MkBool@ box.
410
411 The @if@ expression would compile to this:
412 \begin{verbatim}
413 case (gtInt x y) of
414   MkBool b# -> case b# of { 1# -> e1; 0# -> e2 }
415 \end{verbatim}
416
417 I think this code is a little less efficient than the previous code,
418 but I'm not certain.  At all events, corresponding with the Report is
419 important.  The interesting thing is that the language is expressive
420 enough to describe more than one alternative; and that a type doesn't
421 necessarily need to be a straightforwardly boxed version of its
422 primitive counterpart.
423
424 {\em END IDLE SPECULATION BY SIMON}
425
426 \begin{code}
427 boolTy :: Type
428 boolTy = mkTyConTy boolTyCon
429
430 boolTyCon :: TyCon
431 boolTyCon = pcTyCon True NonRecursive boolTyConName
432                     [] [falseDataCon, trueDataCon]
433
434 falseDataCon, trueDataCon :: DataCon
435 falseDataCon = pcDataCon falseDataConName [] [] boolTyCon
436 trueDataCon  = pcDataCon trueDataConName  [] [] boolTyCon
437
438 falseDataConId, trueDataConId :: Id
439 falseDataConId = dataConWorkId falseDataCon
440 trueDataConId  = dataConWorkId trueDataCon
441 \end{code}
442
443 %************************************************************************
444 %*                                                                      *
445 \subsection[TysWiredIn-List]{The @List@ type (incl ``build'' magic)}
446 %*                                                                      *
447 %************************************************************************
448
449 Special syntax, deeply wired in, but otherwise an ordinary algebraic
450 data types:
451 \begin{verbatim}
452 data [] a = [] | a : (List a)
453 data () = ()
454 data (,) a b = (,,) a b
455 ...
456 \end{verbatim}
457
458 \begin{code}
459 mkListTy :: Type -> Type
460 mkListTy ty = mkTyConApp listTyCon [ty]
461
462 listTyCon :: TyCon
463 listTyCon = pcRecDataTyCon listTyConName alpha_tyvar [nilDataCon, consDataCon]
464
465 nilDataCon :: DataCon
466 nilDataCon  = pcDataCon nilDataConName alpha_tyvar [] listTyCon
467
468 consDataCon :: DataCon
469 consDataCon = pcDataConWithFixity True {- Declared infix -}
470                consDataConName
471                alpha_tyvar [alphaTy, mkTyConApp listTyCon alpha_ty] listTyCon
472 -- Interesting: polymorphic recursion would help here.
473 -- We can't use (mkListTy alphaTy) in the defn of consDataCon, else mkListTy
474 -- gets the over-specific type (Type -> Type)
475 \end{code}
476
477 %************************************************************************
478 %*                                                                      *
479 \subsection[TysWiredIn-Tuples]{The @Tuple@ types}
480 %*                                                                      *
481 %************************************************************************
482
483 The tuple types are definitely magic, because they form an infinite
484 family.
485
486 \begin{itemize}
487 \item
488 They have a special family of type constructors, of type @TyCon@
489 These contain the tycon arity, but don't require a Unique.
490
491 \item
492 They have a special family of constructors, of type
493 @Id@. Again these contain their arity but don't need a Unique.
494
495 \item
496 There should be a magic way of generating the info tables and
497 entry code for all tuples.
498
499 But at the moment we just compile a Haskell source
500 file\srcloc{lib/prelude/...} containing declarations like:
501 \begin{verbatim}
502 data Tuple0             = Tup0
503 data Tuple2  a b        = Tup2  a b
504 data Tuple3  a b c      = Tup3  a b c
505 data Tuple4  a b c d    = Tup4  a b c d
506 ...
507 \end{verbatim}
508 The print-names associated with the magic @Id@s for tuple constructors
509 ``just happen'' to be the same as those generated by these
510 declarations.
511
512 \item
513 The instance environment should have a magic way to know
514 that each tuple type is an instances of classes @Eq@, @Ix@, @Ord@ and
515 so on. \ToDo{Not implemented yet.}
516
517 \item
518 There should also be a way to generate the appropriate code for each
519 of these instances, but (like the info tables and entry code) it is
520 done by enumeration\srcloc{lib/prelude/InTup?.hs}.
521 \end{itemize}
522
523 \begin{code}
524 mkTupleTy :: Boxity -> [Type] -> Type
525 -- Special case for *boxed* 1-tuples, which are represented by the type itself
526 mkTupleTy boxity [ty] | Boxed <- boxity = ty
527 mkTupleTy boxity tys = mkTyConApp (tupleTyCon boxity (length tys)) tys
528
529 -- | Build the type of a small tuple that holds the specified type of thing
530 mkBoxedTupleTy :: [Type] -> Type
531 mkBoxedTupleTy tys = mkTupleTy Boxed tys
532
533 unitTy :: Type
534 unitTy = mkTupleTy Boxed []
535 \end{code}
536
537 %************************************************************************
538 %*                                                                      *
539 \subsection[TysWiredIn-PArr]{The @[::]@ type}
540 %*                                                                      *
541 %************************************************************************
542
543 Special syntax for parallel arrays needs some wired in definitions.
544
545 \begin{code}
546 -- | Construct a type representing the application of the parallel array constructor 
547 mkPArrTy    :: Type -> Type
548 mkPArrTy ty  = mkTyConApp parrTyCon [ty]
549
550 -- | Represents the type constructor of parallel arrays
551 --
552 --  * This must match the definition in @PrelPArr@
553 --
554 -- NB: Although the constructor is given here, it will not be accessible in
555 --     user code as it is not in the environment of any compiled module except
556 --     @PrelPArr@.
557 --
558 parrTyCon :: TyCon
559 parrTyCon  = pcNonRecDataTyCon parrTyConName alpha_tyvar [parrDataCon]
560
561 parrDataCon :: DataCon
562 parrDataCon  = pcDataCon 
563                  parrDataConName 
564                  alpha_tyvar            -- forall'ed type variables
565                  [intPrimTy,            -- 1st argument: Int#
566                   mkTyConApp            -- 2nd argument: Array# a
567                     arrayPrimTyCon 
568                     alpha_ty] 
569                  parrTyCon
570
571 -- | Check whether a type constructor is the constructor for parallel arrays
572 isPArrTyCon    :: TyCon -> Bool
573 isPArrTyCon tc  = tyConName tc == parrTyConName
574
575 -- | Fake array constructors
576 --
577 -- * These constructors are never really used to represent array values;
578 --   however, they are very convenient during desugaring (and, in particular,
579 --   in the pattern matching compiler) to treat array pattern just like
580 --   yet another constructor pattern
581 --
582 parrFakeCon                        :: Arity -> DataCon
583 parrFakeCon i | i > mAX_TUPLE_SIZE  = mkPArrFakeCon  i  -- build one specially
584 parrFakeCon i                       = parrFakeConArr!i
585
586 -- pre-defined set of constructors
587 --
588 parrFakeConArr :: Array Int DataCon
589 parrFakeConArr  = array (0, mAX_TUPLE_SIZE) [(i, mkPArrFakeCon i)   
590                                             | i <- [0..mAX_TUPLE_SIZE]]
591
592 -- build a fake parallel array constructor for the given arity
593 --
594 mkPArrFakeCon       :: Int -> DataCon
595 mkPArrFakeCon arity  = data_con
596   where
597         data_con  = pcDataCon name [tyvar] tyvarTys parrTyCon
598         tyvar     = head alphaTyVars
599         tyvarTys  = replicate arity $ mkTyVarTy tyvar
600         nameStr   = mkFastString ("MkPArr" ++ show arity)
601         name      = mkWiredInName gHC_PARR' (mkDataOccFS nameStr) unique
602                                   (ADataCon data_con) UserSyntax
603         unique      = mkPArrDataConUnique arity
604
605 -- | Checks whether a data constructor is a fake constructor for parallel arrays
606 isPArrFakeCon      :: DataCon -> Bool
607 isPArrFakeCon dcon  = dcon == parrFakeCon (dataConSourceArity dcon)
608 \end{code}
609
610 Heterogeneous Metaprogramming
611
612 \begin{code}
613 -- | Construct a type representing the application of the box type
614 mkHetMetCodeTypeTy    :: TyVar -> Type -> Type
615 mkHetMetCodeTypeTy ecn ty = mkTyConApp hetMetCodeTypeTyCon [(mkTyVarTy ecn), ty]
616
617 ecTyVar = head ecTyVars
618
619 -- | Represents the type constructor of box types
620 hetMetCodeTypeTyCon :: TyCon
621 hetMetCodeTypeTyCon  = pcNonRecDataTyCon hetMetCodeTypeTyConName [ecTyVar, betaTyVar] [hetMetCodeTypeDataCon]
622
623 -- | Check whether a type constructor is the constructor for box types
624 isHetMetCodeTypeTyCon    :: TyCon -> Bool
625 isHetMetCodeTypeTyCon tc  = tyConName tc == hetMetCodeTypeTyConName
626
627 hetMetCodeTypeDataCon :: DataCon
628 hetMetCodeTypeDataCon  = pcDataCon 
629                  hetMetCodeTypeDataConName 
630                  [betaTyVar]            -- forall'ed type variables
631                  [betaTy] 
632                  hetMetCodeTypeTyCon
633
634 \end{code}