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

Carlos Camarao carlos.camarao at gmail.com
Sat May 29 21:24:40 EDT 2010


On Fri, May 28, 2010 at 2:36 AM, Isaac Dupree <
ml at isaac.cedarswampstudios.org> wrote:

> On 05/27/10 17:42, Carlos Camarao wrote:
>
>> On Thu, May 27, 2010 at 5:43 PM, David Menendez<dave at zednenem.com>
>>  wrote:
>>
>>  On Thu, May 27, 2010 at 10:39 AM, Carlos Camarao
>>> <carlos.camarao at gmail.com>  wrote:
>>>
>>>> Isaac Dupree:
>>>>
>>>>> 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?
>>>>>
>>>>
>>>> If qualified importation of k from both P and from Q was specified, we
>>>> would have two *distinct* terms, P.k and Q.k.
>>>>
>>>
>>> I think Isaac's point is that P.k and Q.k have the same definition (f
>>> o). If they don't produce the same value, then referential
>>> transparency is lost.
>>>
>>> --
>>> Dave Menendez<dave at zednenem.com>
>>> <http://www.eyrie.org/~zednenem/ <http://www.eyrie.org/%7Ezednenem/><
>>> http://www.eyrie.org/%7Ezednenem/>>
>>>
>>>
>> The definitions of P.k and Q.k are textually the same but the contexts are
>> different. "f" and "o" denote distinct values in P and Q. Thus, P.k and
>> Q.k
>> don't have the same definition.
>>
>
> Oh, I guess you are correct: it is like defaulting: it is a similar effect
> where the same expression means different things in two different modules as
> if you had default (Int) in one, and default (Bool) in the other.  Except:
> Defaulting according to the standard only works in combination with the 8
> (or however many it is) standard classes; and defaulting in Haskell is
> already a bit poorly designed / frowned upon / annoying that it's specified
> per-module when nothing else in the language is*.(that's a rather
> surmountable argument)


> It may be worth reading the GHC user's guide which attempts to explain the
> difference between incoherent and non-incoherent instance selection,
>
> http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/type-class-extensions.html#instance-overlap
> I didn't read both it and your paper closely enough that I'm sure anymore
> whether GHC devs would think your extension would require or imply
> -XIncoherentInstances ... my intuition was that IncoherentInstances would be
> implied...
>
> *(it's nice when you can substitute any use of a variable, such as P.k,
> with the expression that it is defined as -- i.e. the expression written so
> that it refer to the same identifiers, not a purely textual substitution --
> but in main above, you can't write [assuming you imported C] "print (f o)"
> because it will be rejected for ambiguity. (Now, there is already an
> instance-related situation like this where Main imports two different
> modules that define instances that overlap in an incompatible way, such as
> two different instances for Functor (Either e) -- not everyone is happy
> about how GHC handles this, but at least those overlaps are totally useless
> and could perhaps legitimately result in a compile error if they're even
> imported into the same module.))
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

I have no idea why you think IncoherentInstances would be implied. The
proposal says: do not issue ambiguity error if, using whatever means
permitted and specified (OverlappingInstances, IncoherentInstances,
whatever),  you can select a single instance.

The situation is as if we a FD:

module C where
  class F a b | 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
  g:: Bool -> Bool
  g = f
  k::Bool
  k = g o

module Q where
  import C
  instance F Int Bool where f = even
  instance O Int where o = 0
  g::Int->Bool
  g = f
  k :: Bool
  k = g o

module Main where
   import P
   import Q
   main = do { print P.k ; print Q.k }

Cheers,

Carlos
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-prime/attachments/20100529/0287106f/attachment.html


More information about the Haskell-prime mailing list