[Haskell-cafe] Safe Haskell and instance coherence

MigMit miguelimo38 at yandex.ru
Thu Oct 11 15:54:00 CEST 2012


On Oct 11, 2012, at 5:30 PM, Mikhail Glushenkov <the.dead.shall.rise at gmail.com> wrote:

> Hello Simon,
> 
> On Thu, Oct 11, 2012 at 11:24 AM, Simon Marlow <marlowsd at gmail.com> wrote:
>> On 08/10/2012 20:11, Mikhail Glushenkov wrote:
>>> I couldn't find anything on the interplay between orphan instances and
>>> Safe Haskell both in the Haskell'12 paper and online. Is this
>>> something that the authors of Safe Haskell are aware of/are intending
>>> to fix?
>> 
>> [...]
>> I don't know what we should do about this.  Disallowing orphan instances
>> seems a bit heavy-handed. David, Simon, any thoughts?
> 
> What about detecting duplicate instances at link time? We could put
> information about all instances defined in a given module into the
> .comment section of the corresponding .o file and then have a pre-link
> step script extract this information from all .o files in the program
> and check that there are no duplicate or conflicting instances.
> 

You have a bigger problem coming. Some extensions make multiple instances OK, even in Safe Haskell. For example:

{-# LANGUAGE FlexibleInstances, IncoherentInstances, Safe #-}
module Over where
data Nil = Nil
newtype Cons a = Cons a
class Number n where value :: n -> Integer
instance Number Nil where value Nil = 0
instance Number a => Number (Cons a) where value (Cons n) = value n + 1
instance Number (Cons (Cons Nil)) where value (Cons (Cons Nil)) = 2012
naturals = nats Nil where
    nats :: Number n => n -> [Integer]
    nats n = value n : nats (Cons n)

Here we have two different instances Number (Con (Cons Nil)) at play, because it gives you:

*Over> value (Cons (Cons Nil))
2012
*Over> take 5 naturals
[0,1,2,3,4]




More information about the Haskell-Cafe mailing list