More refactoring in RnNames
[ghc-hetmet.git] / compiler / rename / RnEnv.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-2006
3 %
4 \section[RnEnv]{Environment manipulation for the renamer monad}
5
6 \begin{code}
7 module RnEnv ( 
8         newTopSrcBinder, lookupFamInstDeclBndr,
9         lookupLocatedBndrRn, lookupBndrRn, 
10         lookupLocatedTopBndrRn, lookupTopBndrRn,
11         lookupLocatedOccRn, lookupOccRn, 
12         lookupLocatedGlobalOccRn, lookupGlobalOccRn,
13         lookupLocalDataTcNames, lookupSrcOcc_maybe,
14         lookupFixityRn, lookupTyFixityRn, lookupLocatedSigOccRn, 
15         lookupLocatedInstDeclBndr,
16         lookupSyntaxName, lookupSyntaxTable, lookupImportedName,
17         lookupGreRn, lookupGreRn_maybe,
18
19         newLocalsRn, newIPNameRn,
20         bindLocalNames, bindLocalNamesFV,
21         bindLocatedLocalsFV, bindLocatedLocalsRn,
22         bindSigTyVarsFV, bindPatSigTyVars, bindPatSigTyVarsFV,
23         bindTyVarsRn, extendTyVarEnvFVRn,
24         bindLocalFixities,
25
26         checkDupNames, mapFvRn,
27         warnUnusedMatches, warnUnusedModules, warnUnusedImports, 
28         warnUnusedTopBinds, warnUnusedLocalBinds,
29         dataTcOccs, unknownNameErr,
30     ) where
31
32 #include "HsVersions.h"
33
34 import LoadIface        ( loadInterfaceForName, loadSrcInterface )
35 import IfaceEnv         ( lookupOrig, newGlobalBinder, newIPName )
36 import HsSyn            ( FixitySig(..), HsExpr(..), SyntaxExpr, SyntaxTable,
37                           LHsTyVarBndr, LHsType, 
38                           Fixity, hsLTyVarLocNames, replaceTyVarName )
39 import RdrHsSyn         ( extractHsTyRdrTyVars )
40 import RdrName          ( RdrName, isQual, isUnqual, isOrig_maybe,
41                           isQual_maybe,
42                           mkRdrUnqual, setRdrNameSpace, rdrNameOcc,
43                           pprGlobalRdrEnv, lookupGRE_RdrName, 
44                           isExact_maybe, isSrcRdrName,
45                           Parent(..),
46                           GlobalRdrElt(..), GlobalRdrEnv, lookupGlobalRdrEnv, 
47                           isLocalGRE, extendLocalRdrEnv, elemLocalRdrEnv, lookupLocalRdrEnv,
48                           Provenance(..), pprNameProvenance,
49                           importSpecLoc, importSpecModule
50                         )
51 import HscTypes         ( availNames, ModIface(..), FixItem(..), lookupFixity )
52 import TcRnMonad
53 import Name             ( Name, nameIsLocalOrFrom, mkInternalName, isWiredInName,
54                           nameSrcLoc, nameOccName, nameModule, isExternalName )
55 import NameSet
56 import OccName          ( tcName, isDataOcc, pprNonVarNameSpace, occNameSpace,
57                           reportIfUnused )
58 import Module           ( Module, ModuleName )
59 import PrelNames        ( mkUnboundName, rOOT_MAIN, iNTERACTIVE, consDataConKey, hasKey )
60 import UniqSupply
61 import BasicTypes       ( IPName, mapIPName )
62 import SrcLoc           ( SrcSpan, srcSpanStart, Located(..), eqLocated, unLoc,
63                           srcLocSpan, getLoc, combineSrcSpans, isOneLineSpan )
64 import Outputable
65 import Util             ( sortLe )
66 import ListSetOps       ( removeDups )
67 import List             ( nubBy )
68 import Monad            ( when )
69 import DynFlags
70 \end{code}
71
72 %*********************************************************
73 %*                                                      *
74                 Source-code binders
75 %*                                                      *
76 %*********************************************************
77
78 \begin{code}
79 newTopSrcBinder :: Module -> Located RdrName -> RnM Name
80 newTopSrcBinder this_mod (L loc rdr_name)
81   | Just name <- isExact_maybe rdr_name
82   =     -- This is here to catch 
83         --   (a) Exact-name binders created by Template Haskell
84         --   (b) The PrelBase defn of (say) [] and similar, for which
85         --       the parser reads the special syntax and returns an Exact RdrName
86         -- We are at a binding site for the name, so check first that it 
87         -- the current module is the correct one; otherwise GHC can get
88         -- very confused indeed. This test rejects code like
89         --      data T = (,) Int Int
90         -- unless we are in GHC.Tup
91     ASSERT2( isExternalName name,  ppr name )
92     do  { checkM (this_mod == nameModule name)
93                  (addErrAt loc (badOrigBinding rdr_name))
94         ; return name }
95
96
97   | Just (rdr_mod, rdr_occ) <- isOrig_maybe rdr_name
98   = do  { checkM (rdr_mod == this_mod || rdr_mod == rOOT_MAIN)
99                  (addErrAt loc (badOrigBinding rdr_name))
100         -- When reading External Core we get Orig names as binders, 
101         -- but they should agree with the module gotten from the monad
102         --
103         -- We can get built-in syntax showing up here too, sadly.  If you type
104         --      data T = (,,,)
105         -- the constructor is parsed as a type, and then RdrHsSyn.tyConToDataCon 
106         -- uses setRdrNameSpace to make it into a data constructors.  At that point
107         -- the nice Exact name for the TyCon gets swizzled to an Orig name.
108         -- Hence the badOrigBinding error message.
109         --
110         -- Except for the ":Main.main = ..." definition inserted into 
111         -- the Main module; ugh!
112
113         -- Because of this latter case, we call newGlobalBinder with a module from 
114         -- the RdrName, not from the environment.  In principle, it'd be fine to 
115         -- have an arbitrary mixture of external core definitions in a single module,
116         -- (apart from module-initialisation issues, perhaps).
117         ; newGlobalBinder rdr_mod rdr_occ (srcSpanStart loc) }
118                 --TODO, should pass the whole span
119
120   | otherwise
121   = do  { checkM (not (isQual rdr_name))
122                  (addErrAt loc (badQualBndrErr rdr_name))
123                 -- Binders should not be qualified; if they are, and with a different
124                 -- module name, we we get a confusing "M.T is not in scope" error later
125         ; newGlobalBinder this_mod (rdrNameOcc rdr_name) (srcSpanStart loc) }
126 \end{code}
127
128 %*********************************************************
129 %*                                                      *
130         Source code occurrences
131 %*                                                      *
132 %*********************************************************
133
134 Looking up a name in the RnEnv.
135
136 \begin{code}
137 lookupLocatedBndrRn :: Located RdrName -> RnM (Located Name)
138 lookupLocatedBndrRn = wrapLocM lookupBndrRn
139
140 lookupBndrRn :: RdrName -> RnM Name
141 -- NOTE: assumes that the SrcSpan of the binder has already been setSrcSpan'd
142 lookupBndrRn rdr_name
143   = getLocalRdrEnv              `thenM` \ local_env ->
144     case lookupLocalRdrEnv local_env rdr_name of 
145           Just name -> returnM name
146           Nothing   -> lookupTopBndrRn rdr_name
147
148 lookupLocatedTopBndrRn :: Located RdrName -> RnM (Located Name)
149 lookupLocatedTopBndrRn = wrapLocM lookupTopBndrRn
150
151 lookupTopBndrRn :: RdrName -> RnM Name
152 -- Look up a top-level source-code binder.   We may be looking up an unqualified 'f',
153 -- and there may be several imported 'f's too, which must not confuse us.
154 -- For example, this is OK:
155 --      import Foo( f )
156 --      infix 9 f       -- The 'f' here does not need to be qualified
157 --      f x = x         -- Nor here, of course
158 -- So we have to filter out the non-local ones.
159 --
160 -- A separate function (importsFromLocalDecls) reports duplicate top level
161 -- decls, so here it's safe just to choose an arbitrary one.
162 --
163 -- There should never be a qualified name in a binding position in Haskell,
164 -- but there can be if we have read in an external-Core file.
165 -- The Haskell parser checks for the illegal qualified name in Haskell 
166 -- source files, so we don't need to do so here.
167
168 lookupTopBndrRn rdr_name
169   | Just name <- isExact_maybe rdr_name
170   = returnM name
171
172   | Just (rdr_mod, rdr_occ) <- isOrig_maybe rdr_name    
173         -- This deals with the case of derived bindings, where
174         -- we don't bother to call newTopSrcBinder first
175         -- We assume there is no "parent" name
176   = do  { loc <- getSrcSpanM
177         ; newGlobalBinder rdr_mod rdr_occ (srcSpanStart loc) }
178
179   | otherwise
180   = do  { mb_gre <- lookupGreLocalRn rdr_name
181         ; case mb_gre of
182                 Nothing  -> unboundName rdr_name
183                 Just gre -> returnM (gre_name gre) }
184               
185 -- lookupLocatedSigOccRn is used for type signatures and pragmas
186 -- Is this valid?
187 --   module A
188 --      import M( f )
189 --      f :: Int -> Int
190 --      f x = x
191 -- It's clear that the 'f' in the signature must refer to A.f
192 -- The Haskell98 report does not stipulate this, but it will!
193 -- So we must treat the 'f' in the signature in the same way
194 -- as the binding occurrence of 'f', using lookupBndrRn
195 lookupLocatedSigOccRn :: Located RdrName -> RnM (Located Name)
196 lookupLocatedSigOccRn = lookupLocatedBndrRn
197
198 -- lookupInstDeclBndr is used for the binders in an 
199 -- instance declaration.   Here we use the class name to
200 -- disambiguate.  
201
202 lookupLocatedInstDeclBndr :: Name -> Located RdrName -> RnM (Located Name)
203 lookupLocatedInstDeclBndr cls rdr = wrapLocM (lookupInstDeclBndr cls) rdr
204
205 lookupInstDeclBndr :: Name -> RdrName -> RnM Name
206 -- This is called on the method name on the left-hand side of an 
207 -- instance declaration binding. eg.  instance Functor T where
208 --                                       fmap = ...
209 --                                       ^^^^ called on this
210 -- Regardless of how many unqualified fmaps are in scope, we want
211 -- the one that comes from the Functor class.
212 lookupInstDeclBndr cls_name rdr_name
213   | isUnqual rdr_name   -- Find all the things the rdr-name maps to
214   = do  {               -- and pick the one with the right parent name
215           let { is_op gre@(GRE {gre_par = ParentIs n}) = cls_name == n
216               ; is_op other                            = False
217               ; occ           = rdrNameOcc rdr_name
218               ; lookup_fn env = filter is_op (lookupGlobalRdrEnv env occ) }
219         ; mb_gre <- lookupGreRn_help rdr_name lookup_fn
220         ; case mb_gre of
221             Just gre -> return (gre_name gre)
222             Nothing  -> do { addErr (unknownInstBndrErr cls_name rdr_name)
223                            ; traceRn (text "lookupInstDeclBndr" <+> ppr rdr_name)
224                            ; return (mkUnboundName rdr_name) } }
225
226   | otherwise   -- Occurs in derived instances, where we just
227                 -- refer directly to the right method
228   = ASSERT2( not (isQual rdr_name), ppr rdr_name )
229           -- NB: qualified names are rejected by the parser
230     lookupImportedName rdr_name
231
232 newIPNameRn :: IPName RdrName -> TcRnIf m n (IPName Name)
233 newIPNameRn ip_rdr = newIPName (mapIPName rdrNameOcc ip_rdr)
234
235 -- Looking up family names in type instances is a subtle affair.  The family
236 -- may be imported, in which case we need to lookup the occurence of a global
237 -- name.  Alternatively, the family may be in the same binding group (and in
238 -- fact in a declaration processed later), and we need to create a new top
239 -- source binder.
240 --
241 -- So, also this is strictly speaking an occurence, we cannot raise an error
242 -- message yet for instances without a family declaration.  This will happen
243 -- during renaming the type instance declaration in RnSource.rnTyClDecl.
244 --
245 lookupFamInstDeclBndr :: Module -> Located RdrName -> RnM Name
246 lookupFamInstDeclBndr mod lrdr_name@(L _ rdr_name)
247   | not (isSrcRdrName rdr_name)
248   = lookupImportedName rdr_name 
249
250   | otherwise
251   =     -- First look up the name in the normal environment.
252    lookupGreRn_maybe rdr_name           `thenM` \ mb_gre ->
253    case mb_gre of {
254         Just gre -> returnM (gre_name gre) ;
255         Nothing  -> newTopSrcBinder mod lrdr_name }
256
257 --------------------------------------------------
258 --              Occurrences
259 --------------------------------------------------
260
261 lookupLocatedOccRn :: Located RdrName -> RnM (Located Name)
262 lookupLocatedOccRn = wrapLocM lookupOccRn
263
264 -- lookupOccRn looks up an occurrence of a RdrName
265 lookupOccRn :: RdrName -> RnM Name
266 lookupOccRn rdr_name
267   = getLocalRdrEnv                      `thenM` \ local_env ->
268     case lookupLocalRdrEnv local_env rdr_name of
269           Just name -> returnM name
270           Nothing   -> lookupGlobalOccRn rdr_name
271
272 lookupLocatedGlobalOccRn :: Located RdrName -> RnM (Located Name)
273 lookupLocatedGlobalOccRn = wrapLocM lookupGlobalOccRn
274
275 lookupGlobalOccRn :: RdrName -> RnM Name
276 -- lookupGlobalOccRn is like lookupOccRn, except that it looks in the global 
277 -- environment.  It's used only for
278 --      record field names
279 --      class op names in class and instance decls
280
281 lookupGlobalOccRn rdr_name
282   | not (isSrcRdrName rdr_name)
283   = lookupImportedName rdr_name 
284
285   | otherwise
286   =     -- First look up the name in the normal environment.
287    lookupGreRn_maybe rdr_name           `thenM` \ mb_gre ->
288    case mb_gre of {
289         Just gre -> returnM (gre_name gre) ;
290         Nothing   -> 
291
292         -- We allow qualified names on the command line to refer to 
293         --  *any* name exported by any module in scope, just as if 
294         -- there was an "import qualified M" declaration for every 
295         -- module.
296    getModule            `thenM` \ mod ->
297    if isQual rdr_name && mod == iNTERACTIVE then        
298                                         -- This test is not expensive,
299         lookupQualifiedName rdr_name    -- and only happens for failed lookups
300    else 
301         unboundName rdr_name }
302
303 lookupImportedName :: RdrName -> TcRnIf m n Name
304 -- Lookup the occurrence of an imported name
305 -- The RdrName is *always* qualified or Exact
306 -- Treat it as an original name, and conjure up the Name
307 -- Usually it's Exact or Orig, but it can be Qual if it
308 --      comes from an hi-boot file.  (This minor infelicity is 
309 --      just to reduce duplication in the parser.)
310 lookupImportedName rdr_name
311   | Just n <- isExact_maybe rdr_name 
312         -- This happens in derived code
313   = returnM n
314
315         -- Always Orig, even when reading a .hi-boot file
316   | Just (rdr_mod, rdr_occ) <- isOrig_maybe rdr_name
317   = lookupOrig rdr_mod rdr_occ
318
319   | otherwise
320   = pprPanic "RnEnv.lookupImportedName" (ppr rdr_name)
321
322 unboundName :: RdrName -> RnM Name
323 unboundName rdr_name 
324   = do  { addErr (unknownNameErr rdr_name)
325         ; env <- getGlobalRdrEnv;
326         ; traceRn (vcat [unknownNameErr rdr_name, 
327                          ptext SLIT("Global envt is:"),
328                          nest 3 (pprGlobalRdrEnv env)])
329         ; returnM (mkUnboundName rdr_name) }
330
331 --------------------------------------------------
332 --      Lookup in the Global RdrEnv of the module
333 --------------------------------------------------
334
335 lookupSrcOcc_maybe :: RdrName -> RnM (Maybe Name)
336 -- No filter function; does not report an error on failure
337 lookupSrcOcc_maybe rdr_name
338   = do  { mb_gre <- lookupGreRn_maybe rdr_name
339         ; case mb_gre of
340                 Nothing  -> returnM Nothing
341                 Just gre -> returnM (Just (gre_name gre)) }
342         
343 -------------------------
344 lookupGreRn_maybe :: RdrName -> RnM (Maybe GlobalRdrElt)
345 -- Just look up the RdrName in the GlobalRdrEnv
346 lookupGreRn_maybe rdr_name 
347   = lookupGreRn_help rdr_name (lookupGRE_RdrName rdr_name)
348
349 lookupGreRn :: RdrName -> RnM GlobalRdrElt
350 -- If not found, add error message, and return a fake GRE
351 lookupGreRn rdr_name 
352   = do  { mb_gre <- lookupGreRn_maybe rdr_name
353         ; case mb_gre of {
354             Just gre -> return gre ;
355             Nothing  -> do
356         { name <- unboundName rdr_name
357         ; return (GRE { gre_name = name, gre_par = NoParent,
358                         gre_prov = LocalDef }) }}}
359
360 lookupGreLocalRn :: RdrName -> RnM (Maybe GlobalRdrElt)
361 -- Similar, but restricted to locally-defined things
362 lookupGreLocalRn rdr_name 
363   = lookupGreRn_help rdr_name lookup_fn
364   where
365     lookup_fn env = filter isLocalGRE (lookupGRE_RdrName rdr_name env)
366
367 lookupGreRn_help :: RdrName                     -- Only used in error message
368                  -> (GlobalRdrEnv -> [GlobalRdrElt])    -- Lookup function
369                  -> RnM (Maybe GlobalRdrElt)
370 -- Checks for exactly one match; reports deprecations
371 -- Returns Nothing, without error, if too few
372 lookupGreRn_help rdr_name lookup 
373   = do  { env <- getGlobalRdrEnv
374         ; case lookup env of
375             []    -> returnM Nothing
376             [gre] -> returnM (Just gre)
377             gres  -> do { addNameClashErrRn rdr_name gres
378                         ; returnM (Just (head gres)) } }
379
380 ------------------------------
381 --      GHCi support
382 ------------------------------
383
384 -- A qualified name on the command line can refer to any module at all: we
385 -- try to load the interface if we don't already have it.
386 lookupQualifiedName :: RdrName -> RnM Name
387 lookupQualifiedName rdr_name
388   | Just (mod,occ) <- isQual_maybe rdr_name
389    -- Note: we want to behave as we would for a source file import here,
390    -- and respect hiddenness of modules/packages, hence loadSrcInterface.
391    = loadSrcInterface doc mod False     `thenM` \ iface ->
392
393    case  [ (mod,occ) | 
394            (mod,avails) <- mi_exports iface,
395            avail        <- avails,
396            name         <- availNames avail,
397            name == occ ] of
398       ((mod,occ):ns) -> ASSERT (null ns) 
399                         lookupOrig mod occ
400       _ -> unboundName rdr_name
401
402   | otherwise
403   = pprPanic "RnEnv.lookupQualifiedName" (ppr rdr_name)
404   where
405     doc = ptext SLIT("Need to find") <+> ppr rdr_name
406 \end{code}
407
408 %*********************************************************
409 %*                                                      *
410                 Fixities
411 %*                                                      *
412 %*********************************************************
413
414 \begin{code}
415 lookupLocalDataTcNames :: RdrName -> RnM [Name]
416 -- GHC extension: look up both the tycon and data con 
417 -- for con-like things
418 -- Complain if neither is in scope
419 lookupLocalDataTcNames rdr_name
420   | Just n <- isExact_maybe rdr_name    
421         -- Special case for (:), which doesn't get into the GlobalRdrEnv
422   = return [n]  -- For this we don't need to try the tycon too
423   | otherwise
424   = do  { mb_gres <- mapM lookupGreLocalRn (dataTcOccs rdr_name)
425         ; case [gre_name gre | Just gre <- mb_gres] of
426             [] -> do { addErr (unknownNameErr rdr_name)
427                      ; return [] }
428             names -> return names
429     }
430
431 --------------------------------
432 bindLocalFixities :: [FixitySig RdrName] -> RnM a -> RnM a
433 -- Used for nested fixity decls
434 -- No need to worry about type constructors here,
435 -- Should check for duplicates but we don't
436 bindLocalFixities fixes thing_inside
437   | null fixes = thing_inside
438   | otherwise  = mappM rn_sig fixes     `thenM` \ new_bit ->
439                  extendFixityEnv new_bit thing_inside
440   where
441     rn_sig (FixitySig lv@(L loc v) fix)
442         = addLocM lookupBndrRn lv       `thenM` \ new_v ->
443           returnM (new_v, (FixItem (rdrNameOcc v) fix loc))
444 \end{code}
445
446 --------------------------------
447 lookupFixity is a bit strange.  
448
449 * Nested local fixity decls are put in the local fixity env, which we
450   find with getFixtyEnv
451
452 * Imported fixities are found in the HIT or PIT
453
454 * Top-level fixity decls in this module may be for Names that are
455     either  Global         (constructors, class operations)
456     or      Local/Exported (everything else)
457   (See notes with RnNames.getLocalDeclBinders for why we have this split.)
458   We put them all in the local fixity environment
459
460 \begin{code}
461 lookupFixityRn :: Name -> RnM Fixity
462 lookupFixityRn name
463   = getModule                           `thenM` \ this_mod ->
464     if nameIsLocalOrFrom this_mod name
465     then        -- It's defined in this module
466         getFixityEnv            `thenM` \ local_fix_env ->
467         traceRn (text "lookupFixityRn" <+> (ppr name $$ ppr local_fix_env)) `thenM_`
468         returnM (lookupFixity local_fix_env name)
469
470     else        -- It's imported
471       -- For imported names, we have to get their fixities by doing a
472       -- loadInterfaceForName, and consulting the Ifaces that comes back
473       -- from that, because the interface file for the Name might not
474       -- have been loaded yet.  Why not?  Suppose you import module A,
475       -- which exports a function 'f', thus;
476       --        module CurrentModule where
477       --          import A( f )
478       --        module A( f ) where
479       --          import B( f )
480       -- Then B isn't loaded right away (after all, it's possible that
481       -- nothing from B will be used).  When we come across a use of
482       -- 'f', we need to know its fixity, and it's then, and only
483       -- then, that we load B.hi.  That is what's happening here.
484       --
485       -- loadInterfaceForName will find B.hi even if B is a hidden module,
486       -- and that's what we want.
487         loadInterfaceForName doc name   `thenM` \ iface ->
488         returnM (mi_fix_fn iface (nameOccName name))
489   where
490     doc = ptext SLIT("Checking fixity for") <+> ppr name
491
492 ---------------
493 lookupTyFixityRn :: Located Name -> RnM Fixity
494 lookupTyFixityRn (L loc n)
495   = do  { glaExts <- doptM Opt_GlasgowExts
496         ; when (not glaExts) (addWarnAt loc (infixTyConWarn n))
497         ; lookupFixityRn n }
498
499 ---------------
500 dataTcOccs :: RdrName -> [RdrName]
501 -- If the input is a data constructor, return both it and a type
502 -- constructor.  This is useful when we aren't sure which we are
503 -- looking at.
504 dataTcOccs rdr_name
505   | Just n <- isExact_maybe rdr_name            -- Ghastly special case
506   , n `hasKey` consDataConKey = [rdr_name]      -- see note below
507   | isDataOcc occ             = [rdr_name_tc, rdr_name]
508   | otherwise                 = [rdr_name]
509   where    
510     occ         = rdrNameOcc rdr_name
511     rdr_name_tc = setRdrNameSpace rdr_name tcName
512
513 -- If the user typed "[]" or "(,,)", we'll generate an Exact RdrName,
514 -- and setRdrNameSpace generates an Orig, which is fine
515 -- But it's not fine for (:), because there *is* no corresponding type
516 -- constructor.  If we generate an Orig tycon for GHC.Base.(:), it'll
517 -- appear to be in scope (because Orig's simply allocate a new name-cache
518 -- entry) and then we get an error when we use dataTcOccs in 
519 -- TcRnDriver.tcRnGetInfo.  Large sigh.
520 \end{code}
521
522 %************************************************************************
523 %*                                                                      *
524                         Rebindable names
525         Dealing with rebindable syntax is driven by the 
526         Opt_NoImplicitPrelude dynamic flag.
527
528         In "deriving" code we don't want to use rebindable syntax
529         so we switch off the flag locally
530
531 %*                                                                      *
532 %************************************************************************
533
534 Haskell 98 says that when you say "3" you get the "fromInteger" from the
535 Standard Prelude, regardless of what is in scope.   However, to experiment
536 with having a language that is less coupled to the standard prelude, we're
537 trying a non-standard extension that instead gives you whatever "Prelude.fromInteger"
538 happens to be in scope.  Then you can
539         import Prelude ()
540         import MyPrelude as Prelude
541 to get the desired effect.
542
543 At the moment this just happens for
544   * fromInteger, fromRational on literals (in expressions and patterns)
545   * negate (in expressions)
546   * minus  (arising from n+k patterns)
547   * "do" notation
548
549 We store the relevant Name in the HsSyn tree, in 
550   * HsIntegral/HsFractional     
551   * NegApp
552   * NPlusKPat
553   * HsDo
554 respectively.  Initially, we just store the "standard" name (PrelNames.fromIntegralName,
555 fromRationalName etc), but the renamer changes this to the appropriate user
556 name if Opt_NoImplicitPrelude is on.  That is what lookupSyntaxName does.
557
558 We treat the orignal (standard) names as free-vars too, because the type checker
559 checks the type of the user thing against the type of the standard thing.
560
561 \begin{code}
562 lookupSyntaxName :: Name                                -- The standard name
563                  -> RnM (SyntaxExpr Name, FreeVars)     -- Possibly a non-standard name
564 lookupSyntaxName std_name
565   = doptM Opt_ImplicitPrelude           `thenM` \ implicit_prelude -> 
566     if implicit_prelude then normal_case
567     else
568         -- Get the similarly named thing from the local environment
569     lookupOccRn (mkRdrUnqual (nameOccName std_name)) `thenM` \ usr_name ->
570     returnM (HsVar usr_name, unitFV usr_name)
571   where
572     normal_case = returnM (HsVar std_name, emptyFVs)
573
574 lookupSyntaxTable :: [Name]                             -- Standard names
575                   -> RnM (SyntaxTable Name, FreeVars)   -- See comments with HsExpr.ReboundNames
576 lookupSyntaxTable std_names
577   = doptM Opt_ImplicitPrelude           `thenM` \ implicit_prelude -> 
578     if implicit_prelude then normal_case 
579     else
580         -- Get the similarly named thing from the local environment
581     mappM (lookupOccRn . mkRdrUnqual . nameOccName) std_names   `thenM` \ usr_names ->
582
583     returnM (std_names `zip` map HsVar usr_names, mkFVs usr_names)
584   where
585     normal_case = returnM (std_names `zip` map HsVar std_names, emptyFVs)
586 \end{code}
587
588
589 %*********************************************************
590 %*                                                      *
591 \subsection{Binding}
592 %*                                                      *
593 %*********************************************************
594
595 \begin{code}
596 newLocalsRn :: [Located RdrName] -> RnM [Name]
597 newLocalsRn rdr_names_w_loc
598   = newUniqueSupply             `thenM` \ us ->
599     returnM (zipWith mk rdr_names_w_loc (uniqsFromSupply us))
600   where
601     mk (L loc rdr_name) uniq
602         | Just name <- isExact_maybe rdr_name = name
603                 -- This happens in code generated by Template Haskell 
604         | otherwise = ASSERT2( isUnqual rdr_name, ppr rdr_name )
605                         -- We only bind unqualified names here
606                         -- lookupRdrEnv doesn't even attempt to look up a qualified RdrName
607                       mkInternalName uniq (rdrNameOcc rdr_name) (srcSpanStart loc)
608
609 bindLocatedLocalsRn :: SDoc     -- Documentation string for error message
610                     -> [Located RdrName]
611                     -> ([Name] -> RnM a)
612                     -> RnM a
613 bindLocatedLocalsRn doc_str rdr_names_w_loc enclosed_scope
614   =     -- Check for duplicate names
615     checkDupNames doc_str rdr_names_w_loc       `thenM_`
616
617         -- Warn about shadowing, but only in source modules
618     ifOptM Opt_WarnNameShadowing 
619       (checkShadowing doc_str rdr_names_w_loc)  `thenM_`
620
621         -- Make fresh Names and extend the environment
622     newLocalsRn rdr_names_w_loc         `thenM` \ names ->
623     getLocalRdrEnv                      `thenM` \ local_env ->
624     setLocalRdrEnv (extendLocalRdrEnv local_env names)
625                    (enclosed_scope names)
626
627
628 bindLocalNames :: [Name] -> RnM a -> RnM a
629 bindLocalNames names enclosed_scope
630   = getLocalRdrEnv              `thenM` \ name_env ->
631     setLocalRdrEnv (extendLocalRdrEnv name_env names)
632                     enclosed_scope
633
634 bindLocalNamesFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars)
635 bindLocalNamesFV names enclosed_scope
636   = do  { (result, fvs) <- bindLocalNames names enclosed_scope
637         ; returnM (result, delListFromNameSet fvs names) }
638
639
640 -------------------------------------
641         -- binLocalsFVRn is the same as bindLocalsRn
642         -- except that it deals with free vars
643 bindLocatedLocalsFV :: SDoc -> [Located RdrName] -> ([Name] -> RnM (a,FreeVars))
644   -> RnM (a, FreeVars)
645 bindLocatedLocalsFV doc rdr_names enclosed_scope
646   = bindLocatedLocalsRn doc rdr_names   $ \ names ->
647     enclosed_scope names                `thenM` \ (thing, fvs) ->
648     returnM (thing, delListFromNameSet fvs names)
649
650 -------------------------------------
651 bindTyVarsRn :: SDoc -> [LHsTyVarBndr RdrName]
652               -> ([LHsTyVarBndr Name] -> RnM a)
653               -> RnM a
654 -- Haskell-98 binding of type variables; e.g. within a data type decl
655 bindTyVarsRn doc_str tyvar_names enclosed_scope
656   = let
657         located_tyvars = hsLTyVarLocNames tyvar_names
658     in
659     bindLocatedLocalsRn doc_str located_tyvars  $ \ names ->
660     enclosed_scope (zipWith replace tyvar_names names)
661     where 
662         replace (L loc n1) n2 = L loc (replaceTyVarName n1 n2)
663
664 bindPatSigTyVars :: [LHsType RdrName] -> ([Name] -> RnM a) -> RnM a
665   -- Find the type variables in the pattern type 
666   -- signatures that must be brought into scope
667 bindPatSigTyVars tys thing_inside
668   = do  { scoped_tyvars <- doptM Opt_ScopedTypeVariables
669         ; if not scoped_tyvars then 
670                 thing_inside []
671           else 
672     do  { name_env <- getLocalRdrEnv
673         ; let locd_tvs  = [ tv | ty <- tys
674                                , tv <- extractHsTyRdrTyVars ty
675                                , not (unLoc tv `elemLocalRdrEnv` name_env) ]
676               nubbed_tvs = nubBy eqLocated locd_tvs
677                 -- The 'nub' is important.  For example:
678                 --      f (x :: t) (y :: t) = ....
679                 -- We don't want to complain about binding t twice!
680
681         ; bindLocatedLocalsRn doc_sig nubbed_tvs thing_inside }}
682   where
683     doc_sig = text "In a pattern type-signature"
684
685 bindPatSigTyVarsFV :: [LHsType RdrName]
686                    -> RnM (a, FreeVars)
687                    -> RnM (a, FreeVars)
688 bindPatSigTyVarsFV tys thing_inside
689   = bindPatSigTyVars tys        $ \ tvs ->
690     thing_inside                `thenM` \ (result,fvs) ->
691     returnM (result, fvs `delListFromNameSet` tvs)
692
693 bindSigTyVarsFV :: [Name]
694                 -> RnM (a, FreeVars)
695                 -> RnM (a, FreeVars)
696 bindSigTyVarsFV tvs thing_inside
697   = do  { scoped_tyvars <- doptM Opt_ScopedTypeVariables
698         ; if not scoped_tyvars then 
699                 thing_inside 
700           else
701                 bindLocalNamesFV tvs thing_inside }
702
703 extendTyVarEnvFVRn :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars)
704         -- This function is used only in rnSourceDecl on InstDecl
705 extendTyVarEnvFVRn tyvars thing_inside = bindLocalNamesFV tyvars thing_inside
706
707 -------------------------------------
708 checkDupNames :: SDoc
709               -> [Located RdrName]
710               -> RnM ()
711 checkDupNames doc_str rdr_names_w_loc
712   =     -- Check for duplicated names in a binding group
713     mappM_ (dupNamesErr doc_str) dups
714   where
715     (_, dups) = removeDups (\n1 n2 -> unLoc n1 `compare` unLoc n2) rdr_names_w_loc
716
717 -------------------------------------
718 checkShadowing doc_str loc_rdr_names
719   = getLocalRdrEnv              `thenM` \ local_env ->
720     getGlobalRdrEnv             `thenM` \ global_env ->
721     let
722       check_shadow (L loc rdr_name)
723         |  rdr_name `elemLocalRdrEnv` local_env 
724         || not (null (lookupGRE_RdrName rdr_name global_env ))
725         = addWarnAt loc (shadowedNameWarn doc_str rdr_name)
726         | otherwise = returnM ()
727     in
728     mappM_ check_shadow loc_rdr_names
729 \end{code}
730
731
732 %************************************************************************
733 %*                                                                      *
734 \subsection{Free variable manipulation}
735 %*                                                                      *
736 %************************************************************************
737
738 \begin{code}
739 -- A useful utility
740 mapFvRn f xs = mappM f xs       `thenM` \ stuff ->
741                let
742                   (ys, fvs_s) = unzip stuff
743                in
744                returnM (ys, plusFVs fvs_s)
745 \end{code}
746
747
748 %************************************************************************
749 %*                                                                      *
750 \subsection{Envt utility functions}
751 %*                                                                      *
752 %************************************************************************
753
754 \begin{code}
755 warnUnusedModules :: [(ModuleName,SrcSpan)] -> RnM ()
756 warnUnusedModules mods
757   = ifOptM Opt_WarnUnusedImports (mappM_ bleat mods)
758   where
759     bleat (mod,loc) = addWarnAt loc (mk_warn mod)
760     mk_warn m = vcat [ptext SLIT("Module") <+> quotes (ppr m)
761                         <+> text "is imported, but nothing from it is used,",
762                       nest 2 (ptext SLIT("except perhaps instances visible in") 
763                         <+> quotes (ppr m)),
764                       ptext SLIT("To suppress this warning, use:") 
765                         <+> ptext SLIT("import") <+> ppr m <> parens empty ]
766
767
768 warnUnusedImports, warnUnusedTopBinds :: [GlobalRdrElt] -> RnM ()
769 warnUnusedImports gres  = ifOptM Opt_WarnUnusedImports (warnUnusedGREs gres)
770 warnUnusedTopBinds gres = ifOptM Opt_WarnUnusedBinds   (warnUnusedGREs gres)
771
772 warnUnusedLocalBinds, warnUnusedMatches :: [Name] -> RnM ()
773 warnUnusedLocalBinds names = ifOptM Opt_WarnUnusedBinds   (warnUnusedLocals names)
774 warnUnusedMatches    names = ifOptM Opt_WarnUnusedMatches (warnUnusedLocals names)
775
776 -------------------------
777 --      Helpers
778 warnUnusedGREs gres 
779  = warnUnusedBinds [(n,Just p) | GRE {gre_name = n, gre_prov = p} <- gres]
780
781 warnUnusedLocals names
782  = warnUnusedBinds [(n,Nothing) | n<-names]
783
784 warnUnusedBinds :: [(Name,Maybe Provenance)] -> RnM ()
785 warnUnusedBinds names  = mappM_ warnUnusedName (filter reportable names)
786  where reportable (name,_) 
787         | isWiredInName name = False    -- Don't report unused wired-in names
788                                         -- Otherwise we get a zillion warnings
789                                         -- from Data.Tuple
790         | otherwise = reportIfUnused (nameOccName name)
791
792 -------------------------
793
794 warnUnusedName :: (Name, Maybe Provenance) -> RnM ()
795 warnUnusedName (name, prov)
796   = addWarnAt loc $
797     sep [msg <> colon, 
798          nest 2 $ pprNonVarNameSpace (occNameSpace (nameOccName name))
799                         <+> quotes (ppr name)]
800         -- TODO should be a proper span
801   where
802     (loc,msg) = case prov of
803                   Just (Imported is)
804                         -> (importSpecLoc imp_spec, imp_from (importSpecModule imp_spec))
805                         where
806                           imp_spec = head is
807                   other -> (srcLocSpan (nameSrcLoc name), unused_msg)
808
809     unused_msg   = text "Defined but not used"
810     imp_from mod = text "Imported from" <+> quotes (ppr mod) <+> text "but not used"
811 \end{code}
812
813 \begin{code}
814 addNameClashErrRn rdr_name names
815   = addErr (vcat [ptext SLIT("Ambiguous occurrence") <+> quotes (ppr rdr_name),
816                   ptext SLIT("It could refer to") <+> vcat (msg1 : msgs)])
817   where
818     (np1:nps) = names
819     msg1 = ptext  SLIT("either") <+> mk_ref np1
820     msgs = [ptext SLIT("    or") <+> mk_ref np | np <- nps]
821     mk_ref gre = quotes (ppr (gre_name gre)) <> comma <+> pprNameProvenance gre
822
823 shadowedNameWarn doc shadow
824   = hsep [ptext SLIT("This binding for"), 
825                quotes (ppr shadow),
826                ptext SLIT("shadows an existing binding")]
827     $$ doc
828
829 unknownNameErr rdr_name
830   = sep [ptext SLIT("Not in scope:"), 
831          nest 2 $ pprNonVarNameSpace (occNameSpace (rdrNameOcc rdr_name))
832                   <+> quotes (ppr rdr_name)]
833
834 unknownInstBndrErr cls op
835   = quotes (ppr op) <+> ptext SLIT("is not a (visible) method of class") <+> quotes (ppr cls)
836
837 badOrigBinding name
838   = ptext SLIT("Illegal binding of built-in syntax:") <+> ppr (rdrNameOcc name)
839         -- The rdrNameOcc is because we don't want to print Prelude.(,)
840
841 dupNamesErr :: SDoc -> [Located RdrName] -> RnM ()
842 dupNamesErr descriptor located_names
843   = addErrAt big_loc $
844     vcat [ptext SLIT("Conflicting definitions for") <+> quotes (ppr name1),
845           locations, descriptor]
846   where
847     L _ name1 = head located_names
848     locs      = map getLoc located_names
849     big_loc   = foldr1 combineSrcSpans locs
850     one_line  = isOneLineSpan big_loc
851     locations | one_line  = empty 
852               | otherwise = ptext SLIT("Bound at:") <+> 
853                             vcat (map ppr (sortLe (<=) locs))
854
855 badQualBndrErr rdr_name
856   = ptext SLIT("Qualified name in binding position:") <+> ppr rdr_name
857
858 infixTyConWarn op
859   = vcat [ftext FSLIT("Accepting non-standard infix type constructor") <+> quotes (ppr op),
860           ftext FSLIT("Use -fglasgow-exts to avoid this warning")]
861 \end{code}