Merge branch 'master' of http://darcs.haskell.org/ghc into ghc-generics
[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                 False           -- Not in GADT syntax
200
201 pcDataCon :: Name -> [TyVar] -> [Type] -> TyCon -> DataCon
202 pcDataCon = pcDataConWithFixity False
203
204 pcDataConWithFixity :: Bool -> Name -> [TyVar] -> [Type] -> TyCon -> DataCon
205 -- The Name should be in the DataName name space; it's the name
206 -- of the DataCon itself.
207 --
208 -- The unique is the first of two free uniques;
209 -- the first is used for the datacon itself,
210 -- the second is used for the "worker name"
211
212 pcDataConWithFixity declared_infix dc_name tyvars arg_tys tycon
213   = data_con
214   where
215     data_con = mkDataCon dc_name declared_infix
216                 (map (const HsNoBang) arg_tys)
217                 []      -- No labelled fields
218                 tyvars
219                 []      -- No existential type variables
220                 []      -- No equality spec
221                 []      -- No theta
222                 arg_tys (mkTyConApp tycon (mkTyVarTys tyvars)) 
223                 tycon
224                 []      -- No stupid theta
225                 (mkDataConIds bogus_wrap_name wrk_name data_con)
226                 
227
228     modu     = ASSERT( isExternalName dc_name ) 
229                nameModule dc_name
230     wrk_occ  = mkDataConWorkerOcc (nameOccName dc_name)
231     wrk_key  = incrUnique (nameUnique dc_name)
232     wrk_name = mkWiredInName modu wrk_occ wrk_key
233                              (AnId (dataConWorkId data_con)) UserSyntax
234     bogus_wrap_name = pprPanic "Wired-in data wrapper id" (ppr dc_name)
235         -- Wired-in types are too simple to need wrappers
236 \end{code}
237
238
239 %************************************************************************
240 %*                                                                      *
241 \subsection[TysWiredIn-tuples]{The tuple types}
242 %*                                                                      *
243 %************************************************************************
244
245 \begin{code}
246 tupleTyCon :: Boxity -> Arity -> TyCon
247 tupleTyCon boxity i | i > mAX_TUPLE_SIZE = fst (mk_tuple boxity i)      -- Build one specially
248 tupleTyCon Boxed   i = fst (boxedTupleArr   ! i)
249 tupleTyCon Unboxed i = fst (unboxedTupleArr ! i)
250
251 tupleCon :: Boxity -> Arity -> DataCon
252 tupleCon boxity i | i > mAX_TUPLE_SIZE = snd (mk_tuple boxity i)        -- Build one specially
253 tupleCon Boxed   i = snd (boxedTupleArr   ! i)
254 tupleCon Unboxed i = snd (unboxedTupleArr ! i)
255
256 boxedTupleArr, unboxedTupleArr :: Array Int (TyCon,DataCon)
257 boxedTupleArr   = listArray (0,mAX_TUPLE_SIZE) [mk_tuple Boxed i | i <- [0..mAX_TUPLE_SIZE]]
258 unboxedTupleArr = listArray (0,mAX_TUPLE_SIZE) [mk_tuple Unboxed i | i <- [0..mAX_TUPLE_SIZE]]
259
260 mk_tuple :: Boxity -> Int -> (TyCon,DataCon)
261 mk_tuple boxity arity = (tycon, tuple_con)
262   where
263         tycon   = mkTupleTyCon tc_name tc_kind arity tyvars tuple_con boxity 
264         modu    = mkTupleModule boxity arity
265         tc_name = mkWiredInName modu (mkTupleOcc tcName boxity arity) tc_uniq
266                                 (ATyCon tycon) BuiltInSyntax
267         tc_kind = mkArrowKinds (map tyVarKind tyvars) res_kind
268         res_kind | isBoxed boxity = liftedTypeKind
269                  | otherwise      = ubxTupleKind
270
271         tyvars   | isBoxed boxity = take arity alphaTyVars
272                  | otherwise      = take arity openAlphaTyVars
273
274         tuple_con = pcDataCon dc_name tyvars tyvar_tys tycon
275         tyvar_tys = mkTyVarTys tyvars
276         dc_name   = mkWiredInName modu (mkTupleOcc dataName boxity arity) dc_uniq
277                                   (ADataCon tuple_con) BuiltInSyntax
278         tc_uniq   = mkTupleTyConUnique   boxity arity
279         dc_uniq   = mkTupleDataConUnique boxity arity
280
281 unitTyCon :: TyCon
282 unitTyCon     = tupleTyCon Boxed 0
283 unitDataCon :: DataCon
284 unitDataCon   = head (tyConDataCons unitTyCon)
285 unitDataConId :: Id
286 unitDataConId = dataConWorkId unitDataCon
287
288 pairTyCon :: TyCon
289 pairTyCon = tupleTyCon Boxed 2
290
291 unboxedSingletonTyCon :: TyCon
292 unboxedSingletonTyCon   = tupleTyCon Unboxed 1
293 unboxedSingletonDataCon :: DataCon
294 unboxedSingletonDataCon = tupleCon   Unboxed 1
295
296 unboxedPairTyCon :: TyCon
297 unboxedPairTyCon   = tupleTyCon Unboxed 2
298 unboxedPairDataCon :: DataCon
299 unboxedPairDataCon = tupleCon   Unboxed 2
300 \end{code}
301
302
303 %************************************************************************
304 %*                                                                      *
305 \subsection[TysWiredIn-boxed-prim]{The ``boxed primitive'' types (@Char@, @Int@, etc)}
306 %*                                                                      *
307 %************************************************************************
308
309 \begin{code}
310 charTy :: Type
311 charTy = mkTyConTy charTyCon
312
313 charTyCon :: TyCon
314 charTyCon   = pcNonRecDataTyCon charTyConName [] [charDataCon]
315 charDataCon :: DataCon
316 charDataCon = pcDataCon charDataConName [] [charPrimTy] charTyCon
317
318 stringTy :: Type
319 stringTy = mkListTy charTy -- convenience only
320 \end{code}
321
322 \begin{code}
323 intTy :: Type
324 intTy = mkTyConTy intTyCon 
325
326 intTyCon :: TyCon
327 intTyCon = pcNonRecDataTyCon intTyConName [] [intDataCon]
328 intDataCon :: DataCon
329 intDataCon = pcDataCon intDataConName [] [intPrimTy] intTyCon
330 \end{code}
331
332 \begin{code}
333 wordTy :: Type
334 wordTy = mkTyConTy wordTyCon 
335
336 wordTyCon :: TyCon
337 wordTyCon = pcNonRecDataTyCon wordTyConName [] [wordDataCon]
338 wordDataCon :: DataCon
339 wordDataCon = pcDataCon wordDataConName [] [wordPrimTy] wordTyCon
340 \end{code}
341
342 \begin{code}
343 floatTy :: Type
344 floatTy = mkTyConTy floatTyCon
345
346 floatTyCon :: TyCon
347 floatTyCon   = pcNonRecDataTyCon floatTyConName   [] [floatDataCon]
348 floatDataCon :: DataCon
349 floatDataCon = pcDataCon         floatDataConName [] [floatPrimTy] floatTyCon
350 \end{code}
351
352 \begin{code}
353 doubleTy :: Type
354 doubleTy = mkTyConTy doubleTyCon
355
356 doubleTyCon :: TyCon
357 doubleTyCon = pcNonRecDataTyCon doubleTyConName [] [doubleDataCon]
358
359 doubleDataCon :: DataCon
360 doubleDataCon = pcDataCon doubleDataConName [] [doublePrimTy] doubleTyCon
361 \end{code}
362
363
364 %************************************************************************
365 %*                                                                      *
366 \subsection[TysWiredIn-Bool]{The @Bool@ type}
367 %*                                                                      *
368 %************************************************************************
369
370 An ordinary enumeration type, but deeply wired in.  There are no
371 magical operations on @Bool@ (just the regular Prelude code).
372
373 {\em BEGIN IDLE SPECULATION BY SIMON}
374
375 This is not the only way to encode @Bool@.  A more obvious coding makes
376 @Bool@ just a boxed up version of @Bool#@, like this:
377 \begin{verbatim}
378 type Bool# = Int#
379 data Bool = MkBool Bool#
380 \end{verbatim}
381
382 Unfortunately, this doesn't correspond to what the Report says @Bool@
383 looks like!  Furthermore, we get slightly less efficient code (I
384 think) with this coding. @gtInt@ would look like this:
385
386 \begin{verbatim}
387 gtInt :: Int -> Int -> Bool
388 gtInt x y = case x of I# x# ->
389             case y of I# y# ->
390             case (gtIntPrim x# y#) of
391                 b# -> MkBool b#
392 \end{verbatim}
393
394 Notice that the result of the @gtIntPrim@ comparison has to be turned
395 into an integer (here called @b#@), and returned in a @MkBool@ box.
396
397 The @if@ expression would compile to this:
398 \begin{verbatim}
399 case (gtInt x y) of
400   MkBool b# -> case b# of { 1# -> e1; 0# -> e2 }
401 \end{verbatim}
402
403 I think this code is a little less efficient than the previous code,
404 but I'm not certain.  At all events, corresponding with the Report is
405 important.  The interesting thing is that the language is expressive
406 enough to describe more than one alternative; and that a type doesn't
407 necessarily need to be a straightforwardly boxed version of its
408 primitive counterpart.
409
410 {\em END IDLE SPECULATION BY SIMON}
411
412 \begin{code}
413 boolTy :: Type
414 boolTy = mkTyConTy boolTyCon
415
416 boolTyCon :: TyCon
417 boolTyCon = pcTyCon True NonRecursive boolTyConName
418                     [] [falseDataCon, trueDataCon]
419
420 falseDataCon, trueDataCon :: DataCon
421 falseDataCon = pcDataCon falseDataConName [] [] boolTyCon
422 trueDataCon  = pcDataCon trueDataConName  [] [] boolTyCon
423
424 falseDataConId, trueDataConId :: Id
425 falseDataConId = dataConWorkId falseDataCon
426 trueDataConId  = dataConWorkId trueDataCon
427 \end{code}
428
429 %************************************************************************
430 %*                                                                      *
431 \subsection[TysWiredIn-List]{The @List@ type (incl ``build'' magic)}
432 %*                                                                      *
433 %************************************************************************
434
435 Special syntax, deeply wired in, but otherwise an ordinary algebraic
436 data types:
437 \begin{verbatim}
438 data [] a = [] | a : (List a)
439 data () = ()
440 data (,) a b = (,,) a b
441 ...
442 \end{verbatim}
443
444 \begin{code}
445 mkListTy :: Type -> Type
446 mkListTy ty = mkTyConApp listTyCon [ty]
447
448 listTyCon :: TyCon
449 listTyCon = pcRecDataTyCon listTyConName alpha_tyvar [nilDataCon, consDataCon]
450
451 nilDataCon :: DataCon
452 nilDataCon  = pcDataCon nilDataConName alpha_tyvar [] listTyCon
453
454 consDataCon :: DataCon
455 consDataCon = pcDataConWithFixity True {- Declared infix -}
456                consDataConName
457                alpha_tyvar [alphaTy, mkTyConApp listTyCon alpha_ty] listTyCon
458 -- Interesting: polymorphic recursion would help here.
459 -- We can't use (mkListTy alphaTy) in the defn of consDataCon, else mkListTy
460 -- gets the over-specific type (Type -> Type)
461 \end{code}
462
463 %************************************************************************
464 %*                                                                      *
465 \subsection[TysWiredIn-Tuples]{The @Tuple@ types}
466 %*                                                                      *
467 %************************************************************************
468
469 The tuple types are definitely magic, because they form an infinite
470 family.
471
472 \begin{itemize}
473 \item
474 They have a special family of type constructors, of type @TyCon@
475 These contain the tycon arity, but don't require a Unique.
476
477 \item
478 They have a special family of constructors, of type
479 @Id@. Again these contain their arity but don't need a Unique.
480
481 \item
482 There should be a magic way of generating the info tables and
483 entry code for all tuples.
484
485 But at the moment we just compile a Haskell source
486 file\srcloc{lib/prelude/...} containing declarations like:
487 \begin{verbatim}
488 data Tuple0             = Tup0
489 data Tuple2  a b        = Tup2  a b
490 data Tuple3  a b c      = Tup3  a b c
491 data Tuple4  a b c d    = Tup4  a b c d
492 ...
493 \end{verbatim}
494 The print-names associated with the magic @Id@s for tuple constructors
495 ``just happen'' to be the same as those generated by these
496 declarations.
497
498 \item
499 The instance environment should have a magic way to know
500 that each tuple type is an instances of classes @Eq@, @Ix@, @Ord@ and
501 so on. \ToDo{Not implemented yet.}
502
503 \item
504 There should also be a way to generate the appropriate code for each
505 of these instances, but (like the info tables and entry code) it is
506 done by enumeration\srcloc{lib/prelude/InTup?.hs}.
507 \end{itemize}
508
509 \begin{code}
510 mkTupleTy :: Boxity -> [Type] -> Type
511 -- Special case for *boxed* 1-tuples, which are represented by the type itself
512 mkTupleTy boxity [ty] | Boxed <- boxity = ty
513 mkTupleTy boxity tys = mkTyConApp (tupleTyCon boxity (length tys)) tys
514
515 -- | Build the type of a small tuple that holds the specified type of thing
516 mkBoxedTupleTy :: [Type] -> Type
517 mkBoxedTupleTy tys = mkTupleTy Boxed tys
518
519 unitTy :: Type
520 unitTy = mkTupleTy Boxed []
521 \end{code}
522
523 %************************************************************************
524 %*                                                                      *
525 \subsection[TysWiredIn-PArr]{The @[::]@ type}
526 %*                                                                      *
527 %************************************************************************
528
529 Special syntax for parallel arrays needs some wired in definitions.
530
531 \begin{code}
532 -- | Construct a type representing the application of the parallel array constructor 
533 mkPArrTy    :: Type -> Type
534 mkPArrTy ty  = mkTyConApp parrTyCon [ty]
535
536 -- | Represents the type constructor of parallel arrays
537 --
538 --  * This must match the definition in @PrelPArr@
539 --
540 -- NB: Although the constructor is given here, it will not be accessible in
541 --     user code as it is not in the environment of any compiled module except
542 --     @PrelPArr@.
543 --
544 parrTyCon :: TyCon
545 parrTyCon  = pcNonRecDataTyCon parrTyConName alpha_tyvar [parrDataCon]
546
547 parrDataCon :: DataCon
548 parrDataCon  = pcDataCon 
549                  parrDataConName 
550                  alpha_tyvar            -- forall'ed type variables
551                  [intPrimTy,            -- 1st argument: Int#
552                   mkTyConApp            -- 2nd argument: Array# a
553                     arrayPrimTyCon 
554                     alpha_ty] 
555                  parrTyCon
556
557 -- | Check whether a type constructor is the constructor for parallel arrays
558 isPArrTyCon    :: TyCon -> Bool
559 isPArrTyCon tc  = tyConName tc == parrTyConName
560
561 -- | Fake array constructors
562 --
563 -- * These constructors are never really used to represent array values;
564 --   however, they are very convenient during desugaring (and, in particular,
565 --   in the pattern matching compiler) to treat array pattern just like
566 --   yet another constructor pattern
567 --
568 parrFakeCon                        :: Arity -> DataCon
569 parrFakeCon i | i > mAX_TUPLE_SIZE  = mkPArrFakeCon  i  -- build one specially
570 parrFakeCon i                       = parrFakeConArr!i
571
572 -- pre-defined set of constructors
573 --
574 parrFakeConArr :: Array Int DataCon
575 parrFakeConArr  = array (0, mAX_TUPLE_SIZE) [(i, mkPArrFakeCon i)   
576                                             | i <- [0..mAX_TUPLE_SIZE]]
577
578 -- build a fake parallel array constructor for the given arity
579 --
580 mkPArrFakeCon       :: Int -> DataCon
581 mkPArrFakeCon arity  = data_con
582   where
583         data_con  = pcDataCon name [tyvar] tyvarTys parrTyCon
584         tyvar     = head alphaTyVars
585         tyvarTys  = replicate arity $ mkTyVarTy tyvar
586         nameStr   = mkFastString ("MkPArr" ++ show arity)
587         name      = mkWiredInName gHC_PARR' (mkDataOccFS nameStr) unique
588                                   (ADataCon data_con) UserSyntax
589         unique      = mkPArrDataConUnique arity
590
591 -- | Checks whether a data constructor is a fake constructor for parallel arrays
592 isPArrFakeCon      :: DataCon -> Bool
593 isPArrFakeCon dcon  = dcon == parrFakeCon (dataConSourceArity dcon)
594 \end{code}