[Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

Max Bolingbroke batterseapower at hotmail.com
Wed May 26 18:12:32 EDT 2010


Hi Carlos,

Apologies for the lateness of my reply.

On 23 May 2010 02:24, Carlos Camarao <carlos.camarao at gmail.com> wrote:
> I think that a notion of orphan instances based on whether an
> instance is defined or not in the module where the class of the
> instance is defined is not very nice

I broadly agree, but pragmatically the notion of orphans is useful for
designing robust libraries, even if the notion is a bit horrible.

> A benefit of adopting our approach would be that defaulting would
> become unnecessary (defaulting always occurring in favor of visible
> definitions).

This is something I don't understand (and is not elaborated in your
paper that I can see). Defaulting seems like an orthogonal mechanism.
It turns a constraint that really does have multiple solutions (e.g.
(Num a) => ...) into one where a particular preferred choice is taken
(e.g. Num Int), in situations where abstracting over the choice is
disallowed.

However, you mechanism only turns constraints into instances when
there is no ambiguity.

Can you perhaps explain what you mean a bit further?

I looked at your definition for orphan-hood, which I think might be OK
if you don't have FlexibleInstances. However, if you do then consider
this series of modules:

"""
{-# LANGUAGE MultiParamTypeClasses #-}
module Common where

class C a b where
    foo :: a -> b -> String
"""

"""
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
{-# OPTIONS_GHC -fwarn-orphans #-}
module Mod2 where

import Common

data E = E

instance C a E where
    foo _ _ = "Mod2"
"""

"""
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
{-# OPTIONS_GHC -fwarn-orphans #-}
module Mod1 where

import Common

data D = D

instance C D b where
    foo _ _ = "Mod1"
"""

"""
{-# OPTIONS_GHC -fwarn-orphans #-}
import Common
import Mod1
import Mod2

main = putStrLn (foo D E)
"""

None of the instances are reported as orphans but IMHO they should be,
because we get a conflict in the Main module. I guess that a MPTC
instance (C t1 .. tn) for class C in module M1 is NOT an orphan if:
 1) C is defined in the same module as the instance
 2) OR ALL the t1..tn are instantiated to some concrete type (i.e. not
a type variable) defined in the same module as the instance

Imagine that we had an instance defined in a different module than the
class and violating 2). Then:

\exists i. t_i is a type variable or a datatype defined in another module

Case 1: If t_i is a type variable, we can have a parallel module M2:

"""
data F = F

instance C a_1 ... a_{i-1} F a_{i+1} ... a_n where
"""

Adding the instance to M2 may break client code because it is
potentially ambiguous with the one from M1. Furthermore, the instance
is considered non-orphan by GHC because it has at least one type which
is defined in the same module. However, at least one of this instance
and the one in M1 should have been flagged as orphans :(

Case 2: if t_i is a datatype G defined in another module, we can
similarly consider adding a new instance to that module:

"""
instance C a_1 ... a_{i-1} G a_{i+1} ... a_n where
"""

Same argument as for case 1.

Does this seem right?

==

Basically, you want an orphanhood criteria P you can test locally on a
per-module basis such that:
 * For any composition of modules where P holds on every module individually...
 * Changing any module by *adding* instances such that P still holds..
 * Is guaranteed not to break any other module due to ambiguity

It is not clear to me exactly what this should look like, especially
in the presence of more complicated instance definitions (like the
"instance C [Bool]" style of thing allowed by FlexibleInstances. It
would probably be interesting to find out though.

Cheers,
Max


More information about the Haskell-Cafe mailing list