[commit: ghc] wip/rae-new-coercible: Fix compiler errors (a2288fc)
git at git.haskell.org
git at git.haskell.org
Tue Dec 2 20:43:54 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/rae-new-coercible
Link : http://ghc.haskell.org/trac/ghc/changeset/a2288fc7693476fea62f10a6d3508d1938283ad1/ghc
>---------------------------------------------------------------
commit a2288fc7693476fea62f10a6d3508d1938283ad1
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Mon Dec 1 11:32:26 2014 -0500
Fix compiler errors
>---------------------------------------------------------------
a2288fc7693476fea62f10a6d3508d1938283ad1
compiler/typecheck/TcSMonad.lhs | 12 ++++++++++++
compiler/typecheck/TcValidity.lhs | 10 +++++-----
2 files changed, 17 insertions(+), 5 deletions(-)
diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs
index c9b979d..214afa7 100644
--- a/compiler/typecheck/TcSMonad.lhs
+++ b/compiler/typecheck/TcSMonad.lhs
@@ -913,6 +913,18 @@ lookupSolvedDict (IS { inert_solved_dicts = solved }) loc cls tys
Just ev | ctEvCheckDepth cls loc ev -> Just ev
_ -> Nothing
+\end{code}
+
+%************************************************************************
+%* *
+ TyEqMap
+%* *
+%************************************************************************
+
+\begin{code}
+
+type TyEqMap a = TyVarEnv a
+
findTyEqs :: EqRel -> InertCans -> TyVar -> EqualCtList
findTyEqs NomEq icans tv = lookupVarEnv (inert_eqs icans) tv `orElse` []
findTyEqs ReprEq icans tv = lookupVarEnv (inert_repr_eqs icans) tv `orElse` []
diff --git a/compiler/typecheck/TcValidity.lhs b/compiler/typecheck/TcValidity.lhs
index 42336a3..de93387 100644
--- a/compiler/typecheck/TcValidity.lhs
+++ b/compiler/typecheck/TcValidity.lhs
@@ -530,15 +530,15 @@ check_eq_pred dflags pred
checkTc (xopt Opt_TypeFamilies dflags || xopt Opt_GADTs dflags)
(eqPredTyErr pred)
-check_repr_eq_pred :: DynFlags -> UserTypeCtxt -> PredType -> TcType -> TcType -> TcM ()
+check_repr_eq_pred :: DynFlags -> UserTypeCtxt -> PredType
+ -> TcType -> TcType -> TcM ()
check_repr_eq_pred dflags ctxt pred ty1 ty2
- = do { mapM_ checkValidMonoType tys
- ; check_class_pred_tys dflags ctxt pred tys }
+ = check_class_pred_tys dflags ctxt pred tys
where
tys = [ty1, ty2]
-check_tuple_pred :: DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM ()
-check_tuple_pred dflags ctxt pred ts
+check_tuple_pred :: Bool -> DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM ()
+check_tuple_pred under_syn dflags ctxt pred ts
= do { checkTc (xopt Opt_ConstraintKinds dflags)
(predTupleErr pred)
; mapM_ (check_pred_help under_syn dflags ctxt) ts }
More information about the ghc-commits
mailing list