"Could not unambiguously deduce"..

Simon Peyton-Jones simonpj@microsoft.com
Wed, 6 Nov 2002 17:40:54 -0000


| Yes, but isn't that an implementation problem surfacing at the
| language level? All the dictionaries needed to delay the decision to
| the point of use could also be made available when compiling the
| original program, no? After all, that's the reason why there's an
| ambiguity in the first place.

No, it's not.   It's tricky to understand and tricky to explain.  I'll =
have one more go.

Consider just this:

| > | class C t where
| > |    expl :: t -> String
| > |    expl x "default"
| > |
| > | instance           C String where expl s =3D "String"
| > | instance C a =3D> C [a]    where expl l =3D "[a]"

Now try this:

	f :: C a =3D> [a] -> String
	f xs =3D expl xs ++ "\n"

	foo1 =3D f "wig"
	foo2 =3D expl "wig" ++ "\n"

	baz1 =3D f [True]
	baz2 =3D expl [True] ++ "\n"

I think we'll agree that foo2 should return "String\n" and baz2 should =
return "[a]\n".]
But what about foo1 and baz1?  Both execute the code for 'f'.  What does =
f do?  It needs a dictionary for C[a] to deal with the call (expl xs).  =
BUT it does not know what 'a' is going to be.  It can't choose the =
String instance.  So perhaps it should choose the C [a] instance?  Well, =
it could, but then (f xs) would always return "[a]\n".  And 'f' must =
choose one of the two instances right now, because all it's passed is a =
dictionary for (C a).

If, instead, we say

	f :: C [a] =3D> [a] -> String

then f doesn't have to choose which instance... it can just use the C[a] =
dictionary that is passed.  Then in foo1, the compiler knows that it =
should pass a (C String) dictionary, and in baz1 it should pass a (C =
[Boo]) dictionary and all is well.


In your example things are slightly more complicated because it's the =
instance decl that gives rise to the problem, but it's just the same =
issue.

Simon






|=20
| Not to mention that in the case for which there is an overlap, the
| String instance will always be chosen as the more specific one..
|=20
| Claus
|=20
| > | data T a =FD [a]
| > |
| > | class C t where
| > |    expl :: t -> String
| > |    expl x =FFdefault"
| > |
| > | instance        C String where expl s "String"
| > | instance C a =FFC [a]    where expl l "[a]"
| > |
| > | instance (C a {- ,C [a] -} ) =FFC (T a) where
| > |     expl (D xs) =FExpl xs
| > |
| > | main =FFutStrLn $ expl "hi"
| > |
| > | ------------
| > |
| > | As is, both ghc and hugs reject the program, whereas
| > | both accept it with the extra constraint in the C (T a)
| > | instance.. Now, I think I can see how the right-hand-side
| > | expl could come either from the C String or from the C [a]
| > | instance - hence ghc's message:
| > |
| > |   $ ghc --make Tst.hs
| > |   c:\ghc\ghc-5.04\bin\ghc.exe: chasing modules from: Tst.hs
| > |   Compiling Main             ( Tst.hs, ./Tst.o )
| > |
| > |   Tst.hs:15:
| > |       Could not unambiguously deduce (C [a])
| > |           from the context (C (T a), C a)
| > |       The choice of (overlapping) instance declaration
| > |           depends on the instantiation of `a'
| > |       Probable fix:
| > |           Add (C [a]) to the class or instance method `expl'
| > |           Or add an instance declaration for (C [a])
| > |       arising from use of `expl' at Tst.hs:15
| > |       In the definition of `expl': expl xs
| > |
| > |
| > | Confused,
| > | Claus
| > |
| > | PS. Perhaps related, but why does Hugs seem to ignore the
| > |     C a constraint in the context of the original version?
| > |
| > |     $ hugs -98 Tst.hs
| > |     __   __ __  __  ____   ___
| > |     _________________________________________
| > |     ||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell =
98
| > |     standard
| > |     ||___|| ||__|| ||__||  __||     Copyright (c) 1994-2001
| > |     ||---||         ___||           World Wide Web:
| > |     http://haskell.org/hugs
| > |     ||   ||                         Report bugs to:
| > |     hugs-bugs@haskell.org
| > |     ||   || Version: December 2001
| > |     _________________________________________
| > |
| > |     Hugs mode: Restart with command line option +98 for Haskell 98
| > mode
| > |
| > |     Reading file "c:\Program Files\Hugs98\\lib\Prelude.hs":
| > |     Reading file "Tst.hs":
| > |     Type checking
| > |     ERROR "Tst.hs":15 - Cannot justify constraints in instance =
member
| > |     binding
| > |     *** Expression    : expl
| > |     *** Type          : C (T a) =FFT a -> String
| > |     *** Given context : C (T a)
| > |     *** Constraints   : C [a]
| > |
| > |     Prelude>
| > | _______________________________________________
| > | Glasgow-haskell-bugs mailing list
| > | Glasgow-haskell-bugs@haskell.org
| > | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
|=20