Add separate functions for querying DynFlag and ExtensionFlag options
[ghc-hetmet.git] / compiler / rename / RnExpr.lhs
index 78088d5..de7760e 100644 (file)
@@ -30,7 +30,7 @@ import RnEnv
 import RnTypes         ( rnHsTypeFVs, rnSplice, checkTH,
                          mkOpFormRn, mkOpAppRn, mkNegAppRn, checkSectionPrec)
 import RnPat
-import DynFlags                ( DynFlag(..) )
+import DynFlags
 import BasicTypes      ( FixityDirection(..) )
 import PrelNames
 
@@ -110,7 +110,7 @@ rnExpr (HsIPVar v)
 
 rnExpr (HsLit lit@(HsString s))
   = do {
-         opt_OverloadedStrings <- doptM Opt_OverloadedStrings
+         opt_OverloadedStrings <- xoptM Opt_OverloadedStrings
        ; if opt_OverloadedStrings then
             rnExpr (HsOverLit (mkHsIsString s placeHolderType))
         else -- Same as below
@@ -605,7 +605,7 @@ rnBracket (DecBrL decls)
   = do { (group, mb_splice) <- findSplice decls
        ; case mb_splice of
            Nothing -> return ()
-           Just (SpliceDecl (L loc _), _)  
+           Just (SpliceDecl (L loc _) _, _)  
               -> setSrcSpan loc $
                  addErr (ptext (sLit "Declaration splices are not permitted inside declaration brackets"))
                -- Why not?  See Section 7.3 of the TH paper.  
@@ -618,8 +618,9 @@ rnBracket (DecBrL decls)
                                      setStage thRnBrack $
                              rnSrcDecls group      
 
-       -- Discard the tcg_env; it contains only extra info about fixity
-       ; return (DecBrG group', allUses (tcg_dus tcg_env)) }
+             -- Discard the tcg_env; it contains only extra info about fixity
+        ; traceRn (text "rnBracket dec" <+> (ppr (tcg_dus tcg_env) $$ ppr (duUses (tcg_dus tcg_env))))
+       ; return (DecBrG group', duUses (tcg_dus tcg_env)) }
 
 rnBracket (DecBrG _) = panic "rnBracket: unexpected DecBrG"
 \end{code}
@@ -780,6 +781,7 @@ rnStmt ctxt (L loc (GroupStmt stmts _ by using)) thing_inside
 
        ; let all_fvs  = fvs1 `plusFV` fvs2 
              bndr_map = used_bndrs `zip` used_bndrs
+            -- See Note [GroupStmt binder map] in HsExpr
 
        ; traceRn (text "rnStmt: implicitly rebound these used binders:" <+> ppr bndr_map)
        ; return (([L loc (GroupStmt stmts' bndr_map by' using')], thing), all_fvs) }
@@ -885,7 +887,8 @@ rn_rec_stmts_and_then s cont
 
          --    ...bring them and their fixities into scope
        ; let bound_names = collectLStmtsBinders (map fst new_lhs_and_fv)
-       ; bindLocalNamesFV_WithFixities bound_names fix_env $ do
+       ; bindLocalNamesFV bound_names $
+          addLocalFixities fix_env bound_names $ do
 
          -- (C) do the right-hand-sides and thing-inside
        { segs <- rn_rec_stmts bound_names new_lhs_and_fv
@@ -992,8 +995,8 @@ 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 (mkNameSet all_bndrs) binds'
-  return [(duDefs du_binds, duUses du_binds, 
-           emptyNameSet, L loc (LetStmt (HsValBinds binds')))]
+  return [(duDefs du_binds, allUses du_binds, 
+          emptyNameSet, L loc (LetStmt (HsValBinds binds')))]
 
 -- no RecStmt case becuase they get flattened above when doing the LHSes
 rn_rec_stmt _ stmt@(L _ (RecStmt {})) _
@@ -1172,7 +1175,7 @@ checkRecStmt ctxt   = addErr msg
 ---------
 checkParStmt :: HsStmtContext Name -> RnM ()
 checkParStmt _
-  = do { parallel_list_comp <- doptM Opt_ParallelListComp
+  = do { parallel_list_comp <- xoptM Opt_ParallelListComp
        ; checkErr parallel_list_comp msg }
   where
     msg = ptext (sLit "Illegal parallel list comprehension: use -XParallelListComp")
@@ -1181,7 +1184,7 @@ checkParStmt _
 checkTransformStmt :: HsStmtContext Name -> RnM ()
 checkTransformStmt ListComp  -- Ensure we are really within a list comprehension because otherwise the
                             -- desugarer will break when we come to operate on a parallel array
-  = do { transform_list_comp <- doptM Opt_TransformListComp
+  = do { transform_list_comp <- xoptM Opt_TransformListComp
        ; checkErr transform_list_comp msg }
   where
     msg = ptext (sLit "Illegal transform or grouping list comprehension: use -XTransformListComp")
@@ -1194,7 +1197,7 @@ checkTransformStmt ctxt = addErr msg
 ---------
 checkTupleSection :: [HsTupArg RdrName] -> RnM ()
 checkTupleSection args
-  = do { tuple_section <- doptM Opt_TupleSections
+  = do { tuple_section <- xoptM Opt_TupleSections
        ; checkErr (all tupArgPresent args || tuple_section) msg }
   where
     msg = ptext (sLit "Illegal tuple section: use -XTupleSections")