Liberalising IncoherentInstances

John Lato jwlato at gmail.com
Mon Jul 29 17:19:08 CEST 2013


+1 to the original proposal and Edward's suggestion of emitting a warning.
I've occasionally wanted this behavior from IncoherentInstances as well.


On Mon, Jul 29, 2013 at 3:01 PM, Edward Kmett <ekmett at gmail.com> wrote:

> I'll probably never use it, but I can't see any real problems with the
> proposal. In many ways it is what I always expected IncoherentInstances to
> be.
>
> One thing you might consider is that if you have to make an arbitrary
> instance selection at the end during compile time, making that emit a
> warning by default or at least under -Wall. That way it is clear when you
> are leaning on underdetermined semantics.
>
> -Edward
>
>
> On Sat, Jul 27, 2013 at 4:16 PM, Simon Peyton-Jones <simonpj at microsoft.com
> > wrote:
>
>> Friends
>>
>> I've realised that GHC's -XIncoherentInstances flag is, I think,
>> over-conservative.  I propose to liberalise it a bit. This email describes
>> the issue.  Please yell if you think this is a bad idea.
>>
>> Simon
>>
>> Suppose we have
>>
>>         class C a where { op :: a -> String }
>>         instance C [a] where ...
>>         instance C [Char] where ...
>>
>>         f :: [b] -> String
>>         f xs = "Result:" ++ op xs
>>
>> With -XOverlappingInstances, but without -XIncoherentInstances, f won't
>> compile.  Reason: if we call 'f' at Char (e.g.  f "foo") then you might
>> think we should use instance C [Char].  For example, if we inlined 'f' at
>> the call site, to get ("Result:" ++ op "foo"), we certainly then would use
>> the C [Char] instance, giving perhaps different results.  If we accept the
>> program as-is, we'll permanently commit 'f' to using the C [a] instance.
>>
>> The -XIncoherentInstances flag says "Go ahead and use an instance, even
>> if another instance might become relevant if you were to specialise or
>> inline the enclosing function."  The GHC user manual gives a more precise
>> spec [1].
>>
>> Now consider this
>>         class D a b where { opD :: a -> b -> String }
>>         instance D Int b where ...
>>         instance D a Int where ...
>>
>>         g (x::Int) = opD x x
>>
>> Here 'g' gives rise to a constraint (D Int Int), and that matches two
>> instance declarations.   So this is rejected regardless of flags.  We can
>> fix it up by adding
>>         instance D Int Int where ...
>> but this is pretty tiresome in cases where it really doesn't matter which
>> instance you choose.  (And I have a use-case where it's more than tiresome
>> [2].)
>>
>> The underlying issue is similar to the previous example.  Before, there
>> was *potentially* more than one way to generate evidence for (C [b]); here
>> there is *actually* more than one instance.  In both cases the dynamic
>> semantics of the language are potentially affected by the choice -- but
>> -XIncoherentInstnaces says "I don't care".
>>
>>
>> So the change I propose to make IncoherentInstances to pick arbitrarily
>> among instances that match.  More precisely, when trying to find an
>> instance matching a target constraint (C tys),
>>
>> a) Find all instances matching (C tys); these are the candidates
>>
>> b) Eliminate any candidate X for which another candidate Y is
>>   strictly more specific (ie Y is a substitution instance of X),
>>   if either X or Y was complied with -XOverlappingInstances
>>
>> c) Check that any non-candidate instances that *unify* with (C tys)
>>    were compiled with -XIncoherentInstances
>>
>> d) If only one candidate remains, pick it.
>>     Otherwise if all remaining candidates were compiled with
>>     -XInccoherentInstances, pick an arbitrary candidate
>>
>> All of this is precisely as now, except for the "Otherwise" part of (d).
>>  One could imagine different flags for the test in (c) and (d) but I really
>> don't think it's worth it.
>>
>>
>> Incidentally, I think it'd be an improvement to localise the
>> Overlapping/Incoherent flags to particular instance declarations, via
>> pragmas, something like
>>         instance C [a] where
>>           {-# ALLOW_OVERLAP #-}
>>           op x = ....
>>
>> Similarly {-# ALLOW_INCOHERENT #-}.   Having -XOverlappingInstances for
>> the whole module is a bit crude., and might be missed when looking at an
>> instance.   How valuable would this be?
>>
>> [1]
>> http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap
>> [2] http://ghc.haskell.org/trac/ghc/wiki/NewtypeWrappers
>>
>>
>>
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users at haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20130729/46f6e803/attachment.htm>


More information about the Glasgow-haskell-users mailing list