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