X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Frename%2FRnExpr.lhs;h=103badca9e9758e02e212ee9a4b2c5c4e25250d5;hb=174dccda5a8213f9a777ddf5230effef6b5f464d;hp=716a7a2c721940f12b0f847860f0ef4be80add87;hpb=7b9ccfe6947e4ef514057668d6f6673c3fedc10d;p=ghc-hetmet.git diff --git a/compiler/rename/RnExpr.lhs b/compiler/rename/RnExpr.lhs index 716a7a2..103badc 100644 --- a/compiler/rename/RnExpr.lhs +++ b/compiler/rename/RnExpr.lhs @@ -25,13 +25,14 @@ import RnBinds ( rnLocalBindsAndThen, rnValBindsLHS, rnValBindsRHS, rnMatchGroup, makeMiniFixityEnv) import HsSyn import TcRnMonad +import TcEnv ( thRnBrack ) import RnEnv import RnTypes ( rnHsTypeFVs, mkOpFormRn, mkOpAppRn, mkNegAppRn, checkSectionPrec) import RnPat import DynFlags ( DynFlag(..) ) import BasicTypes ( FixityDirection(..) ) -import PrelNames ( thFAKE, hasKey, assertIdKey, assertErrorName, +import PrelNames ( hasKey, assertIdKey, assertErrorName, loopAName, choiceAName, appAName, arrAName, composeAName, firstAName, negateName, thenMName, bindMName, failMName, groupWithName ) @@ -166,10 +167,7 @@ rnExpr (NegApp e _) mkNegAppRn e' neg_name `thenM` \ final_e -> returnM (final_e, fv_e `plusFV` fv_neg) -rnExpr (HsPar e) - = rnLExpr e `thenM` \ (e', fvs_e) -> - returnM (HsPar e', fvs_e) - +------------------------------------------ -- Template Haskell extensions -- Don't ifdef-GHCI them because we want to fail gracefully -- (not with an rnExpr crash) in a stage-1 compiler. @@ -192,18 +190,27 @@ rnExpr (HsQuasiQuoteE qq) returnM (expr'', fvs_qq `plusFV` fvs_expr) #endif /* GHCI */ -rnExpr section@(SectionL expr op) - = rnLExpr expr `thenM` \ (expr', fvs_expr) -> - rnLExpr op `thenM` \ (op', fvs_op) -> - checkSectionPrec InfixL section op' expr' `thenM_` - returnM (SectionL expr' op', fvs_op `plusFV` fvs_expr) +--------------------------------------------- +-- Sections +-- See Note [Parsing sections] in Parser.y.pp +rnExpr (HsPar (L loc (section@(SectionL {})))) + = do { (section', fvs) <- rnSection section + ; return (HsPar (L loc section'), fvs) } + +rnExpr (HsPar (L loc (section@(SectionR {})))) + = do { (section', fvs) <- rnSection section + ; return (HsPar (L loc section'), fvs) } + +rnExpr (HsPar e) + = do { (e', fvs_e) <- rnLExpr e + ; return (HsPar e', fvs_e) } -rnExpr section@(SectionR op expr) - = rnLExpr op `thenM` \ (op', fvs_op) -> - rnLExpr expr `thenM` \ (expr', fvs_expr) -> - checkSectionPrec InfixR section op' expr' `thenM_` - returnM (SectionR op' expr', fvs_op `plusFV` fvs_expr) +rnExpr expr@(SectionL {}) + = do { addErr (sectionErr expr); rnSection expr } +rnExpr expr@(SectionR {}) + = do { addErr (sectionErr expr); rnSection expr } +--------------------------------------------- rnExpr (HsCoreAnn ann expr) = rnLExpr expr `thenM` \ (expr', fvs_expr) -> returnM (HsCoreAnn ann expr', fvs_expr) @@ -344,8 +351,24 @@ rnExpr (HsArrForm op fixity cmds) rnExpr other = pprPanic "rnExpr: unexpected expression" (ppr other) -- HsWrap -\end{code} +---------------------- +-- See Note [Parsing sections] in Parser.y.pp +rnSection :: HsExpr RdrName -> RnM (HsExpr Name, FreeVars) +rnSection section@(SectionR op expr) + = do { (op', fvs_op) <- rnLExpr op + ; (expr', fvs_expr) <- rnLExpr expr + ; checkSectionPrec InfixR section op' expr' + ; return (SectionR op' expr', fvs_op `plusFV` fvs_expr) } + +rnSection section@(SectionL expr op) + = do { (expr', fvs_expr) <- rnLExpr expr + ; (op', fvs_op) <- rnLExpr op + ; checkSectionPrec InfixL section op' expr' + ; return (SectionL expr' op', fvs_op `plusFV` fvs_expr) } + +rnSection other = pprPanic "rnSection" (ppr other) +\end{code} %************************************************************************ %* * @@ -572,31 +595,15 @@ rnBracket (TypBr t) = do { (t', fvs) <- rnHsTypeFVs doc t rnBracket (DecBr group) = do { gbl_env <- getGblEnv - ; let new_gbl_env = gbl_env { -- Set the module to thFAKE. The top-level names from the bracketed - -- declarations will go into the name cache, and we don't want them to - -- confuse the Names for the current module. - -- By using a pretend module, thFAKE, we keep them safely out of the way. - tcg_mod = thFAKE, - - -- The emptyDUs is so that we just collect uses for this group alone - -- in the call to rnSrcDecls below - tcg_dus = emptyDUs } - ; setGblEnv new_gbl_env $ do { - - -- In this situation we want to *shadow* top-level bindings. - -- foo = 1 - -- bar = [d| foo = 1 |] - -- If we don't shadow, we'll get an ambiguity complaint when we do - -- a lookupTopBndrRn (which uses lookupGreLocalRn) on the binder of the 'foo' - -- - -- Furthermore, arguably if the splice does define foo, that should hide - -- any foo's further out - -- - -- The shadowing is acheived by calling rnSrcDecls with True as the shadowing flag - ; (tcg_env, group') <- rnSrcDecls True group + ; let new_gbl_env = gbl_env { tcg_dus = emptyDUs } + -- The emptyDUs is so that we just collect uses for this + -- group alone in the call to rnSrcDecls below + ; (tcg_env, group') <- setGblEnv new_gbl_env $ + setStage thRnBrack $ + rnSrcDecls group -- Discard the tcg_env; it contains only extra info about fixity - ; return (DecBr group', allUses (tcg_dus tcg_env)) } } + ; return (DecBr group', allUses (tcg_dus tcg_env)) } \end{code} %************************************************************************ @@ -995,7 +1002,7 @@ rn_rec_stmt _ (L _ (LetStmt binds@(HsIPBinds _))) _ rn_rec_stmt all_bndrs (L loc (LetStmt (HsValBinds binds'))) _ = do (binds', du_binds) <- -- fixities and unused are handled above in rn_rec_stmts_and_then - rnValBindsRHS all_bndrs binds' + rnValBindsRHS (mkNameSet all_bndrs) binds' returnM [(duDefs du_binds, duUses du_binds, emptyNameSet, L loc (LetStmt (HsValBinds binds')))] @@ -1128,7 +1135,7 @@ segsToStmts ((defs, uses, fwds, ss) : segs) fvs_later \begin{code} srcSpanPrimLit :: SrcSpan -> HsExpr Name -srcSpanPrimLit span = HsLit (HsStringPrim (mkFastString (showSDoc (ppr span)))) +srcSpanPrimLit span = HsLit (HsStringPrim (mkFastString (showSDocOneLine (ppr span)))) mkAssertErrorExpr :: RnM (HsExpr Name) -- Return an expression for (assertError "Foo.hs:27") @@ -1198,6 +1205,11 @@ checkTransformStmt ctxt = addErr msg msg = ptext (sLit "Illegal transform or grouping in") <+> pprStmtContext ctxt --------- +sectionErr :: HsExpr RdrName -> SDoc +sectionErr expr + = hang (ptext (sLit "A section must be enclosed in parentheses")) + 2 (ptext (sLit "thus:") <+> (parens (ppr expr))) + patSynErr :: HsExpr RdrName -> RnM (HsExpr Name, FreeVars) patSynErr e = do { addErr (sep [ptext (sLit "Pattern syntax in expression context:"), nest 4 (ppr e)])