summaryrefslogtreecommitdiff
path: root/ghc/compiler/rename/RnEnv.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2001-03-23 14:51:54 +0000
committersimonpj <unknown>2001-03-23 14:51:54 +0000
commit09fe7371cd36dd78b3801cc1c548bb375da7f2d9 (patch)
tree0b2474123aac97e9b9350400df38b8c11b177de5 /ghc/compiler/rename/RnEnv.lhs
parent1c4b7a51cb0a6d15432d35f018429a0f88f06d37 (diff)
downloadhaskell-09fe7371cd36dd78b3801cc1c548bb375da7f2d9.tar.gz
[project @ 2001-03-23 14:51:54 by simonpj]
Fix renamer error that prevented PrelBase compiling
Diffstat (limited to 'ghc/compiler/rename/RnEnv.lhs')
-rw-r--r--ghc/compiler/rename/RnEnv.lhs13
1 files changed, 11 insertions, 2 deletions
diff --git a/ghc/compiler/rename/RnEnv.lhs b/ghc/compiler/rename/RnEnv.lhs
index e7f101f5c3..3c25da03a8 100644
--- a/ghc/compiler/rename/RnEnv.lhs
+++ b/ghc/compiler/rename/RnEnv.lhs
@@ -10,7 +10,6 @@ module RnEnv where -- Export everything
import {-# SOURCE #-} RnHiFiles
-import HscTypes ( ModIface(..) )
import HsSyn
import RdrHsSyn ( RdrNameIE )
import RdrName ( RdrName, rdrNameModule, rdrNameOcc, isQual, isUnqual, isOrig,
@@ -20,6 +19,7 @@ import HsTypes ( hsTyVarName, replaceTyVarName )
import HscTypes ( Provenance(..), pprNameProvenance, hasBetterProv,
ImportReason(..), GlobalRdrEnv, GlobalRdrElt(..), AvailEnv,
AvailInfo, Avails, GenAvailInfo(..), NameSupply(..),
+ ModIface(..),
Deprecations(..), lookupDeprec,
extendLocalRdrEnv
)
@@ -199,6 +199,15 @@ lookupTopBndrRn rdr_name
-- So we have to filter out the non-local ones.
-- A separate function (importsFromLocalDecls) reports duplicate top level
-- decls, so here it's safe just to choose an arbitrary one.
+
+ | isOrig rdr_name
+ -- This is here just to catch the PrelBase defn of (say) [] and similar
+ -- The parser reads the special syntax and returns an Orig RdrName
+ -- But the global_env contains only Qual RdrNames, so we won't
+ -- find it there; instead just get the name via the Orig route
+ = lookupOrigName rdr_name
+
+ | otherwise
= getModeRn `thenRn` \ mode ->
if isInterfaceMode mode
then lookupIfaceName rdr_name
@@ -216,7 +225,7 @@ lookupTopBndrRn rdr_name
Just gres -> case [n | GRE n _ _ <- gres, nameIsLocalOrFrom mod n] of
[] -> Nothing
(n:ns) -> Just n
-
+
-- lookupSigOccRn is used for type signatures and pragmas
-- Is this valid?