[commit: ghc] wip/type-app: Fix compiler errors from merging (3c061dc)

git at git.haskell.org git at git.haskell.org
Fri Aug 7 12:08:23 UTC 2015


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

On branch  : wip/type-app
Link       : http://ghc.haskell.org/trac/ghc/changeset/3c061dc766845d148ce23236d3c0122a6dcd0eda/ghc

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

commit 3c061dc766845d148ce23236d3c0122a6dcd0eda
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Thu Aug 6 16:25:57 2015 -0400

    Fix compiler errors from merging


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

3c061dc766845d148ce23236d3c0122a6dcd0eda
 compiler/typecheck/TcBinds.hs   | 2 +-
 compiler/typecheck/TcExpr.hs    | 2 +-
 compiler/typecheck/TcHsType.hs  | 2 +-
 compiler/typecheck/TcMatches.hs | 4 ++++
 4 files changed, 7 insertions(+), 3 deletions(-)

diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index 01648a9..874b7a1 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -1802,7 +1802,7 @@ instTcTySig ctxt hs_ty sigma_ty extra_cts nwcs name
                   = CompleteSig $ mkLocalId name sigma_ty HasSigId  -- non-partial
                   | otherwise
                   = PartialSig { sig_name = name, sig_nwcs = nwcs
-                               , sig_cts = extra_ctx, sig_hs_ty = hs_ty }
+                               , sig_cts = extra_cts, sig_hs_ty = hs_ty }
        ; return (TISI { sig_bndr   = bndr
                       , sig_tvs   = findScopedTyVars hs_ty sigma_ty inst_tvs
                       , sig_theta = theta
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index 72b54e3..c9cdb29 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -243,7 +243,7 @@ tcExpr (ExprWithTySig expr sig_ty wcs) res_ty
 
       ; let inner_expr = ExprWithTySigOut (mkLHsWrap gen_fn expr') sig_ty
 
-      ; tcWrapResult inner_expr sig_tc_ty res_ty ExprSigOrigin } }
+      ; tcWrapResult inner_expr sig_tc_ty res_ty ExprSigOrigin }
 
 tcExpr (HsType ty _) _
   = failWithTc (sep [ text "Type argument used outside of a function argument:"
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index a5478f7..9ad4a5d 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -238,7 +238,7 @@ tcHsTypeApp (hs_ty, wcs) kind
   = tcWildcardBinders wcs $ \ wc_prs ->
     do { ty <- tcCheckLHsType hs_ty kind
        ; checkValidType TypeAppCtxt ty
-       ; return ty } }
+       ; return ty }
         -- NB: we don't call emitWildcardHoleConstraints here, because
         -- we want any holes in visible type applications to be used
         -- without fuss. No errors, warnings, extensions, etc.
diff --git a/compiler/typecheck/TcMatches.hs b/compiler/typecheck/TcMatches.hs
index 30c3f4a..18e3df0 100644
--- a/compiler/typecheck/TcMatches.hs
+++ b/compiler/typecheck/TcMatches.hs
@@ -43,6 +43,10 @@ import MkCore
 
 import Control.Monad
 
+#if __GLASGOW_HASKELL__ < 709
+import Data.Traversable ( traverse )
+#endif
+
 #include "HsVersions.h"
 
 {-



More information about the ghc-commits mailing list