[commit: ghc] master: Add a couple of HasDebugCallStack contexts (60d338f)
git at git.haskell.org
git at git.haskell.org
Wed Mar 29 13:59:33 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/60d338f50992ddd932cbdd47587ef495a1ab8d21/ghc
>---------------------------------------------------------------
commit 60d338f50992ddd932cbdd47587ef495a1ab8d21
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Mar 29 09:01:58 2017 +0100
Add a couple of HasDebugCallStack contexts
Just for future (and past) debugging...
>---------------------------------------------------------------
60d338f50992ddd932cbdd47587ef495a1ab8d21
compiler/types/Coercion.hs | 4 ++--
compiler/types/Coercion.hs-boot | 2 +-
2 files changed, 3 insertions(+), 3 deletions(-)
diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs
index 86f9d76..e1dcfde 100644
--- a/compiler/types/Coercion.hs
+++ b/compiler/types/Coercion.hs
@@ -426,7 +426,7 @@ mkHeteroCoercionType Phantom = panic "mkHeteroCoercionType"
-- | Given a coercion @co1 :: (a :: TYPE r1) ~ (b :: TYPE r2)@,
-- produce a coercion @rep_co :: r1 ~ r2 at .
-mkRuntimeRepCo :: Coercion -> Coercion
+mkRuntimeRepCo :: HasDebugCallStack => Coercion -> Coercion
mkRuntimeRepCo co
= mkNthCo 0 kind_co
where
@@ -1530,7 +1530,7 @@ liftCoSubstWith r tvs cos ty
-- that coerces between @lc_left(ty)@ and @lc_right(ty)@, where
-- @lc_left@ is a substitution mapping type variables to the left-hand
-- types of the mapped coercions in @lc@, and similar for @lc_right at .
-liftCoSubst :: Role -> LiftingContext -> Type -> Coercion
+liftCoSubst :: HasDebugCallStack => Role -> LiftingContext -> Type -> Coercion
liftCoSubst r lc@(LC subst env) ty
| isEmptyVarEnv env = Refl r (substTy subst ty)
| otherwise = ty_co_subst lc r ty
diff --git a/compiler/types/Coercion.hs-boot b/compiler/types/Coercion.hs-boot
index eefefd0..dd10d6e 100644
--- a/compiler/types/Coercion.hs-boot
+++ b/compiler/types/Coercion.hs-boot
@@ -42,7 +42,7 @@ coVarRole :: CoVar -> Role
mkCoercionType :: Role -> Type -> Type -> Type
data LiftingContext
-liftCoSubst :: Role -> LiftingContext -> Type -> Coercion
+liftCoSubst :: HasDebugCallStack => Role -> LiftingContext -> Type -> Coercion
seqCo :: Coercion -> ()
coercionKind :: Coercion -> Pair Type
More information about the ghc-commits
mailing list