From dd45134bcb376a8bbc982370b95b3dbeaa8dc58a Mon Sep 17 00:00:00 2001
From: simonpj <unknown>
Date: Thu, 5 Jan 2006 13:10:55 +0000
Subject: [PATCH] [project @ 2006-01-05 13:10:55 by simonpj] MERGE TO STABLE

This commit fixes a nasty problem discovered by Volker Stolz.
The problem is described in Note [Multiple instantiation] in
TcExpr, which is reproduced below.

(Core Lint identifies the problem, incidentally.)

tc200 is a test case.


Note [Multiple instantiation]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We are careful never to make a MethodInst that has, as its meth_id, another MethodInst.
For example, consider
	f :: forall a. Eq a => forall b. Ord b => a -> b
At a call to f, at say [Int, Bool], it's tempting to translate the call to

	f_m1
  where
	f_m1 :: forall b. Ord b => Int -> b
	f_m1 = f Int dEqInt

	f_m2 :: Int -> Bool
	f_m2 = f_m1 Bool dOrdBool

But notice that f_m2 has f_m1 as its meth_id.  Now the danger is that if we do
a tcSimplCheck with a Given f_mx :: f Int dEqInt, we may make a binding
	f_m1 = f_mx
But it's entirely possible that f_m2 will continue to float out, because it
mentions no type variables.  Result, f_m1 isn't in scope.

Here's a concrete example that does this (test tc200):

    class C a where
      f :: Eq b => b -> a -> Int
      baz :: Eq a => Int -> a -> Int

    instance C Int where
      baz = f

Current solution: only do the "method sharing" thing for the first type/dict
application, not for the iterated ones.  A horribly subtle point.
---
 ghc/compiler/typecheck/TcExpr.lhs | 47 +++++++++++++++++++++++++++----
 1 file changed, 42 insertions(+), 5 deletions(-)

diff --git a/ghc/compiler/typecheck/TcExpr.lhs b/ghc/compiler/typecheck/TcExpr.lhs
index a26a106e8461..70a426b56a2e 100644
--- a/ghc/compiler/typecheck/TcExpr.lhs
+++ b/ghc/compiler/typecheck/TcExpr.lhs
@@ -875,15 +875,18 @@ tcId orig id_name	-- Look up the Id and instantiate its type
 #endif /* GHCI */
 
     instantiate :: TcId -> TcM (HsExpr TcId, [TcTyVar], TcRhoType)
-    instantiate fun_id = loop (HsVar fun_id) [] (idType fun_id)
-
-    loop (HsVar fun_id) tvs fun_ty
-	| want_method_inst fun_ty
+    instantiate fun_id 
+	| not (want_method_inst fun_ty)
+	= loop (HsVar fun_id) [] fun_ty
+	| otherwise	-- Make a MethodInst
 	= tcInstType fun_ty		`thenM` \ (tyvars, theta, tau) ->
 	  newMethodWithGivenTy orig fun_id 
 		(mkTyVarTys tyvars) theta tau	`thenM` \ meth_id ->
-	  loop (HsVar meth_id) (tvs ++ tyvars) tau
+	  loop (HsVar meth_id) tyvars tau
+	where
+	  fun_ty = idType fun_id
 
+	-- See Note [Multiple instantiation]
     loop fun tvs fun_ty 
 	| isSigmaTy fun_ty
 	= tcInstCall orig fun_ty	`thenM` \ (inst_fn, new_tvs, tau) ->
@@ -907,6 +910,40 @@ tcId orig id_name	-- Look up the Id and instantiate its type
 				  (_,theta,_) -> not (any isLinearPred theta)
 \end{code}
 
+Note [Multiple instantiation]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We are careful never to make a MethodInst that has, as its meth_id, another MethodInst.
+For example, consider
+	f :: forall a. Eq a => forall b. Ord b => a -> b
+At a call to f, at say [Int, Bool], it's tempting to translate the call to 
+
+	f_m1
+  where
+	f_m1 :: forall b. Ord b => Int -> b
+	f_m1 = f Int dEqInt
+
+	f_m2 :: Int -> Bool
+	f_m2 = f_m1 Bool dOrdBool
+
+But notice that f_m2 has f_m1 as its meth_id.  Now the danger is that if we do
+a tcSimplCheck with a Given f_mx :: f Int dEqInt, we may make a binding
+	f_m1 = f_mx
+But it's entirely possible that f_m2 will continue to float out, because it
+mentions no type variables.  Result, f_m1 isn't in scope.
+
+Here's a concrete example that does this (test tc200):
+
+    class C a where
+      f :: Eq b => b -> a -> Int
+      baz :: Eq a => Int -> a -> Int
+
+    instance C Int where
+      baz = f
+
+Current solution: only do the "method sharing" thing for the first type/dict
+application, not for the iterated ones.  A horribly subtle point.
+
+
 %************************************************************************
 %*									*
 \subsection{Record bindings}
-- 
GitLab