3f581960950b62699616b1389aed858b105f9a1a
[ghc-hetmet.git] / ghc / compiler / prelude / AbsPrel.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
3 %
4 \section[AbsPrel]{The @AbsPrel@ interface to the compiler's prelude knowledge}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module AbsPrel (
10
11 -- unlike most export lists, this one is actually interesting :-)
12
13         -- re-export some PrimOp stuff:
14         PrimOp(..), typeOfPrimOp, primOpNameInfo,
15         HeapRequirement(..), primOpHeapReq, primOpCanTriggerGC, 
16         primOpNeedsWrapper, primOpOkForSpeculation, primOpIsCheap,
17         fragilePrimOp,
18         PrimOpResultInfo(..), getPrimOpResultInfo,
19         pprPrimOp, showPrimOp, isCompareOp,
20         readUnfoldingPrimOp,  -- actually, defined herein
21
22         pRELUDE, pRELUDE_BUILTIN, pRELUDE_CORE, pRELUDE_RATIO,
23         pRELUDE_LIST, pRELUDE_TEXT, --OLD: pRELUDE_ARRAY, pRELUDE_COMPLEX,
24         pRELUDE_PRIMIO, pRELUDE_IO, pRELUDE_PS,
25         gLASGOW_ST, {-gLASGOW_IO,-} gLASGOW_MISC,
26
27         -- lookup functions for built-in names, for the renamer:
28         builtinNameInfo,
29
30         -- *odd* values that need to be reached out and grabbed:
31         eRROR_ID, pAT_ERROR_ID, aBSENT_ERROR_ID,
32         packStringForCId,
33         unpackCStringId, unpackCString2Id,
34         unpackCStringAppendId, unpackCStringFoldrId,
35         integerZeroId, integerPlusOneId,
36         integerPlusTwoId, integerMinusOneId,
37
38 #ifdef DPH
39         -- ProcessorClass
40         toPodId,
41
42         -- Pid Class
43         fromDomainId, toDomainId,
44 #endif {- Data Parallel Haskell -}
45
46         -----------------------------------------------------
47         -- the rest of the export list is organised by *type*
48         -----------------------------------------------------
49
50         -- "type": functions ("arrow" type constructor)
51         mkFunTy,
52
53         -- type: Bool
54         boolTyCon, boolTy, falseDataCon, trueDataCon,
55
56         -- types: Char#, Char, String (= [Char])
57         charPrimTy, charTy, stringTy,
58         charPrimTyCon, charTyCon, charDataCon,
59
60         -- type: CMP_TAG (used in deriving)
61         cmpTagTy, ltPrimDataCon, eqPrimDataCon, gtPrimDataCon,
62
63         -- types: Double#, Double
64         doublePrimTy, doubleTy,
65         doublePrimTyCon, doubleTyCon, doubleDataCon,
66
67         -- types: Float#, Float
68         floatPrimTy, floatTy,
69         floatPrimTyCon, floatTyCon, floatDataCon,
70
71         -- types: Glasgow *primitive* arrays, sequencing and I/O
72         mkPrimIoTy, -- to typecheck "mainIO", "mainPrimIO" & for _ccall_s
73         realWorldStatePrimTy, realWorldStateTy{-boxed-},
74         realWorldTy, realWorldTyCon, realWorldPrimId,
75         stateDataCon, getStatePairingConInfo,
76
77         -- types: Void# (only used within the compiler)
78         voidPrimTy, voidPrimId,
79
80         -- types: Addr#, Int#, Word#, Int
81         intPrimTy, intTy, intPrimTyCon, intTyCon, intDataCon,
82         wordPrimTyCon, wordPrimTy, wordTy, wordTyCon, wordDataCon,
83         addrPrimTyCon, addrPrimTy, addrTy, addrTyCon, addrDataCon,
84
85         -- types: Integer, Rational (= Ratio Integer)
86         integerTy, rationalTy,
87         integerTyCon, integerDataCon,
88         rationalTyCon, ratioDataCon,
89
90         -- type: Lift
91         liftTyCon, liftDataCon, mkLiftTy,
92
93         -- type: List
94         listTyCon, mkListTy, nilDataCon, consDataCon,
95         -- NOT USED: buildDataCon,
96
97         -- type: tuples
98         mkTupleTy, unitTy,
99
100         -- packed Strings
101 --      packedStringTyCon, packedStringTy, psDataCon, cpsDataCon,
102
103         -- for compilation of List Comprehensions and foldr
104         foldlId, foldrId, mkFoldl, mkFoldr,
105         mkBuild, buildId, augmentId, appendId,
106
107 #ifdef DPH
108         mkProcessorTy,
109         mkPodTy, mkPodNTy, podTyCon,                         -- user model
110         mkPodizedPodNTy,                                     -- podized model
111         mkInterfacePodNTy, interfacePodTyCon, mKINTERPOD_ID, -- interface model
112
113         -- Misc used during podization
114         primIfromPodNSelectorId,
115 #endif {- Data Parallel Haskell -}
116
117         -- and, finally, we must put in some (abstract) data types,
118         -- to make the interface self-sufficient
119         GlobalSwitch, Id, Maybe, Name, PprStyle, PrimKind, HeapOffset,
120         TyCon, UniType, TauType(..), Unique, CoreExpr, PlainCoreExpr(..)
121
122         IF_ATTACK_PRAGMAS(COMMA tagOf_PrimOp)
123         IF_ATTACK_PRAGMAS(COMMA mkStatePrimTy)
124
125 #ifndef __GLASGOW_HASKELL__
126         ,TAG_
127 #endif
128     ) where
129
130 #ifdef DPH
131 import TyPod
132 import TyProcs
133 #endif {- Data Parallel Haskell -}
134
135 import PrelFuns         -- help functions, types and things
136 import PrimKind
137
138 import TysPrim          -- TYPES
139 import TysWiredIn
140 import PrelVals         -- VALUES
141 import PrimOps          -- PRIMITIVE OPS
142
143 import AbsUniType       ( getTyConDataCons, TyCon
144                           IF_ATTACK_PRAGMAS(COMMA cmpTyCon)
145                         )
146 import CmdLineOpts      ( GlobalSwitch(..) )
147 import FiniteMap
148 import Id               ( Id )
149 --OLD:import NameEnv
150 import Maybes
151 import Unique           -- *Key stuff
152 import Util
153 \end{code}
154
155 This little devil is too small to merit its own ``TyFun'' module:
156
157 \begin{code}
158 mkFunTy = UniFun
159 \end{code}
160
161 %************************************************************************
162 %*                                                                      *
163 \subsection[builtinNameInfo]{Lookup built-in names}
164 %*                                                                      *
165 %************************************************************************
166
167 We have two ``builtin name funs,'' one to look up @TyCons@ and
168 @Classes@, the other to look up values.
169
170 \begin{code}
171 builtinNameInfo :: (GlobalSwitch -> Bool)       -- access to global cmd-line flags
172                 -> (FAST_STRING -> Maybe Name,  -- name lookup fn for values
173                     FAST_STRING -> Maybe Name)  -- name lookup fn for tycons/classes
174
175 builtinNameInfo switch_is_on
176   = (init_val_lookup_fn, init_tc_lookup_fn)
177   where
178     --
179     -- values (including data constructors)
180     --
181     init_val_lookup_fn
182       = if      switch_is_on HideBuiltinNames then
183                 (\ x -> Nothing)
184         else if switch_is_on HideMostBuiltinNames then
185                 lookupFM (listToFM min_val_assoc_list)
186                 -- OLD: mkStringLookupFn min_val_assoc_list False{-not pre-sorted-}
187         else
188                 lookupFM (listToFM (concat list_of_val_assoc_lists))
189                 -- mkStringLookupFn (concat list_of_val_assoc_lists) False{-not pre-sorted-}
190
191     min_val_assoc_list          -- this is an ad-hoc list; what "happens"
192         =  totally_wired_in_Ids -- to be needed (when compiling bits of
193         ++ unboxed_ops          -- Prelude).
194         ++ (concat (map pcDataConNameInfo min_nonprim_tycon_list))
195
196     -- We let a lot of "non-standard" values be visible, so that we
197     -- can make sense of them in interface pragmas.  It's cool, though
198     -- -- they all have "non-standard" names, so they won't get past
199     -- the parser in user code.
200     list_of_val_assoc_lists
201         = [ -- each list is empty or all there
202
203             totally_wired_in_Ids,
204
205             concat (map pcDataConNameInfo data_tycons),
206
207             unboxed_ops,
208
209             if switch_is_on ForConcurrent then parallel_vals else []
210           ]
211
212     --
213     -- type constructors and classes
214     --
215     init_tc_lookup_fn
216       = if      switch_is_on HideBuiltinNames then
217                 (\ x -> Nothing)
218         else if switch_is_on HideMostBuiltinNames then
219                 lookupFM (listToFM min_tc_assoc_list)
220                 --OLD: mkStringLookupFn min_tc_assoc_list False{-not pre-sorted-}
221         else
222                 lookupFM (listToFM (
223                 -- OLD: mkStringLookupFn
224                     map pcTyConNameInfo (data_tycons ++ synonym_tycons)
225                     ++ std_tycon_list -- TyCons not quite so wired in
226                     ++ std_class_list
227                     ++ prim_tys))
228                     -- The prim_tys,etc., are OK, because they all
229                     -- have "non-standard" names (and we really
230                     -- want them for interface pragmas).
231                   --OLD: False{-not pre-sorted-}
232
233     min_tc_assoc_list   -- again, pretty ad-hoc
234         = prim_tys ++ (map pcTyConNameInfo min_nonprim_tycon_list)
235 --HA!     ++ std_class_list -- no harm in this
236
237 min_nonprim_tycon_list -- used w/ HideMostBuiltinNames
238   = [ boolTyCon,
239       cmpTagTyCon,
240       charTyCon,
241       intTyCon,
242       floatTyCon,
243       doubleTyCon,
244       integerTyCon,
245       ratioTyCon,
246       liftTyCon,
247       return2GMPsTyCon, -- ADR asked for these last two (WDP 94/11)
248       returnIntAndGMPTyCon ]
249
250 -- sigh: I (WDP) think these should be local defns
251 -- but you cannot imagine how bad it is for speed (w/ GHC)
252 prim_tys    = map pcTyConNameInfo prim_tycons
253
254 -- values
255
256 totally_wired_in_Ids
257   = [(SLIT(":"),                WiredInVal consDataCon),
258      (SLIT("error"),            WiredInVal eRROR_ID),
259      (SLIT("patError#"),        WiredInVal pAT_ERROR_ID), -- occurs in i/faces
260      (SLIT("parError#"),        WiredInVal pAR_ERROR_ID), -- ditto
261      (SLIT("_trace"),           WiredInVal tRACE_ID),
262
263      -- now the foldr/build Ids, which need to be built in
264      -- because they have magic unfoldings
265      (SLIT("_build"),           WiredInVal buildId),
266      (SLIT("_augment"),         WiredInVal augmentId),
267      (SLIT("foldl"),            WiredInVal foldlId),
268      (SLIT("foldr"),            WiredInVal foldrId),
269      (SLIT("unpackAppendPS#"),  WiredInVal unpackCStringAppendId),
270      (SLIT("unpackFoldrPS#"),   WiredInVal unpackCStringFoldrId),
271
272      (SLIT("_runST"),           WiredInVal runSTId),
273      (SLIT("_seq_"),            WiredInVal seqId),  -- yes, used in sequential-land, too
274                                                     -- WDP 95/11
275     (SLIT("realWorld#"),        WiredInVal realWorldPrimId)
276     ]
277
278 parallel_vals
279   =[(SLIT("_par_"),             WiredInVal parId),
280     (SLIT("_fork_"),            WiredInVal forkId)
281 #ifdef GRAN
282     ,
283     (SLIT("_parLocal_"),        WiredInVal parLocalId),
284     (SLIT("_parGlobal_"),       WiredInVal parGlobalId)
285     -- Add later:
286     -- (SLIT("_parAt_"),        WiredInVal parAtId)
287     -- (SLIT("_parAtForNow_"),  WiredInVal parAtForNowId)
288     -- (SLIT("_copyable_"),     WiredInVal copyableId)
289     -- (SLIT("_noFollow_"),     WiredInVal noFollowId)
290 #endif {-GRAN-}
291    ]
292
293 unboxed_ops
294   = (map primOpNameInfo lots_of_primops)
295    ++
296     -- plus some of the same ones but w/ different names
297    [case (primOpNameInfo IntAddOp)      of (_,n) -> (SLIT("+#"),   n),
298     case (primOpNameInfo IntSubOp)      of (_,n) -> (SLIT("-#"),   n),
299     case (primOpNameInfo IntMulOp)      of (_,n) -> (SLIT("*#"),   n),
300     case (primOpNameInfo IntGtOp)       of (_,n) -> (SLIT(">#"),   n),
301     case (primOpNameInfo IntGeOp)       of (_,n) -> (SLIT(">=#"),  n),
302     case (primOpNameInfo IntEqOp)       of (_,n) -> (SLIT("==#"),  n),
303     case (primOpNameInfo IntNeOp)       of (_,n) -> (SLIT("/=#"),  n),
304     case (primOpNameInfo IntLtOp)       of (_,n) -> (SLIT("<#"),   n),
305     case (primOpNameInfo IntLeOp)       of (_,n) -> (SLIT("<=#"),  n),
306     case (primOpNameInfo DoubleAddOp)   of (_,n) -> (SLIT("+##"),  n),
307     case (primOpNameInfo DoubleSubOp)   of (_,n) -> (SLIT("-##"),  n),
308     case (primOpNameInfo DoubleMulOp)   of (_,n) -> (SLIT("*##"),  n),
309     case (primOpNameInfo DoubleDivOp)   of (_,n) -> (SLIT("/##"),  n),
310     case (primOpNameInfo DoublePowerOp) of (_,n) -> (SLIT("**##"), n),
311     case (primOpNameInfo DoubleGtOp)    of (_,n) -> (SLIT(">##"),  n),
312     case (primOpNameInfo DoubleGeOp)    of (_,n) -> (SLIT(">=##"), n),
313     case (primOpNameInfo DoubleEqOp)    of (_,n) -> (SLIT("==##"), n),
314     case (primOpNameInfo DoubleNeOp)    of (_,n) -> (SLIT("/=##"), n),
315     case (primOpNameInfo DoubleLtOp)    of (_,n) -> (SLIT("<##"),  n),
316     case (primOpNameInfo DoubleLeOp)    of (_,n) -> (SLIT("<=##"), n)]
317
318 prim_tycons
319   = [addrPrimTyCon,
320      arrayPrimTyCon,
321      byteArrayPrimTyCon,
322      charPrimTyCon,
323      doublePrimTyCon,
324      floatPrimTyCon,
325      intPrimTyCon,
326      mallocPtrPrimTyCon,
327      mutableArrayPrimTyCon,
328      mutableByteArrayPrimTyCon,
329      synchVarPrimTyCon,
330      realWorldTyCon,
331      stablePtrPrimTyCon,
332      statePrimTyCon,
333      wordPrimTyCon
334     ]
335
336 std_tycon_list
337   = let
338         swizzle_over (mod, nm, key, arity, is_data)
339           = let
340                 fname = mkPreludeCoreName mod nm
341             in
342             (nm, PreludeTyCon key fname arity is_data)
343     in
344     map swizzle_over
345         [--(pRELUDE_IO,    SLIT("Request"),  requestTyConKey,  0, True),
346 --OLD:   (pRELUDE_IO,      SLIT("Response"), responseTyConKey, 0, True),
347          (pRELUDE_IO,      SLIT("Dialogue"), dialogueTyConKey, 0, False),
348          (SLIT("PreludeMonadicIO"), SLIT("IO"), iOTyConKey,    1, False)
349         ]
350
351 -- Several of these are non-std, but they have non-std
352 -- names, so they won't get past the parser in user code
353 -- (but will be visible for interface-pragma purposes).
354
355 data_tycons
356   = [addrTyCon,
357      boolTyCon,
358 --   byteArrayTyCon,
359      charTyCon,
360      cmpTagTyCon,
361      doubleTyCon,
362      floatTyCon,
363      intTyCon,
364      integerTyCon,
365      liftTyCon,
366      mallocPtrTyCon,
367 --   mutableArrayTyCon,
368 --   mutableByteArrayTyCon,
369      ratioTyCon,
370      return2GMPsTyCon,
371      returnIntAndGMPTyCon,
372      stablePtrTyCon,
373      stateAndAddrPrimTyCon,
374      stateAndArrayPrimTyCon,
375      stateAndByteArrayPrimTyCon,
376      stateAndCharPrimTyCon,
377      stateAndDoublePrimTyCon,
378      stateAndFloatPrimTyCon,
379      stateAndIntPrimTyCon,
380      stateAndMallocPtrPrimTyCon,
381      stateAndMutableArrayPrimTyCon,
382      stateAndMutableByteArrayPrimTyCon,
383      stateAndSynchVarPrimTyCon,
384      stateAndPtrPrimTyCon,
385      stateAndStablePtrPrimTyCon,
386      stateAndWordPrimTyCon,
387      stateTyCon,
388      wordTyCon
389 #ifdef DPH
390      ,podTyCon
391 #endif {- Data Parallel Haskell -}
392     ]
393
394 synonym_tycons
395   = [primIoTyCon,
396      rationalTyCon,
397      stTyCon,
398      stringTyCon]
399
400 std_class_list
401   = let
402         swizzle_over (str, key)
403           = (str, PreludeClass key (mkPreludeCoreName pRELUDE_CORE str))
404     in
405     map swizzle_over
406         [(SLIT("Eq"),           eqClassKey),
407          (SLIT("Ord"),          ordClassKey),
408          (SLIT("Num"),          numClassKey),
409          (SLIT("Real"),         realClassKey),
410          (SLIT("Integral"),     integralClassKey),
411          (SLIT("Fractional"),   fractionalClassKey),
412          (SLIT("Floating"),     floatingClassKey),
413          (SLIT("RealFrac"),     realFracClassKey),
414          (SLIT("RealFloat"),    realFloatClassKey),
415          (SLIT("Ix"),           ixClassKey),
416          (SLIT("Enum"),         enumClassKey),
417          (SLIT("Text"),         textClassKey),
418          (SLIT("_CCallable"),   cCallableClassKey),
419          (SLIT("_CReturnable"), cReturnableClassKey),
420          (SLIT("Binary"),       binaryClassKey)
421 #ifdef DPH
422          , (SLIT("Pid"),        pidClassKey)
423          , (SLIT("Processor"),processorClassKey)
424 #endif {- Data Parallel Haskell -}
425         ]
426
427 lots_of_primops
428   = [   CharGtOp,
429         CharGeOp,
430         CharEqOp,
431         CharNeOp,
432         CharLtOp,
433         CharLeOp,
434         IntGtOp,
435         IntGeOp,
436         IntEqOp,
437         IntNeOp,
438         IntLtOp,
439         IntLeOp,
440         WordGtOp,
441         WordGeOp,
442         WordEqOp,
443         WordNeOp,
444         WordLtOp,
445         WordLeOp,
446         AddrGtOp,
447         AddrGeOp,
448         AddrEqOp,
449         AddrNeOp,
450         AddrLtOp,
451         AddrLeOp,
452         FloatGtOp,
453         FloatGeOp,
454         FloatEqOp,
455         FloatNeOp,
456         FloatLtOp,
457         FloatLeOp,
458         DoubleGtOp,
459         DoubleGeOp,
460         DoubleEqOp,
461         DoubleNeOp,
462         DoubleLtOp,
463         DoubleLeOp,
464         OrdOp,
465         ChrOp,
466         IntAddOp,
467         IntSubOp,
468         IntMulOp,
469         IntQuotOp,
470         IntRemOp,
471         IntNegOp,
472         AndOp,
473         OrOp,
474         NotOp,
475         SllOp,
476         SraOp,
477         SrlOp,
478         ISllOp,
479         ISraOp,
480         ISrlOp,
481         Int2WordOp,
482         Word2IntOp,
483         Int2AddrOp,
484         Addr2IntOp,
485         FloatAddOp,
486         FloatSubOp,
487         FloatMulOp,
488         FloatDivOp,
489         FloatNegOp,
490         Float2IntOp,
491         Int2FloatOp,
492         FloatExpOp,
493         FloatLogOp,
494         FloatSqrtOp,
495         FloatSinOp,
496         FloatCosOp,
497         FloatTanOp,
498         FloatAsinOp,
499         FloatAcosOp,
500         FloatAtanOp,
501         FloatSinhOp,
502         FloatCoshOp,
503         FloatTanhOp,
504         FloatPowerOp,
505         DoubleAddOp,
506         DoubleSubOp,
507         DoubleMulOp,
508         DoubleDivOp,
509         DoubleNegOp,
510         Double2IntOp,
511         Int2DoubleOp,
512         Double2FloatOp,
513         Float2DoubleOp,
514         DoubleExpOp,
515         DoubleLogOp,
516         DoubleSqrtOp,
517         DoubleSinOp,
518         DoubleCosOp,
519         DoubleTanOp,
520         DoubleAsinOp,
521         DoubleAcosOp,
522         DoubleAtanOp,
523         DoubleSinhOp,
524         DoubleCoshOp,
525         DoubleTanhOp,
526         DoublePowerOp,
527         IntegerAddOp,
528         IntegerSubOp,
529         IntegerMulOp,
530         IntegerQuotRemOp,
531         IntegerDivModOp,
532         IntegerNegOp,
533         IntegerCmpOp,
534         Integer2IntOp,
535         Int2IntegerOp,
536         Word2IntegerOp,
537         Addr2IntegerOp,
538         FloatEncodeOp,
539         FloatDecodeOp,
540         DoubleEncodeOp,
541         DoubleDecodeOp,
542         NewArrayOp,
543         NewByteArrayOp CharKind,
544         NewByteArrayOp IntKind,
545         NewByteArrayOp AddrKind,
546         NewByteArrayOp FloatKind,
547         NewByteArrayOp DoubleKind,
548         SameMutableArrayOp,
549         SameMutableByteArrayOp,
550         ReadArrayOp,
551         WriteArrayOp,
552         IndexArrayOp,
553         ReadByteArrayOp CharKind,
554         ReadByteArrayOp IntKind,
555         ReadByteArrayOp AddrKind,
556         ReadByteArrayOp FloatKind,
557         ReadByteArrayOp DoubleKind,
558         WriteByteArrayOp CharKind,
559         WriteByteArrayOp IntKind,
560         WriteByteArrayOp AddrKind,
561         WriteByteArrayOp FloatKind,
562         WriteByteArrayOp DoubleKind,
563         IndexByteArrayOp CharKind,
564         IndexByteArrayOp IntKind,
565         IndexByteArrayOp AddrKind,
566         IndexByteArrayOp FloatKind,
567         IndexByteArrayOp DoubleKind,
568         IndexOffAddrOp CharKind,
569         IndexOffAddrOp IntKind,
570         IndexOffAddrOp AddrKind,
571         IndexOffAddrOp FloatKind,
572         IndexOffAddrOp DoubleKind,
573         UnsafeFreezeArrayOp,
574         UnsafeFreezeByteArrayOp,
575         NewSynchVarOp,
576         ReadArrayOp,
577         TakeMVarOp,
578         PutMVarOp,
579         ReadIVarOp,
580         WriteIVarOp,
581         MakeStablePtrOp,
582         DeRefStablePtrOp,
583         ReallyUnsafePtrEqualityOp,
584         ErrorIOPrimOp,
585 #ifdef GRAN
586         ParGlobalOp,
587         ParLocalOp,
588 #endif {-GRAN-}
589         SeqOp,
590         ParOp,
591         ForkOp,
592         DelayOp,
593         WaitOp
594     ]
595 \end{code}
596
597 \begin{code}
598 readUnfoldingPrimOp :: FAST_STRING -> PrimOp
599
600 readUnfoldingPrimOp
601   = let
602         -- "reverse" lookup table
603         tbl = map (\ o -> let { (str,_) = primOpNameInfo o } in (str, o)) lots_of_primops
604     in
605     \ str -> case [ op | (s, op) <- tbl, s == str ] of
606                (op:_) -> op
607 #ifdef DEBUG
608                [] -> panic "readUnfoldingPrimOp" -- ++ _UNPK_ str ++"::"++show (map fst tbl))
609 #endif
610 \end{code}
611
612 Make table entries for various things:
613 \begin{code}
614 pcTyConNameInfo :: TyCon -> (FAST_STRING, Name)
615 pcTyConNameInfo tycon
616   = (getOccurrenceName tycon, WiredInTyCon tycon)
617
618 pcDataConNameInfo :: TyCon -> [(FAST_STRING, Name)]
619 pcDataConNameInfo tycon
620   = -- slurp out its data constructors...
621     [(getOccurrenceName con, WiredInVal con) | con <- getTyConDataCons tycon]
622 \end{code}