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