[project @ 2002-01-09 12:41:45 by simonmar]
[ghc-hetmet.git] / ghc / compiler / prelude / PrelNames.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[PrelNames]{Definitions of prelude modules}
5
6 The strings identify built-in prelude modules.  They are
7 defined here so as to avod 
8
9 [oh dear, looks like the recursive module monster caught up with
10  and gobbled whoever was writing the above :-) -- SOF ]
11
12 \begin{code}
13 module PrelNames (
14         Unique, Uniquable(..), hasKey,  -- Re-exported for convenience
15
16         -----------------------------------------------------------
17         module PrelNames,       -- A huge bunch of (a) RdrNames, e.g. intTyCon_RDR
18                                 --                 (b) Uniques   e.g. intTyConKey
19                                 -- So many that we export them all
20
21         -----------------------------------------------------------
22         knownKeyNames, 
23         mkTupNameStr, mkTupConRdrName,
24
25         ------------------------------------------------------------
26         -- Goups of classes and types
27         needsDataDeclCtxtClassKeys, cCallishClassKeys, noDictClassKeys,
28         fractionalClassKeys, numericClassKeys, standardClassKeys,
29         derivingOccurrences,    -- For a given class C, this tells what other 
30         derivableClassKeys,     -- things are needed as a result of a 
31                                 -- deriving(C) clause
32         numericTyKeys, cCallishTyKeys,
33
34         mkUnboundName, isUnboundName
35     ) where
36
37 #include "HsVersions.h"
38
39 import Module     ( ModuleName, mkPrelModule, mkHomeModule, mkModuleName )
40 import OccName    ( NameSpace, UserFS, varName, dataName, tcName, clsName, 
41                     mkKindOccFS, mkOccFS
42                   )
43 import RdrName    ( RdrName, mkOrig, mkUnqual )
44 import UniqFM
45 import Unique     ( Unique, Uniquable(..), hasKey,
46                     mkPreludeMiscIdUnique, mkPreludeDataConUnique,
47                     mkPreludeTyConUnique, mkPreludeClassUnique,
48                     mkTupleTyConUnique
49                   ) 
50 import BasicTypes ( Boxity(..), Arity )
51 import UniqFM     ( UniqFM, listToUFM )
52 import Name       ( Name, mkLocalName, mkKnownKeyGlobal, nameRdrName )
53 import RdrName    ( rdrNameOcc )
54 import SrcLoc     ( builtinSrcLoc, noSrcLoc )
55 import Util       ( nOfThem )
56 import Panic      ( panic )
57 \end{code}
58
59
60 %************************************************************************
61 %*                                                                      *
62 \subsection{Local Names}
63 %*                                                                      *
64 %************************************************************************
65
66 This *local* name is used by the interactive stuff
67
68 \begin{code}
69 itName uniq = mkLocalName uniq (mkOccFS varName SLIT("it")) noSrcLoc
70 \end{code}
71
72 \begin{code}
73 -- mkUnboundName makes a place-holder Name; it shouldn't be looked at except possibly
74 -- during compiler debugging.
75 mkUnboundName :: RdrName -> Name
76 mkUnboundName rdr_name = mkLocalName unboundKey (rdrNameOcc rdr_name) builtinSrcLoc
77
78 isUnboundName :: Name -> Bool
79 isUnboundName name = name `hasKey` unboundKey
80 \end{code}
81
82
83 %************************************************************************
84 %*                                                                      *
85 \subsection{Known key Names}
86 %*                                                                      *
87 %************************************************************************
88
89 This section tells what the compiler knows about the assocation of
90 names with uniques.  These ones are the *non* wired-in ones.  The
91 wired in ones are defined in TysWiredIn etc.
92
93 \begin{code}
94 knownKeyNames :: [Name]
95 knownKeyNames
96  =  [
97         -- Type constructors (synonyms especially)
98         ioTyConName, ioDataConName,
99         mainName,
100         orderingTyConName,
101         rationalTyConName,
102         ratioDataConName,
103         ratioTyConName,
104         byteArrayTyConName,
105         mutableByteArrayTyConName,
106         foreignObjTyConName,
107         foreignPtrTyConName,
108         bcoPrimTyConName,
109         stablePtrTyConName,
110         stablePtrDataConName,
111
112         --  Classes.  *Must* include:
113         --      classes that are grabbed by key (e.g., eqClassKey)
114         --      classes in "Class.standardClassKeys" (quite a few)
115         eqClassName,                    -- mentioned, derivable
116         ordClassName,                   -- derivable
117         boundedClassName,               -- derivable
118         numClassName,                   -- mentioned, numeric
119         enumClassName,                  -- derivable
120         monadClassName,
121         monadPlusClassName,
122         functorClassName,
123         showClassName,                  -- derivable
124         realClassName,                  -- numeric
125         integralClassName,              -- numeric
126         fractionalClassName,            -- numeric
127         floatingClassName,              -- numeric
128         realFracClassName,              -- numeric
129         realFloatClassName,             -- numeric
130         readClassName,                  -- derivable
131         ixClassName,                    -- derivable (but it isn't Prelude.Ix; hmmm)
132         cCallableClassName,             -- mentioned, ccallish
133         cReturnableClassName,           -- mentioned, ccallish
134
135         -- ClassOps 
136         fromIntegerName,
137         negateName,
138         geName,
139         minusName,
140         enumFromName,
141         enumFromThenName,
142         enumFromToName,
143         enumFromThenToName,
144         fromEnumName,
145         toEnumName,
146         eqName,
147         thenMName,
148         returnMName,
149         failMName,
150         fromRationalName,
151     
152         deRefStablePtrName,
153         newStablePtrName,
154         bindIOName,
155         returnIOName,
156         failIOName,
157
158         -- Strings and lists
159         mapName,
160         appendName,
161         unpackCStringName,
162         unpackCStringListName,
163         unpackCStringAppendName,
164         unpackCStringFoldrName,
165         unpackCStringUtf8Name,
166
167         -- List operations
168         concatName,
169         filterName,
170         zipName,
171         foldrName,
172         buildName,
173         augmentName,
174
175         -- FFI primitive types that are not wired-in.
176         int8TyConName,
177         int16TyConName,
178         int32TyConName,
179         int64TyConName,
180         word8TyConName,
181         word16TyConName,
182         word32TyConName,
183         word64TyConName,
184
185         -- Others
186         unsafeCoerceName,
187         otherwiseIdName,
188         plusIntegerName,
189         timesIntegerName,
190         eqStringName,
191         assertName,
192         runSTRepName,
193         printName,
194         splitIdName, fstIdName, sndIdName       -- Used by splittery
195     ]
196 \end{code}
197
198
199 %************************************************************************
200 %*                                                                      *
201 \subsection{Module names}
202 %*                                                                      *
203 %************************************************************************
204
205 \begin{code}
206 pRELUDE_Name      = mkModuleName "Prelude"
207 pREL_GHC_Name     = mkModuleName "PrelGHC"         -- Primitive types and values
208 pREL_BASE_Name    = mkModuleName "PrelBase"
209 pREL_ENUM_Name    = mkModuleName "PrelEnum"
210 pREL_SHOW_Name    = mkModuleName "PrelShow"
211 pREL_READ_Name    = mkModuleName "PrelRead"
212 pREL_NUM_Name     = mkModuleName "PrelNum"
213 pREL_LIST_Name    = mkModuleName "PrelList"
214 pREL_TUP_Name     = mkModuleName "PrelTup"
215 pREL_PACK_Name    = mkModuleName "PrelPack"
216 pREL_CONC_Name    = mkModuleName "PrelConc"
217 pREL_IO_BASE_Name = mkModuleName "PrelIOBase"
218 pREL_IO_Name      = mkModuleName "PrelIO"
219 pREL_ST_Name      = mkModuleName "PrelST"
220 pREL_ARR_Name     = mkModuleName "PrelArr"
221 pREL_BYTEARR_Name = mkModuleName "PrelByteArr"
222 pREL_FOREIGN_Name = mkModuleName "PrelForeign"
223 pREL_STABLE_Name  = mkModuleName "PrelStable"
224 pREL_SPLIT_Name   = mkModuleName "PrelSplit"
225 pREL_ADDR_Name    = mkModuleName "PrelAddr"
226 pREL_PTR_Name     = mkModuleName "PrelPtr"
227 pREL_ERR_Name     = mkModuleName "PrelErr"
228 pREL_REAL_Name    = mkModuleName "PrelReal"
229 pREL_FLOAT_Name   = mkModuleName "PrelFloat"
230
231 pREL_MAIN_Name    = mkModuleName "PrelMain"
232 mAIN_Name         = mkModuleName "Main"
233 pREL_INT_Name     = mkModuleName "PrelInt"
234 pREL_WORD_Name    = mkModuleName "PrelWord"
235
236 fOREIGNOBJ_Name   = mkModuleName "ForeignObj"
237 aDDR_Name         = mkModuleName "Addr"
238
239 gLA_EXTS_Name   = mkModuleName "GlaExts"
240
241 pREL_GHC        = mkPrelModule pREL_GHC_Name
242 pREL_BASE       = mkPrelModule pREL_BASE_Name
243 pREL_ADDR       = mkPrelModule pREL_ADDR_Name
244 pREL_PTR        = mkPrelModule pREL_PTR_Name
245 pREL_STABLE     = mkPrelModule pREL_STABLE_Name
246 pREL_IO_BASE    = mkPrelModule pREL_IO_BASE_Name
247 pREL_PACK       = mkPrelModule pREL_PACK_Name
248 pREL_ERR        = mkPrelModule pREL_ERR_Name
249 pREL_NUM        = mkPrelModule pREL_NUM_Name
250 pREL_REAL       = mkPrelModule pREL_REAL_Name
251 pREL_FLOAT      = mkPrelModule pREL_FLOAT_Name
252 pRELUDE         = mkPrelModule pRELUDE_Name
253
254 iNTERACTIVE     = mkHomeModule (mkModuleName "$Interactive")
255 \end{code}
256
257 %************************************************************************
258 %*                                                                      *
259 \subsection{Constructing the names of tuples
260 %*                                                                      *
261 %************************************************************************
262
263 \begin{code}
264 mkTupNameStr :: Boxity -> Int -> (ModuleName, UserFS)
265
266 mkTupNameStr Boxed 0 = (pREL_BASE_Name, SLIT("()"))
267 mkTupNameStr Boxed 1 = panic "Name.mkTupNameStr: 1 ???"
268 mkTupNameStr Boxed 2 = (pREL_TUP_Name, _PK_ "(,)")   -- not strictly necessary
269 mkTupNameStr Boxed 3 = (pREL_TUP_Name, _PK_ "(,,)")  -- ditto
270 mkTupNameStr Boxed 4 = (pREL_TUP_Name, _PK_ "(,,,)") -- ditto
271 mkTupNameStr Boxed n = (pREL_TUP_Name, _PK_ ("(" ++ nOfThem (n-1) ',' ++ ")"))
272
273 mkTupNameStr Unboxed 0 = panic "Name.mkUbxTupNameStr: 0 ???"
274 mkTupNameStr Unboxed 1 = (pREL_GHC_Name, _PK_ "(# #)") -- 1 and 0 both make sense!!!
275 mkTupNameStr Unboxed 2 = (pREL_GHC_Name, _PK_ "(#,#)")
276 mkTupNameStr Unboxed 3 = (pREL_GHC_Name, _PK_ "(#,,#)")
277 mkTupNameStr Unboxed 4 = (pREL_GHC_Name, _PK_ "(#,,,#)")
278 mkTupNameStr Unboxed n = (pREL_GHC_Name, _PK_ ("(#" ++ nOfThem (n-1) ',' ++ "#)"))
279
280 mkTupConRdrName :: NameSpace -> Boxity -> Arity -> RdrName 
281 mkTupConRdrName space boxity arity   = case mkTupNameStr boxity arity of
282                                           (mod, occ) -> mkOrig space mod occ
283 \end{code}
284
285
286 %************************************************************************
287 %*                                                                      *
288 \subsection{Unqualified RdrNames}
289 %*                                                                      *
290 %************************************************************************
291
292 \begin{code}
293 main_RDR_Unqual :: RdrName
294 main_RDR_Unqual = mkUnqual varName SLIT("main")
295 -- Don't get a RdrName from PrelNames.mainName, because nameRdrName
296 -- gets an Orig RdrName, and we want a Qual or Unqual one.  An Unqual
297 -- one will do fine.
298 \end{code}
299
300
301 %************************************************************************
302 %*                                                                      *
303 \subsection{Commonly-used RdrNames}
304 %*                                                                      *
305 %************************************************************************
306
307 Many of these Names are not really "built in", but some parts of the
308 compiler (notably the deriving mechanism) need to mention their names,
309 and it's convenient to write them all down in one place.
310
311 \begin{code}
312 mainName = varQual mAIN_Name SLIT("main") mainKey
313
314 -- Stuff from PrelGHC
315 usOnceTyConName  = kindQual SLIT(".") usOnceTyConKey
316 usManyTyConName  = kindQual SLIT("!") usManyTyConKey
317 superKindName    = kindQual SLIT("KX") kindConKey
318 superBoxityName  = kindQual SLIT("BX") boxityConKey
319 liftedConName    = kindQual SLIT("*") liftedConKey
320 unliftedConName  = kindQual SLIT("#") unliftedConKey
321 openKindConName  = kindQual SLIT("?") anyBoxConKey
322 usageKindConName = kindQual SLIT("$") usageConKey
323 typeConName      = kindQual SLIT("Type") typeConKey
324
325 funTyConName                  = tcQual  pREL_GHC_Name SLIT("(->)")  funTyConKey
326 charPrimTyConName             = tcQual  pREL_GHC_Name SLIT("Char#") charPrimTyConKey 
327 intPrimTyConName              = tcQual  pREL_GHC_Name SLIT("Int#") intPrimTyConKey 
328 int32PrimTyConName            = tcQual  pREL_GHC_Name SLIT("Int32#") int32PrimTyConKey 
329 int64PrimTyConName            = tcQual  pREL_GHC_Name SLIT("Int64#") int64PrimTyConKey 
330 wordPrimTyConName             = tcQual  pREL_GHC_Name SLIT("Word#") wordPrimTyConKey 
331 word32PrimTyConName           = tcQual  pREL_GHC_Name SLIT("Word32#") word32PrimTyConKey 
332 word64PrimTyConName           = tcQual  pREL_GHC_Name SLIT("Word64#") word64PrimTyConKey 
333 addrPrimTyConName             = tcQual  pREL_GHC_Name SLIT("Addr#") addrPrimTyConKey 
334 floatPrimTyConName            = tcQual  pREL_GHC_Name SLIT("Float#") floatPrimTyConKey 
335 doublePrimTyConName           = tcQual  pREL_GHC_Name SLIT("Double#") doublePrimTyConKey 
336 statePrimTyConName            = tcQual  pREL_GHC_Name SLIT("State#") statePrimTyConKey 
337 realWorldTyConName            = tcQual  pREL_GHC_Name SLIT("RealWorld") realWorldTyConKey 
338 arrayPrimTyConName            = tcQual  pREL_GHC_Name SLIT("Array#") arrayPrimTyConKey 
339 byteArrayPrimTyConName        = tcQual  pREL_GHC_Name SLIT("ByteArray#") byteArrayPrimTyConKey 
340 mutableArrayPrimTyConName     = tcQual  pREL_GHC_Name SLIT("MutableArray#") mutableArrayPrimTyConKey 
341 mutableByteArrayPrimTyConName = tcQual  pREL_GHC_Name SLIT("MutableByteArray#") mutableByteArrayPrimTyConKey 
342 mutVarPrimTyConName           = tcQual  pREL_GHC_Name SLIT("MutVar#") mutVarPrimTyConKey 
343 mVarPrimTyConName             = tcQual  pREL_GHC_Name SLIT("MVar#") mVarPrimTyConKey 
344 stablePtrPrimTyConName        = tcQual  pREL_GHC_Name SLIT("StablePtr#") stablePtrPrimTyConKey 
345 stableNamePrimTyConName       = tcQual  pREL_GHC_Name SLIT("StableName#") stableNamePrimTyConKey 
346 foreignObjPrimTyConName       = tcQual  pREL_GHC_Name SLIT("ForeignObj#") foreignObjPrimTyConKey 
347 bcoPrimTyConName              = tcQual  pREL_GHC_Name SLIT("BCO#") bcoPrimTyConKey 
348 weakPrimTyConName             = tcQual  pREL_GHC_Name SLIT("Weak#") weakPrimTyConKey 
349 threadIdPrimTyConName         = tcQual  pREL_GHC_Name SLIT("ThreadId#") threadIdPrimTyConKey 
350 cCallableClassName            = clsQual pREL_GHC_Name SLIT("CCallable") cCallableClassKey
351 cReturnableClassName          = clsQual pREL_GHC_Name SLIT("CReturnable") cReturnableClassKey
352
353 -- PrelBase data types and constructors
354 charTyConName     = tcQual   pREL_BASE_Name SLIT("Char") charTyConKey
355 charDataConName   = dataQual pREL_BASE_Name SLIT("C#") charDataConKey
356 intTyConName      = tcQual   pREL_BASE_Name SLIT("Int") intTyConKey
357 intDataConName    = dataQual pREL_BASE_Name SLIT("I#") intDataConKey
358 orderingTyConName = tcQual   pREL_BASE_Name SLIT("Ordering") orderingTyConKey
359 boolTyConName     = tcQual   pREL_BASE_Name SLIT("Bool") boolTyConKey
360 falseDataConName  = dataQual pREL_BASE_Name SLIT("False") falseDataConKey
361 trueDataConName   = dataQual pREL_BASE_Name SLIT("True") trueDataConKey
362 listTyConName     = tcQual   pREL_BASE_Name SLIT("[]") listTyConKey
363 nilDataConName    = dataQual pREL_BASE_Name SLIT("[]") nilDataConKey
364 consDataConName   = dataQual pREL_BASE_Name SLIT(":") consDataConKey
365
366 -- PrelTup
367 fstIdName         = varQual pREL_TUP_Name SLIT("fst") fstIdKey
368 sndIdName         = varQual pREL_TUP_Name SLIT("snd") sndIdKey
369
370 -- Generics
371 crossTyConName     = tcQual   pREL_BASE_Name SLIT(":*:") crossTyConKey
372 crossDataConName   = dataQual pREL_BASE_Name SLIT(":*:") crossDataConKey
373 plusTyConName      = tcQual   pREL_BASE_Name SLIT(":+:") plusTyConKey
374 inlDataConName     = dataQual pREL_BASE_Name SLIT("Inl") inlDataConKey
375 inrDataConName     = dataQual pREL_BASE_Name SLIT("Inr") inrDataConKey
376 genUnitTyConName   = tcQual   pREL_BASE_Name SLIT("Unit") genUnitTyConKey
377 genUnitDataConName = dataQual pREL_BASE_Name SLIT("Unit") genUnitDataConKey
378
379 -- Random PrelBase functions
380 unsafeCoerceName  = varQual pREL_BASE_Name SLIT("unsafeCoerce") unsafeCoerceIdKey
381 otherwiseIdName   = varQual pREL_BASE_Name SLIT("otherwise") otherwiseIdKey
382 appendName        = varQual pREL_BASE_Name SLIT("++") appendIdKey
383 foldrName         = varQual pREL_BASE_Name SLIT("foldr") foldrIdKey
384 mapName           = varQual pREL_BASE_Name SLIT("map") mapIdKey
385 buildName         = varQual pREL_BASE_Name SLIT("build") buildIdKey
386 augmentName       = varQual pREL_BASE_Name SLIT("augment") augmentIdKey
387 eqStringName      = varQual pREL_BASE_Name SLIT("eqString") eqStringIdKey
388
389 -- Strings
390 unpackCStringName       = varQual pREL_BASE_Name SLIT("unpackCString#") unpackCStringIdKey
391 unpackCStringListName   = varQual pREL_BASE_Name SLIT("unpackCStringList#") unpackCStringListIdKey
392 unpackCStringAppendName = varQual pREL_BASE_Name SLIT("unpackAppendCString#") unpackCStringAppendIdKey
393 unpackCStringFoldrName  = varQual pREL_BASE_Name SLIT("unpackFoldrCString#") unpackCStringFoldrIdKey
394 unpackCStringUtf8Name   = varQual pREL_BASE_Name SLIT("unpackCStringUtf8#") unpackCStringUtf8IdKey
395
396 -- Classes Eq and Ord
397 eqClassName       = clsQual pREL_BASE_Name SLIT("Eq") eqClassKey
398 ordClassName      = clsQual pREL_BASE_Name SLIT("Ord") ordClassKey
399 eqName            = varQual  pREL_BASE_Name SLIT("==") eqClassOpKey
400 geName            = varQual  pREL_BASE_Name SLIT(">=") geClassOpKey
401
402 -- Class Monad
403 monadClassName     = clsQual pREL_BASE_Name SLIT("Monad") monadClassKey
404 monadPlusClassName = clsQual pREL_BASE_Name SLIT("MonadPlus") monadPlusClassKey
405 thenMName          = varQual pREL_BASE_Name SLIT(">>=") thenMClassOpKey
406 returnMName        = varQual pREL_BASE_Name SLIT("return") returnMClassOpKey
407 failMName          = varQual pREL_BASE_Name SLIT("fail") failMClassOpKey
408
409 -- Class Functor
410 functorClassName  = clsQual pREL_BASE_Name SLIT("Functor") functorClassKey
411
412 -- Class Show
413 showClassName     = clsQual pREL_SHOW_Name SLIT("Show") showClassKey
414
415 -- Class Read
416 readClassName     = clsQual pREL_READ_Name SLIT("Read") readClassKey
417
418 -- Module PrelNum
419 numClassName      = clsQual pREL_NUM_Name SLIT("Num") numClassKey
420 fromIntegerName   = varQual pREL_NUM_Name SLIT("fromInteger") fromIntegerClassOpKey
421 minusName         = varQual pREL_NUM_Name SLIT("-") minusClassOpKey
422 negateName        = varQual pREL_NUM_Name SLIT("negate") negateClassOpKey
423 plusIntegerName   = varQual pREL_NUM_Name SLIT("plusInteger") plusIntegerIdKey
424 timesIntegerName  = varQual pREL_NUM_Name SLIT("timesInteger") timesIntegerIdKey
425 integerTyConName  = tcQual  pREL_NUM_Name SLIT("Integer") integerTyConKey
426 smallIntegerDataConName = dataQual pREL_NUM_Name SLIT("S#") smallIntegerDataConKey
427 largeIntegerDataConName = dataQual pREL_NUM_Name SLIT("J#") largeIntegerDataConKey
428
429 -- PrelReal types and classes
430 rationalTyConName   = tcQual   pREL_REAL_Name  SLIT("Rational") rationalTyConKey
431 ratioTyConName      = tcQual   pREL_REAL_Name  SLIT("Ratio") ratioTyConKey
432 ratioDataConName    = dataQual pREL_REAL_Name  SLIT(":%") ratioDataConKey
433 realClassName       = clsQual  pREL_REAL_Name  SLIT("Real") realClassKey
434 integralClassName   = clsQual  pREL_REAL_Name  SLIT("Integral") integralClassKey
435 realFracClassName   = clsQual  pREL_REAL_Name  SLIT("RealFrac") realFracClassKey
436 fractionalClassName = clsQual  pREL_REAL_Name  SLIT("Fractional") fractionalClassKey
437 fromRationalName    = varQual  pREL_REAL_Name  SLIT("fromRational") fromRationalClassOpKey
438
439 -- PrelFloat classes
440 floatTyConName     = tcQual   pREL_FLOAT_Name SLIT("Float") floatTyConKey
441 floatDataConName   = dataQual pREL_FLOAT_Name SLIT("F#") floatDataConKey
442 doubleTyConName    = tcQual   pREL_FLOAT_Name SLIT("Double") doubleTyConKey
443 doubleDataConName  = dataQual pREL_FLOAT_Name SLIT("D#") doubleDataConKey
444 floatingClassName  = clsQual  pREL_FLOAT_Name SLIT("Floating") floatingClassKey
445 realFloatClassName = clsQual  pREL_FLOAT_Name SLIT("RealFloat") realFloatClassKey
446
447 -- Class Ix
448 ixClassName        = clsQual pREL_ARR_Name SLIT("Ix") ixClassKey
449
450 -- Class Enum
451 enumClassName      = clsQual pREL_ENUM_Name SLIT("Enum") enumClassKey
452 toEnumName         = varQual pREL_ENUM_Name SLIT("toEnum") toEnumClassOpKey
453 fromEnumName       = varQual pREL_ENUM_Name SLIT("fromEnum") fromEnumClassOpKey
454 enumFromName       = varQual pREL_ENUM_Name SLIT("enumFrom") enumFromClassOpKey
455 enumFromToName     = varQual pREL_ENUM_Name SLIT("enumFromTo") enumFromToClassOpKey
456 enumFromThenName   = varQual pREL_ENUM_Name SLIT("enumFromThen") enumFromThenClassOpKey
457 enumFromThenToName = varQual pREL_ENUM_Name SLIT("enumFromThenTo") enumFromThenToClassOpKey
458
459 -- Class Bounded
460 boundedClassName  = clsQual pREL_ENUM_Name SLIT("Bounded") boundedClassKey
461
462 -- List functions
463 concatName        = varQual pREL_LIST_Name SLIT("concat") concatIdKey
464 filterName        = varQual pREL_LIST_Name SLIT("filter") filterIdKey
465 zipName           = varQual pREL_LIST_Name SLIT("zip") zipIdKey
466
467 -- IOBase things
468 ioTyConName       = tcQual   pREL_IO_BASE_Name SLIT("IO") ioTyConKey
469 ioDataConName     = dataQual pREL_IO_BASE_Name SLIT("IO") ioDataConKey
470 bindIOName        = varQual  pREL_IO_BASE_Name SLIT("bindIO") bindIOIdKey
471 returnIOName      = varQual  pREL_IO_BASE_Name SLIT("returnIO") returnIOIdKey
472 failIOName        = varQual  pREL_IO_BASE_Name SLIT("failIO") failIOIdKey
473
474 -- IO things
475 printName         = varQual pREL_IO_Name SLIT("print") printIdKey
476
477 -- Int, Word, and Addr things
478 int8TyConName     = tcQual pREL_INT_Name  SLIT("Int8") int8TyConKey
479 int16TyConName    = tcQual pREL_INT_Name  SLIT("Int16") int16TyConKey
480 int32TyConName    = tcQual pREL_INT_Name  SLIT("Int32") int32TyConKey
481 int64TyConName    = tcQual pREL_INT_Name  SLIT("Int64") int64TyConKey
482
483 word8TyConName    = tcQual pREL_WORD_Name SLIT("Word8")  word8TyConKey
484 word16TyConName   = tcQual pREL_WORD_Name SLIT("Word16") word16TyConKey
485 word32TyConName   = tcQual pREL_WORD_Name SLIT("Word32") word32TyConKey
486 word64TyConName   = tcQual pREL_WORD_Name SLIT("Word64") word64TyConKey
487
488 wordTyConName     = tcQual   pREL_WORD_Name SLIT("Word")   wordTyConKey
489 wordDataConName   = dataQual pREL_WORD_Name SLIT("W#")     wordDataConKey
490
491 addrTyConName     = tcQual   aDDR_Name SLIT("Addr") addrTyConKey
492 addrDataConName   = dataQual aDDR_Name SLIT("A#") addrDataConKey
493
494 ptrTyConName      = tcQual   pREL_PTR_Name SLIT("Ptr") ptrTyConKey
495 ptrDataConName    = dataQual pREL_PTR_Name SLIT("Ptr") ptrDataConKey
496
497 funPtrTyConName   = tcQual   pREL_PTR_Name SLIT("FunPtr") funPtrTyConKey
498 funPtrDataConName = dataQual pREL_PTR_Name SLIT("FunPtr") funPtrDataConKey
499
500 -- Byte array types
501 byteArrayTyConName        = tcQual pREL_BYTEARR_Name  SLIT("ByteArray") byteArrayTyConKey
502 mutableByteArrayTyConName = tcQual pREL_BYTEARR_Name  SLIT("MutableByteArray") mutableByteArrayTyConKey
503
504 -- Forign objects and weak pointers
505 foreignObjTyConName   = tcQual   fOREIGNOBJ_Name SLIT("ForeignObj") foreignObjTyConKey
506 foreignObjDataConName = dataQual fOREIGNOBJ_Name SLIT("ForeignObj") foreignObjDataConKey
507 foreignPtrTyConName   = tcQual   pREL_FOREIGN_Name SLIT("ForeignPtr") foreignPtrTyConKey
508 foreignPtrDataConName = dataQual pREL_FOREIGN_Name SLIT("ForeignPtr") foreignPtrDataConKey
509 stablePtrTyConName    = tcQual   pREL_STABLE_Name SLIT("StablePtr") stablePtrTyConKey
510 stablePtrDataConName  = dataQual pREL_STABLE_Name SLIT("StablePtr") stablePtrDataConKey
511 deRefStablePtrName    = varQual  pREL_STABLE_Name SLIT("deRefStablePtr") deRefStablePtrIdKey
512 newStablePtrName      = varQual  pREL_STABLE_Name SLIT("newStablePtr") newStablePtrIdKey
513
514 errorName          = varQual pREL_ERR_Name SLIT("error") errorIdKey
515 assertName         = varQual pREL_GHC_Name SLIT("assert") assertIdKey
516 getTagName         = varQual pREL_GHC_Name SLIT("getTag#") getTagIdKey
517 runSTRepName       = varQual pREL_ST_Name  SLIT("runSTRep") runSTRepIdKey
518
519 -- The "split" Id for splittable implicit parameters
520 splitIdName = varQual pREL_SPLIT_Name SLIT("split") splitIdKey
521 \end{code}
522
523 %************************************************************************
524 %*                                                                      *
525 \subsection{Known names}
526 %*                                                                      *
527 %************************************************************************
528
529 The following names are known to the compiler, but they don't require
530 pre-assigned keys.  Mostly these names are used in generating deriving
531 code, which is passed through the renamer anyway.
532
533         THEY ARE ALL ORIGINAL NAMES, HOWEVER
534
535 \begin{code}
536 -- Lists and tuples
537 tupleCon_RDR, tupleTyCon_RDR            :: Int -> RdrName
538 ubxTupleCon_RDR, ubxTupleTyCon_RDR      :: Int -> RdrName
539
540 tupleCon_RDR      = mkTupConRdrName dataName Boxed  
541 tupleTyCon_RDR    = mkTupConRdrName tcName   Boxed  
542 ubxTupleCon_RDR   = mkTupConRdrName dataName Unboxed
543 ubxTupleTyCon_RDR = mkTupConRdrName tcName   Unboxed
544
545 unitCon_RDR       = dataQual_RDR pREL_BASE_Name SLIT("()")
546 unitTyCon_RDR     = tcQual_RDR   pREL_BASE_Name SLIT("()")
547
548 and_RDR            = varQual_RDR  pREL_BASE_Name SLIT("&&")
549 not_RDR            = varQual_RDR  pREL_BASE_Name SLIT("not")
550 compose_RDR        = varQual_RDR  pREL_BASE_Name SLIT(".")
551 ne_RDR             = varQual_RDR  pREL_BASE_Name SLIT("/=")
552 le_RDR             = varQual_RDR  pREL_BASE_Name SLIT("<=")
553 lt_RDR             = varQual_RDR  pREL_BASE_Name SLIT("<")
554 gt_RDR             = varQual_RDR  pREL_BASE_Name SLIT(">")
555 ltTag_RDR          = dataQual_RDR pREL_BASE_Name SLIT("LT")
556 eqTag_RDR          = dataQual_RDR pREL_BASE_Name SLIT("EQ")
557 gtTag_RDR          = dataQual_RDR pREL_BASE_Name SLIT("GT")
558 max_RDR            = varQual_RDR  pREL_BASE_Name SLIT("max")
559 min_RDR            = varQual_RDR  pREL_BASE_Name SLIT("min")
560 compare_RDR        = varQual_RDR  pREL_BASE_Name SLIT("compare")
561 showList_RDR       = varQual_RDR  pREL_SHOW_Name SLIT("showList")
562 showList___RDR     = varQual_RDR  pREL_SHOW_Name SLIT("showList__")
563 showsPrec_RDR      = varQual_RDR  pREL_SHOW_Name SLIT("showsPrec")
564 showSpace_RDR      = varQual_RDR  pREL_SHOW_Name SLIT("showSpace")
565 showString_RDR     = varQual_RDR  pREL_SHOW_Name SLIT("showString")
566 showParen_RDR      = varQual_RDR  pREL_SHOW_Name SLIT("showParen")
567 readsPrec_RDR      = varQual_RDR  pREL_READ_Name SLIT("readsPrec")
568 readList_RDR       = varQual_RDR  pREL_READ_Name SLIT("readList")
569 readParen_RDR      = varQual_RDR  pREL_READ_Name SLIT("readParen")
570 lex_RDR            = varQual_RDR  pREL_READ_Name SLIT("lex")
571 readList___RDR     = varQual_RDR  pREL_READ_Name SLIT("readList__")
572 times_RDR          = varQual_RDR  pREL_NUM_Name SLIT("*")
573 plus_RDR           = varQual_RDR  pREL_NUM_Name SLIT("+")
574 negate_RDR         = varQual_RDR  pREL_NUM_Name SLIT("negate")
575 range_RDR          = varQual_RDR  pREL_ARR_Name SLIT("range")
576 index_RDR          = varQual_RDR  pREL_ARR_Name SLIT("index")
577 inRange_RDR        = varQual_RDR  pREL_ARR_Name SLIT("inRange")
578 succ_RDR           = varQual_RDR  pREL_ENUM_Name SLIT("succ")
579 pred_RDR           = varQual_RDR  pREL_ENUM_Name SLIT("pred")
580 minBound_RDR       = varQual_RDR  pREL_ENUM_Name SLIT("minBound")
581 maxBound_RDR       = varQual_RDR  pREL_ENUM_Name SLIT("maxBound")
582 assertErr_RDR      = varQual_RDR  pREL_ERR_Name SLIT("assertError")
583 \end{code}
584
585 These RDR names also have known keys, so we need to get back the RDR names to
586 populate the occurrence list above.
587
588 \begin{code}
589 funTyCon_RDR            = nameRdrName funTyConName
590 nilCon_RDR              = nameRdrName nilDataConName
591 listTyCon_RDR           = nameRdrName listTyConName
592 ioTyCon_RDR             = nameRdrName ioTyConName
593 intTyCon_RDR            = nameRdrName intTyConName
594 eq_RDR                  = nameRdrName eqName
595 ge_RDR                  = nameRdrName geName
596 numClass_RDR            = nameRdrName numClassName
597 ordClass_RDR            = nameRdrName ordClassName
598 map_RDR                 = nameRdrName mapName
599 append_RDR              = nameRdrName appendName
600 foldr_RDR               = nameRdrName foldrName
601 build_RDR               = nameRdrName buildName
602 enumFromTo_RDR          = nameRdrName enumFromToName
603 returnM_RDR             = nameRdrName returnMName
604 thenM_RDR               = nameRdrName thenMName
605 failM_RDR               = nameRdrName failMName
606 false_RDR               = nameRdrName falseDataConName
607 true_RDR                = nameRdrName trueDataConName
608 error_RDR               = nameRdrName errorName
609 getTag_RDR              = nameRdrName getTagName
610 fromEnum_RDR            = nameRdrName fromEnumName
611 toEnum_RDR              = nameRdrName toEnumName
612 enumFrom_RDR            = nameRdrName enumFromName
613 mkInt_RDR               = nameRdrName intDataConName
614 enumFromThen_RDR        = nameRdrName enumFromThenName
615 enumFromThenTo_RDR      = nameRdrName enumFromThenToName
616 ratioDataCon_RDR        = nameRdrName ratioDataConName
617 plusInteger_RDR         = nameRdrName plusIntegerName
618 timesInteger_RDR        = nameRdrName timesIntegerName
619 enumClass_RDR           = nameRdrName enumClassName
620 monadClass_RDR          = nameRdrName monadClassName
621 ioDataCon_RDR           = nameRdrName ioDataConName
622 cCallableClass_RDR      = nameRdrName cCallableClassName
623 cReturnableClass_RDR    = nameRdrName cReturnableClassName
624 eqClass_RDR             = nameRdrName eqClassName
625 eqString_RDR            = nameRdrName eqStringName
626 unpackCString_RDR       = nameRdrName unpackCStringName
627 unpackCStringFoldr_RDR  = nameRdrName unpackCStringFoldrName
628 unpackCStringUtf8_RDR   = nameRdrName unpackCStringUtf8Name
629 deRefStablePtr_RDR      = nameRdrName deRefStablePtrName
630 newStablePtr_RDR        = nameRdrName newStablePtrName
631 bindIO_RDR              = nameRdrName bindIOName
632 returnIO_RDR            = nameRdrName returnIOName
633 fromInteger_RDR         = nameRdrName fromIntegerName
634 fromRational_RDR        = nameRdrName fromRationalName
635 minus_RDR               = nameRdrName minusName
636 \end{code}
637
638 %************************************************************************
639 %*                                                                      *
640 \subsection{Local helpers}
641 %*                                                                      *
642 %************************************************************************
643
644 All these are original names; hence mkOrig
645
646 \begin{code}
647 varQual  mod str uq = mkKnownKeyGlobal (varQual_RDR  mod str) uq
648 dataQual mod str uq = mkKnownKeyGlobal (dataQual_RDR mod str) uq
649 tcQual   mod str uq = mkKnownKeyGlobal (tcQual_RDR   mod str) uq
650 clsQual  mod str uq = mkKnownKeyGlobal (clsQual_RDR  mod str) uq
651
652 kindQual str uq = mkLocalName uq (mkKindOccFS tcName str) builtinSrcLoc
653         -- Kinds are not z-encoded in interface file, hence mkKindOccFS
654         -- And they don't come from any particular module; indeed we always
655         -- want to print them unqualified.  Hence the LocalName
656
657 varQual_RDR  mod str = mkOrig varName  mod str
658 tcQual_RDR   mod str = mkOrig tcName   mod str
659 clsQual_RDR  mod str = mkOrig clsName  mod str
660 dataQual_RDR mod str = mkOrig dataName mod str
661 \end{code}
662
663 %************************************************************************
664 %*                                                                      *
665 \subsubsection[Uniques-prelude-Classes]{@Uniques@ for wired-in @Classes@}
666 %*                                                                      *
667 %************************************************************************
668
669 \begin{code}
670 boundedClassKey         = mkPreludeClassUnique 1 
671 enumClassKey            = mkPreludeClassUnique 2 
672 eqClassKey              = mkPreludeClassUnique 3 
673 floatingClassKey        = mkPreludeClassUnique 5 
674 fractionalClassKey      = mkPreludeClassUnique 6 
675 integralClassKey        = mkPreludeClassUnique 7 
676 monadClassKey           = mkPreludeClassUnique 8 
677 monadPlusClassKey       = mkPreludeClassUnique 9
678 functorClassKey         = mkPreludeClassUnique 10
679 numClassKey             = mkPreludeClassUnique 11
680 ordClassKey             = mkPreludeClassUnique 12
681 readClassKey            = mkPreludeClassUnique 13
682 realClassKey            = mkPreludeClassUnique 14
683 realFloatClassKey       = mkPreludeClassUnique 15
684 realFracClassKey        = mkPreludeClassUnique 16
685 showClassKey            = mkPreludeClassUnique 17
686                                                
687 cCallableClassKey       = mkPreludeClassUnique 18
688 cReturnableClassKey     = mkPreludeClassUnique 19
689
690 ixClassKey              = mkPreludeClassUnique 20
691 \end{code}
692
693 %************************************************************************
694 %*                                                                      *
695 \subsubsection[Uniques-prelude-TyCons]{@Uniques@ for wired-in @TyCons@}
696 %*                                                                      *
697 %************************************************************************
698
699 \begin{code}
700 addrPrimTyConKey                        = mkPreludeTyConUnique  1
701 addrTyConKey                            = mkPreludeTyConUnique  2
702 arrayPrimTyConKey                       = mkPreludeTyConUnique  3
703 boolTyConKey                            = mkPreludeTyConUnique  4
704 byteArrayPrimTyConKey                   = mkPreludeTyConUnique  5
705 charPrimTyConKey                        = mkPreludeTyConUnique  7
706 charTyConKey                            = mkPreludeTyConUnique  8
707 doublePrimTyConKey                      = mkPreludeTyConUnique  9
708 doubleTyConKey                          = mkPreludeTyConUnique 10 
709 floatPrimTyConKey                       = mkPreludeTyConUnique 11
710 floatTyConKey                           = mkPreludeTyConUnique 12
711 funTyConKey                             = mkPreludeTyConUnique 13
712 intPrimTyConKey                         = mkPreludeTyConUnique 14
713 intTyConKey                             = mkPreludeTyConUnique 15
714 int8TyConKey                            = mkPreludeTyConUnique 16
715 int16TyConKey                           = mkPreludeTyConUnique 17
716 int32PrimTyConKey                       = mkPreludeTyConUnique 18
717 int32TyConKey                           = mkPreludeTyConUnique 19
718 int64PrimTyConKey                       = mkPreludeTyConUnique 20
719 int64TyConKey                           = mkPreludeTyConUnique 21
720 integerTyConKey                         = mkPreludeTyConUnique 22
721 listTyConKey                            = mkPreludeTyConUnique 23
722 foreignObjPrimTyConKey                  = mkPreludeTyConUnique 24
723 foreignObjTyConKey                      = mkPreludeTyConUnique 25
724 foreignPtrTyConKey                      = mkPreludeTyConUnique 26
725 weakPrimTyConKey                        = mkPreludeTyConUnique 27
726 mutableArrayPrimTyConKey                = mkPreludeTyConUnique 28
727 mutableByteArrayPrimTyConKey            = mkPreludeTyConUnique 29
728 orderingTyConKey                        = mkPreludeTyConUnique 30
729 mVarPrimTyConKey                        = mkPreludeTyConUnique 31
730 ratioTyConKey                           = mkPreludeTyConUnique 32
731 rationalTyConKey                        = mkPreludeTyConUnique 33
732 realWorldTyConKey                       = mkPreludeTyConUnique 34
733 stablePtrPrimTyConKey                   = mkPreludeTyConUnique 35
734 stablePtrTyConKey                       = mkPreludeTyConUnique 36
735 statePrimTyConKey                       = mkPreludeTyConUnique 50
736 stableNamePrimTyConKey                  = mkPreludeTyConUnique 51
737 stableNameTyConKey                      = mkPreludeTyConUnique 52
738 mutableByteArrayTyConKey                = mkPreludeTyConUnique 53
739 mutVarPrimTyConKey                      = mkPreludeTyConUnique 55
740 ioTyConKey                              = mkPreludeTyConUnique 56
741 byteArrayTyConKey                       = mkPreludeTyConUnique 57
742 wordPrimTyConKey                        = mkPreludeTyConUnique 58
743 wordTyConKey                            = mkPreludeTyConUnique 59
744 word8TyConKey                           = mkPreludeTyConUnique 60
745 word16TyConKey                          = mkPreludeTyConUnique 61 
746 word32PrimTyConKey                      = mkPreludeTyConUnique 62 
747 word32TyConKey                          = mkPreludeTyConUnique 63
748 word64PrimTyConKey                      = mkPreludeTyConUnique 64
749 word64TyConKey                          = mkPreludeTyConUnique 65
750 liftedConKey                            = mkPreludeTyConUnique 66
751 unliftedConKey                          = mkPreludeTyConUnique 67
752 anyBoxConKey                            = mkPreludeTyConUnique 68
753 kindConKey                              = mkPreludeTyConUnique 69
754 boxityConKey                            = mkPreludeTyConUnique 70
755 typeConKey                              = mkPreludeTyConUnique 71
756 threadIdPrimTyConKey                    = mkPreludeTyConUnique 72
757 bcoPrimTyConKey                         = mkPreludeTyConUnique 73
758 ptrTyConKey                             = mkPreludeTyConUnique 74
759 funPtrTyConKey                          = mkPreludeTyConUnique 75
760
761 -- Usage type constructors
762 usageConKey                             = mkPreludeTyConUnique 76
763 usOnceTyConKey                          = mkPreludeTyConUnique 77
764 usManyTyConKey                          = mkPreludeTyConUnique 78
765
766 -- Generic Type Constructors
767 crossTyConKey                           = mkPreludeTyConUnique 79
768 plusTyConKey                            = mkPreludeTyConUnique 80
769 genUnitTyConKey                         = mkPreludeTyConUnique 81
770
771 unitTyConKey = mkTupleTyConUnique Boxed 0
772 \end{code}
773
774 %************************************************************************
775 %*                                                                      *
776 \subsubsection[Uniques-prelude-DataCons]{@Uniques@ for wired-in @DataCons@}
777 %*                                                                      *
778 %************************************************************************
779
780 \begin{code}
781 addrDataConKey                          = mkPreludeDataConUnique  0
782 charDataConKey                          = mkPreludeDataConUnique  1
783 consDataConKey                          = mkPreludeDataConUnique  2
784 doubleDataConKey                        = mkPreludeDataConUnique  3
785 falseDataConKey                         = mkPreludeDataConUnique  4
786 floatDataConKey                         = mkPreludeDataConUnique  5
787 intDataConKey                           = mkPreludeDataConUnique  6
788 smallIntegerDataConKey                  = mkPreludeDataConUnique  7
789 largeIntegerDataConKey                  = mkPreludeDataConUnique  8
790 foreignObjDataConKey                    = mkPreludeDataConUnique  9
791 foreignPtrDataConKey                    = mkPreludeDataConUnique 10
792 nilDataConKey                           = mkPreludeDataConUnique 11
793 ratioDataConKey                         = mkPreludeDataConUnique 12
794 stablePtrDataConKey                     = mkPreludeDataConUnique 13
795 stableNameDataConKey                    = mkPreludeDataConUnique 14
796 trueDataConKey                          = mkPreludeDataConUnique 15
797 wordDataConKey                          = mkPreludeDataConUnique 16
798 ioDataConKey                            = mkPreludeDataConUnique 17
799 ptrDataConKey                           = mkPreludeDataConUnique 18
800 funPtrDataConKey                        = mkPreludeDataConUnique 19
801
802 -- Generic data constructors
803 crossDataConKey                         = mkPreludeDataConUnique 20
804 inlDataConKey                           = mkPreludeDataConUnique 21
805 inrDataConKey                           = mkPreludeDataConUnique 22
806 genUnitDataConKey                       = mkPreludeDataConUnique 23
807 \end{code}
808
809 %************************************************************************
810 %*                                                                      *
811 \subsubsection[Uniques-prelude-Ids]{@Uniques@ for wired-in @Ids@ (except @DataCons@)}
812 %*                                                                      *
813 %************************************************************************
814
815 \begin{code}
816 absentErrorIdKey              = mkPreludeMiscIdUnique  1
817 appendIdKey                   = mkPreludeMiscIdUnique  2
818 augmentIdKey                  = mkPreludeMiscIdUnique  3
819 buildIdKey                    = mkPreludeMiscIdUnique  4
820 errorIdKey                    = mkPreludeMiscIdUnique  5
821 foldlIdKey                    = mkPreludeMiscIdUnique  6
822 foldrIdKey                    = mkPreludeMiscIdUnique  7
823 recSelErrIdKey                = mkPreludeMiscIdUnique  8
824 integerMinusOneIdKey          = mkPreludeMiscIdUnique  9
825 integerPlusOneIdKey           = mkPreludeMiscIdUnique 10
826 integerPlusTwoIdKey           = mkPreludeMiscIdUnique 11
827 integerZeroIdKey              = mkPreludeMiscIdUnique 12
828 int2IntegerIdKey              = mkPreludeMiscIdUnique 13
829 seqIdKey                      = mkPreludeMiscIdUnique 14
830 irrefutPatErrorIdKey          = mkPreludeMiscIdUnique 15
831 eqStringIdKey                 = mkPreludeMiscIdUnique 16
832 noMethodBindingErrorIdKey     = mkPreludeMiscIdUnique 17
833 nonExhaustiveGuardsErrorIdKey = mkPreludeMiscIdUnique 18
834 errorCStringIdKey             = mkPreludeMiscIdUnique 19 
835 parErrorIdKey                 = mkPreludeMiscIdUnique 20
836 parIdKey                      = mkPreludeMiscIdUnique 21
837 patErrorIdKey                 = mkPreludeMiscIdUnique 22
838 realWorldPrimIdKey            = mkPreludeMiscIdUnique 23
839 recConErrorIdKey              = mkPreludeMiscIdUnique 24
840 recUpdErrorIdKey              = mkPreludeMiscIdUnique 25
841 traceIdKey                    = mkPreludeMiscIdUnique 26
842 unpackCStringUtf8IdKey        = mkPreludeMiscIdUnique 27
843 unpackCStringAppendIdKey      = mkPreludeMiscIdUnique 28
844 unpackCStringFoldrIdKey       = mkPreludeMiscIdUnique 29
845 unpackCStringIdKey            = mkPreludeMiscIdUnique 30
846 ushowListIdKey                = mkPreludeMiscIdUnique 31
847 unsafeCoerceIdKey             = mkPreludeMiscIdUnique 32
848 concatIdKey                   = mkPreludeMiscIdUnique 33
849 filterIdKey                   = mkPreludeMiscIdUnique 34
850 zipIdKey                      = mkPreludeMiscIdUnique 35
851 bindIOIdKey                   = mkPreludeMiscIdUnique 36
852 returnIOIdKey                 = mkPreludeMiscIdUnique 37
853 deRefStablePtrIdKey           = mkPreludeMiscIdUnique 38
854 newStablePtrIdKey             = mkPreludeMiscIdUnique 39
855 getTagIdKey                   = mkPreludeMiscIdUnique 40
856 plusIntegerIdKey              = mkPreludeMiscIdUnique 41
857 timesIntegerIdKey             = mkPreludeMiscIdUnique 42
858 printIdKey                    = mkPreludeMiscIdUnique 43
859 failIOIdKey                   = mkPreludeMiscIdUnique 44
860 unpackCStringListIdKey        = mkPreludeMiscIdUnique 45
861 nullAddrIdKey                 = mkPreludeMiscIdUnique 46
862 voidArgIdKey                  = mkPreludeMiscIdUnique 47
863 splitIdKey                    = mkPreludeMiscIdUnique 48
864 fstIdKey                      = mkPreludeMiscIdUnique 49
865 sndIdKey                      = mkPreludeMiscIdUnique 50
866 \end{code}
867
868 Certain class operations from Prelude classes.  They get their own
869 uniques so we can look them up easily when we want to conjure them up
870 during type checking.
871
872 \begin{code}
873 fromIntegerClassOpKey         = mkPreludeMiscIdUnique 102
874 minusClassOpKey               = mkPreludeMiscIdUnique 103
875 fromRationalClassOpKey        = mkPreludeMiscIdUnique 104
876 enumFromClassOpKey            = mkPreludeMiscIdUnique 105
877 enumFromThenClassOpKey        = mkPreludeMiscIdUnique 106
878 enumFromToClassOpKey          = mkPreludeMiscIdUnique 107
879 enumFromThenToClassOpKey      = mkPreludeMiscIdUnique 108
880 eqClassOpKey                  = mkPreludeMiscIdUnique 109
881 geClassOpKey                  = mkPreludeMiscIdUnique 110
882 negateClassOpKey              = mkPreludeMiscIdUnique 111
883 failMClassOpKey               = mkPreludeMiscIdUnique 112
884 thenMClassOpKey               = mkPreludeMiscIdUnique 113 -- (>>=)
885         -- Just a place holder for  unbound variables  produced by the renamer:
886 unboundKey                    = mkPreludeMiscIdUnique 114 
887 fromEnumClassOpKey            = mkPreludeMiscIdUnique 115
888                               
889 mainKey                       = mkPreludeMiscIdUnique 116
890 returnMClassOpKey             = mkPreludeMiscIdUnique 117
891 otherwiseIdKey                = mkPreludeMiscIdUnique 118
892 toEnumClassOpKey              = mkPreludeMiscIdUnique 119
893 mapIdKey                      = mkPreludeMiscIdUnique 120
894 \end{code}
895
896 \begin{code}
897 assertIdKey                   = mkPreludeMiscIdUnique 121
898 runSTRepIdKey                 = mkPreludeMiscIdUnique 122
899 \end{code}
900
901
902 %************************************************************************
903 %*                                                                      *
904 \subsection{Standard groups of types}
905 %*                                                                      *
906 %************************************************************************
907
908 \begin{code}
909 numericTyKeys = 
910         [ addrTyConKey
911         , wordTyConKey
912         , intTyConKey
913         , integerTyConKey
914         , doubleTyConKey
915         , floatTyConKey
916         ]
917
918         -- Renamer always imports these data decls replete with constructors
919         -- so that desugarer can always see their constructors.  Ugh!
920 cCallishTyKeys = 
921         [ addrTyConKey
922         , wordTyConKey
923         , byteArrayTyConKey
924         , mutableByteArrayTyConKey
925         , foreignObjTyConKey
926         , foreignPtrTyConKey
927         , stablePtrTyConKey
928         , int8TyConKey
929         , int16TyConKey
930         , int32TyConKey
931         , int64TyConKey
932         , word8TyConKey
933         , word16TyConKey
934         , word32TyConKey
935         , word64TyConKey
936         ]
937 \end{code}
938
939
940 %************************************************************************
941 %*                                                                      *
942 \subsection[Class-std-groups]{Standard groups of Prelude classes}
943 %*                                                                      *
944 %************************************************************************
945
946 @derivableClassKeys@ is also used in checking \tr{deriving} constructs
947 (@TcDeriv@).
948
949 @derivingOccurrences@ maps a class name to a list of the (qualified)
950 occurrences that will be mentioned by the derived code for the class
951 when it is later generated.  We don't need to put in things that are
952 WiredIn (because they are already mapped to their correct name by the
953 @NameSupply@.  The class itself, and all its class ops, is already
954 flagged as an occurrence so we don't need to mention that either.
955
956 @derivingOccurrences@ has an item for every derivable class, even if
957 that item is empty, because we treat lookup failure as indicating that
958 the class is illegal in a deriving clause.
959
960 \begin{code}
961 derivingOccurrences :: UniqFM [RdrName]
962 derivingOccurrences = listToUFM deriving_occ_info
963
964 derivableClassKeys  = map fst deriving_occ_info
965
966 deriving_occ_info
967   = [ (eqClassKey,      [intTyCon_RDR, and_RDR, not_RDR])
968     , (ordClassKey,     [intTyCon_RDR, compose_RDR, eqTag_RDR])
969                                 -- EQ (from Ordering) is needed to force in the constructors
970                                 -- as well as the type constructor.
971     , (enumClassKey,    [intTyCon_RDR, eq_RDR, ge_RDR, and_RDR, map_RDR, plus_RDR, showsPrec_RDR, append_RDR]) 
972                                 -- The last two Enum deps are only used to produce better
973                                 -- error msgs for derived toEnum methods.
974     , (boundedClassKey, [intTyCon_RDR])
975     , (showClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, compose_RDR, showString_RDR, 
976                          showParen_RDR, showSpace_RDR, showList___RDR])
977     , (readClassKey,    [intTyCon_RDR, numClass_RDR, ordClass_RDR, append_RDR,
978                          foldr_RDR, build_RDR,
979                              -- foldr and build required for list comprehension
980                              -- KSW 2000-06
981                          lex_RDR, readParen_RDR, readList___RDR, thenM_RDR])
982                              -- returnM (and the rest of the Monad class decl) 
983                              -- will be forced in as result of depending
984                              -- on thenM.   -- SOF 1/99
985     , (ixClassKey,      [intTyCon_RDR, numClass_RDR, and_RDR, map_RDR, enumFromTo_RDR,
986                          foldr_RDR, build_RDR,
987                              -- foldr and build required for list comprehension used
988                              -- with single constructor types  -- KSW 2000-06
989                          returnM_RDR, failM_RDR])
990                              -- the last two are needed to force returnM, thenM and failM
991                              -- in before typechecking the list(monad) comprehension
992                              -- generated for derived Ix instances (range method)
993                              -- of single constructor types.  -- SOF 8/97
994     ]
995         -- intTyCon: Practically any deriving needs Int, either for index calculations, 
996         --              or for taggery.
997         -- ordClass: really it's the methods that are actually used.
998         -- numClass: for Int literals
999 \end{code}
1000
1001
1002 NOTE: @Eq@ and @Text@ do need to appear in @standardClasses@
1003 even though every numeric class has these two as a superclass,
1004 because the list of ambiguous dictionaries hasn't been simplified.
1005
1006 \begin{code}
1007 numericClassKeys =
1008         [ numClassKey
1009         , realClassKey
1010         , integralClassKey
1011         ]
1012         ++ fractionalClassKeys
1013
1014 fractionalClassKeys = 
1015         [ fractionalClassKey
1016         , floatingClassKey
1017         , realFracClassKey
1018         , realFloatClassKey
1019         ]
1020
1021         -- the strictness analyser needs to know about numeric types
1022         -- (see SaAbsInt.lhs)
1023 needsDataDeclCtxtClassKeys = -- see comments in TcDeriv
1024         [ readClassKey
1025         ]
1026
1027 cCallishClassKeys = 
1028         [ cCallableClassKey
1029         , cReturnableClassKey
1030         ]
1031
1032 standardClassKeys
1033   = derivableClassKeys ++ numericClassKeys ++ cCallishClassKeys
1034     --
1035     -- We have to have "CCallable" and "CReturnable" in the standard
1036     -- classes, so that if you go...
1037     --
1038     --      _ccall_ foo ... 93{-numeric literal-} ...
1039     --
1040     -- ... it can do The Right Thing on the 93.
1041
1042 noDictClassKeys         -- These classes are used only for type annotations;
1043                         -- they are not implemented by dictionaries, ever.
1044   = cCallishClassKeys
1045 \end{code}
1046