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