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