summaryrefslogtreecommitdiff
path: root/ghc/compiler/rename/RnEnv.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2005-04-04 11:55:17 +0000
committersimonpj <unknown>2005-04-04 11:55:17 +0000
commitd551dbfef0b710f5ede21ee0c54ee7e80dd53b64 (patch)
treef49de74d65f1a0351751b7298b518764e1bbe90d /ghc/compiler/rename/RnEnv.lhs
parentcb486104c9225bb44f5ccdd700ff204a37014207 (diff)
downloadhaskell-d551dbfef0b710f5ede21ee0c54ee7e80dd53b64.tar.gz
[project @ 2005-04-04 11:55:11 by simonpj]
This commit combines three overlapping things: 1. Make rebindable syntax work for do-notation. The idea here is that, in particular, (>>=) can have a type that has class constraints on its argument types, e.g. (>>=) :: (Foo m, Baz a) => m a -> (a -> m b) -> m b The consequence is that a BindStmt and ExprStmt must have individual evidence attached -- previously it was one batch of evidence for the entire Do Sadly, we can't do this for MDo, because we use bind at a polymorphic type (to tie the knot), so we still use one blob of evidence (now in the HsStmtContext) for MDo. For arrow syntax, the evidence is in the HsCmd. For list comprehensions, it's all built-in anyway. So the evidence on a BindStmt is only used for ordinary do-notation. 2. Tidy up HsSyn. In particular: - Eliminate a few "Out" forms, which we can manage without (e.g. - It ought to be the case that the type checker only decorates the syntax tree, but doesn't change one construct into another. That wasn't true for NPat, LitPat, NPlusKPat, so I've fixed that. - Eliminate ResultStmts from Stmt. They always had to be the last Stmt, which led to awkward pattern matching in some places; and the benefits didn't seem to outweigh the costs. Now each construct that uses [Stmt] has a result expression too (e.g. GRHS). 3. Make 'deriving( Ix )' generate a binding for unsafeIndex, rather than for index. This is loads more efficient. (This item only affects TcGenDeriv, but some of point (2) also affects TcGenDeriv, so it has to be in one commit.)
Diffstat (limited to 'ghc/compiler/rename/RnEnv.lhs')
-rw-r--r--ghc/compiler/rename/RnEnv.lhs20
1 files changed, 10 insertions, 10 deletions
diff --git a/ghc/compiler/rename/RnEnv.lhs b/ghc/compiler/rename/RnEnv.lhs
index fadf87a6d5..116f9de411 100644
--- a/ghc/compiler/rename/RnEnv.lhs
+++ b/ghc/compiler/rename/RnEnv.lhs
@@ -13,7 +13,7 @@ module RnEnv (
lookupTopFixSigNames, lookupSrcOcc_maybe,
lookupFixityRn, lookupLocatedSigOccRn,
lookupLocatedInstDeclBndr,
- lookupSyntaxName, lookupSyntaxNames, lookupImportedName,
+ lookupSyntaxName, lookupSyntaxTable, lookupImportedName,
newLocalsRn, newIPNameRn,
bindLocalNames, bindLocalNamesFV,
@@ -32,7 +32,7 @@ module RnEnv (
import LoadIface ( loadHomeInterface, loadSrcInterface )
import IfaceEnv ( lookupOrig, newGlobalBinder, newIPName )
-import HsSyn ( FixitySig(..), ReboundNames, HsExpr(..),
+import HsSyn ( FixitySig(..), HsExpr(..), SyntaxExpr, SyntaxTable,
HsType(..), HsExplicitForAll(..), LHsTyVarBndr, LHsType,
LSig, Sig(..), Fixity, hsLTyVarName, hsLTyVarLocNames, replaceTyVarName )
import RdrHsSyn ( extractHsTyRdrTyVars )
@@ -485,7 +485,7 @@ At the moment this just happens for
We store the relevant Name in the HsSyn tree, in
* HsIntegral/HsFractional
* NegApp
- * NPlusKPatIn
+ * NPlusKPat
* HsDo
respectively. Initially, we just store the "standard" name (PrelNames.fromIntegralName,
fromRationalName etc), but the renamer changes this to the appropriate user
@@ -495,21 +495,21 @@ We treat the orignal (standard) names as free-vars too, because the type checker
checks the type of the user thing against the type of the standard thing.
\begin{code}
-lookupSyntaxName :: Name -- The standard name
- -> RnM (Name, FreeVars) -- Possibly a non-standard name
+lookupSyntaxName :: Name -- The standard name
+ -> RnM (SyntaxExpr Name, FreeVars) -- Possibly a non-standard name
lookupSyntaxName std_name
= doptM Opt_ImplicitPrelude `thenM` \ implicit_prelude ->
if implicit_prelude then normal_case
else
-- Get the similarly named thing from the local environment
lookupOccRn (mkRdrUnqual (nameOccName std_name)) `thenM` \ usr_name ->
- returnM (usr_name, unitFV usr_name)
+ returnM (HsVar usr_name, unitFV usr_name)
where
- normal_case = returnM (std_name, emptyFVs)
+ normal_case = returnM (HsVar std_name, emptyFVs)
-lookupSyntaxNames :: [Name] -- Standard names
- -> RnM (ReboundNames Name, FreeVars) -- See comments with HsExpr.ReboundNames
-lookupSyntaxNames std_names
+lookupSyntaxTable :: [Name] -- Standard names
+ -> RnM (SyntaxTable Name, FreeVars) -- See comments with HsExpr.ReboundNames
+lookupSyntaxTable std_names
= doptM Opt_ImplicitPrelude `thenM` \ implicit_prelude ->
if implicit_prelude then normal_case
else