Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/69762107e4ff9aab809eba4312c2844ff32d9902

>---------------------------------------------------------------

commit 69762107e4ff9aab809eba4312c2844ff32d9902
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Mon Oct 15 15:46:48 2012 +0100

    Refactor the type of tcBracked (no change in behaviour)

>---------------------------------------------------------------

 compiler/typecheck/TcExpr.lhs        |    3 +--
 compiler/typecheck/TcSplice.lhs      |    4 ++--
 compiler/typecheck/TcSplice.lhs-boot |    2 +-
 3 files changed, 4 insertions(+), 5 deletions(-)

diff --git a/compiler/typecheck/TcExpr.lhs b/compiler/typecheck/TcExpr.lhs
index e21eb4e..9075033 100644
--- a/compiler/typecheck/TcExpr.lhs
+++ b/compiler/typecheck/TcExpr.lhs
@@ -823,8 +823,7 @@ tcExpr (PArrSeq _ _) _
 #ifdef GHCI    /* Only if bootstrapped */
        -- Rename excludes these cases otherwise
 tcExpr (HsSpliceE splice) res_ty = tcSpliceExpr splice res_ty
-tcExpr (HsBracket brack)  res_ty = do  { e <- tcBracket brack res_ty
-                                       ; return (unLoc e) }
+tcExpr (HsBracket brack)  res_ty = tcBracket brack res_ty
 tcExpr e@(HsQuasiQuoteE _) _ =
     pprPanic "Should never see HsQuasiQuoteE in type checker" (ppr e)
 #endif /* GHCI */
diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs
index 7c064b8..bcaca71 100644
--- a/compiler/typecheck/TcSplice.lhs
+++ b/compiler/typecheck/TcSplice.lhs
@@ -284,7 +284,7 @@ The predicate we use is TcEnv.thTopLevelId.
 %************************************************************************
 
 \begin{code}
-tcBracket     :: HsBracket Name -> TcRhoType -> TcM (LHsExpr TcId)
+tcBracket     :: HsBracket Name -> TcRhoType -> TcM (HsExpr TcId)
 tcSpliceDecls :: LHsExpr Name -> TcM [LHsDecl RdrName]
 tcSpliceExpr  :: HsSplice Name -> TcRhoType -> TcM (HsExpr TcId)
 tcSpliceType  :: HsSplice Name -> FreeVars -> TcM (TcType, TcKind)
@@ -365,7 +365,7 @@ tcBracket brack res_ty
         -- Return the original expression, not the type-decorated one
        ; pendings <- readMutVar pending_splices
        ; co <- unifyType meta_ty res_ty
-       ; return (noLoc (mkHsWrapCo co (HsBracketOut brack pendings))) }
+       ; return (mkHsWrapCo co (HsBracketOut brack pendings)) }
 
 tc_bracket :: ThStage -> HsBracket Name -> TcM TcType
 tc_bracket outer_stage br@(VarBr _ name)     -- Note [Quoting names]
diff --git a/compiler/typecheck/TcSplice.lhs-boot 
b/compiler/typecheck/TcSplice.lhs-boot
index de14aa3..4f185fb 100644
--- a/compiler/typecheck/TcSplice.lhs-boot
+++ b/compiler/typecheck/TcSplice.lhs-boot
@@ -18,7 +18,7 @@ tcSpliceType :: HsSplice Name -> FreeVars -> TcM (TcType, 
TcKind)
 
 tcBracket :: HsBracket Name 
           -> TcRhoType
-          -> TcM (LHsExpr TcId)
+          -> TcM (HsExpr TcId)
 
 tcSpliceDecls :: LHsExpr Name -> TcM [LHsDecl RdrName]
 



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to