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