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