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