Proposal to solve Haskell's MPTC dilemma
Isaac Dupree
ml at isaac.cedarswampstudios.org
Wed May 26 23:00:57 EDT 2010
On 05/26/10 15:42, Carlos Camarao wrote:
> What do you think?
I think you are proposing using the current set of instances in scope in
order to remove ambiguity. Am I right? ..I read the haskell-cafe
thread so far, and it looks like I'm right. This is what I'll add to
what's been said so far:
Your proposal appears to allow /incoherent/ instance selection. This
means that an expression can be well-typed in one module, and well-typed
in another module, but have different semantics in the two modules. For
example (drawing from above discussion) :
module C where
class F a b where f :: a -> b
class O a where o :: a
module P where
import C
instance F Bool Bool where f = not
instance O Bool where o = True
k :: Bool
k = f o
module Q where
import C
instance F Int Bool where f = even
instance O Int where o = 0
k :: Bool
k = f o
module Main where
import P
import Q
-- (here, all four instances are in scope)
main = do { print P.k ; print Q.k }
-- should result, according to your proposal, in
-- False
-- True
-- , am I correct?
Also, in your paper, example 2 includes
> m = (m1 * m2) * m3
and you state
> In Example 2, there is no means of specializing type variable c0 occurring in the
> type of m to Matrix.
I suggest that there is an appropriate such means, namely, to write
m = (m1 * m2 :: Matrix) * m3
. (Could the paper address how that solution falls short? Are there
other cases in which there is more than just a little syntactical
convenience at stake?, or is even that much added code too much for some
use-case?)
-Isaac
More information about the Haskell-prime
mailing list