[commit: ghc] master: Comments and eta expand only (c90f833)

git at git.haskell.org git at git.haskell.org
Thu Apr 6 11:34:29 UTC 2017


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

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

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

commit c90f8334fa99e8de1ecb7b135a2846bc4d2bf25a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Apr 5 13:45:30 2017 +0100

    Comments and eta expand only


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

c90f8334fa99e8de1ecb7b135a2846bc4d2bf25a
 compiler/typecheck/TcBinds.hs | 2 +-
 compiler/typecheck/TcType.hs  | 4 ++--
 2 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index 1133e81..74f4b62 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -840,7 +840,7 @@ mkExport prag_fn qtvs theta
 
         ; wrap <- if sel_poly_ty `eqType` poly_ty  -- NB: eqType ignores visibility
                   then return idHsWrapper  -- Fast path; also avoids complaint when we infer
-                                           -- an ambiguouse type and have AllowAmbiguousType
+                                           -- an ambiguous type and have AllowAmbiguousType
                                            -- e..g infer  x :: forall a. F a -> Int
                   else addErrCtxtM (mk_impedance_match_msg mono_info sel_poly_ty poly_ty) $
                        tcSubType_NC sig_ctxt sel_poly_ty poly_ty
diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs
index 783b530..c76647c 100644
--- a/compiler/typecheck/TcType.hs
+++ b/compiler/typecheck/TcType.hs
@@ -1284,7 +1284,7 @@ mkSigmaTy bndrs theta tau = mkForAllTys bndrs (mkPhiTy theta tau)
 -- | Make a sigma ty where all type variables are 'Inferred'. That is,
 -- they cannot be used with visible type application.
 mkInfSigmaTy :: [TyVar] -> [PredType] -> Type -> Type
-mkInfSigmaTy tyvars ty = mkSigmaTy (mkTyVarBinders Inferred tyvars) ty
+mkInfSigmaTy tyvars theta ty = mkSigmaTy (mkTyVarBinders Inferred tyvars) theta ty
 
 -- | Make a sigma ty where all type variables are "specified". That is,
 -- they can be used with visible type application
@@ -1889,7 +1889,7 @@ pickCapturedPreds
   -> TcThetaType        -- Proposed constraints to quantify
   -> TcThetaType        -- A subset that we can actually quantify
 -- A simpler version of pickQuantifiablePreds, used to winnow down
--- the inferred constrains of a group of bindings, into those for
+-- the inferred constraints of a group of bindings, into those for
 -- one particular identifier
 pickCapturedPreds qtvs theta
   = filter captured theta



More information about the ghc-commits mailing list