[commit: ghc] master: Inline solveTopConstraints (29b4632)

git at git.haskell.org git at git.haskell.org
Thu Jan 7 08:36:32 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/29b463278bf59809a929ef9cad4a3fcacc12c0da/ghc

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

commit 29b463278bf59809a929ef9cad4a3fcacc12c0da
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Jan 6 17:15:47 2016 +0000

    Inline solveTopConstraints
    
    It was only called in one place; easier to inline it


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

29b463278bf59809a929ef9cad4a3fcacc12c0da
 compiler/typecheck/TcSimplify.hs | 10 +---------
 compiler/typecheck/TcSplice.hs   |  3 ++-
 2 files changed, 3 insertions(+), 10 deletions(-)

diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index 6114e13..4a5d131 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE CPP #-}
 
 module TcSimplify(
-       simplifyInfer, solveTopConstraints,
+       simplifyInfer,
        growThetaTyVars,
        simplifyAmbiguityCheck,
        simplifyDefault,
@@ -187,14 +187,6 @@ defaultCallStacks wanteds
     = return (Just ct)
 
 
--- | Type-check a thing, returning the result and any EvBinds produced
--- during solving. Emits errors -- but does not fail -- if there is trouble.
-solveTopConstraints :: TcM a -> TcM (a, Bag EvBind)
-solveTopConstraints thing_inside
-  = do { (result, wanted) <- captureConstraints thing_inside
-       ; ev_binds <- simplifyTop wanted
-       ; return (result, ev_binds) }
-
 {-
 Note [When to do type-class defaulting]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs
index 2de83c4..63a3371 100644
--- a/compiler/typecheck/TcSplice.hs
+++ b/compiler/typecheck/TcSplice.hs
@@ -528,7 +528,8 @@ tcTopSpliceExpr isTypedSplice tc_action
                    -- is expected (Trac #7276)
     setStage (Splice isTypedSplice) $
     do {    -- Typecheck the expression
-         (expr', const_binds) <- solveTopConstraints tc_action
+         (expr', wanted) <- captureConstraints tc_action
+       ; const_binds     <- simplifyTop wanted
 
           -- Zonk it and tie the knot of dictionary bindings
        ; zonkTopLExpr (mkHsDictLet (EvBinds const_binds) expr') }



More information about the ghc-commits mailing list