[Haskell-cafe] Non-termination due to context

Ryan Ingram ryani.spam at gmail.com
Fri Jan 22 14:50:59 EST 2010


Here's the relevant core for this file (GHC 6.10.4, so I'm a bit out of date):

Rec {
$dB_rh6 :: Undec.B GHC.Types.Int
[GlobalId]
[]
$dB_rh6 = $dB_rh6
end Rec }

Undec.test :: GHC.Bool.Bool
[GlobalId]
[]
Undec.test =
  GHC.Classes.==
    @ GHC.Types.Int
    ($dB_rh6
     `cast` ((Undec.:Co:TB) GHC.Types.Int
             :: (Undec.:TB) GHC.Types.Int ~ (GHC.Classes.:TEq) GHC.Types.Int))
    (GHC.Types.I# 1)
    (GHC.Types.I# 2)

The "cast" is saying that the dictionary for B is equivalent to the
dictionary for Eq (an optimization for empty classes with one
superclass, I guess).

"$dB_rh6" is the dictionary for B Int.  GHC 'solves' this into a
classic looping program.  I'm not sure how the derivation for this
dictionary goes.

   -- ryan

so, given an A we can just pull the dictionary out of it

On Fri, Jan 22, 2010 at 3:24 AM, Emil Axelsson <emax at chalmers.se> wrote:
> Hello all!
>
> Consider the following program:
>
>> {-# LANGUAGE FlexibleInstances, OverlappingInstances, UndecidableInstances
>> #-}
>>
>> class B a => A a
>>
>> instance A Int
>>
>> class Eq a => B a
>>
>> instance (A a, Eq a) => B a
>>
>> eq :: B a => a -> a -> Bool
>> eq = (==)
>>
>> test = 1 `eq` (2::Int)
>
> (This is a condensed version of a much larger program that I've been
> debugging.)
>
> It compiles just fine, but `test` doesn't terminate (GHCi 6.10.4). If I
> change the context `B a` to `Eq a` for the function `eq`, it terminates.
>
> Although I don't know all the details of the class system, it seems
> unintuitive that I can make a program non-terminating just by changing the
> context of a function (regardless of UndecidableInstances etc.).
>
> Is this a bug or a feature?
>
> / Emil
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: undec.core
Type: application/octet-stream
Size: 2507 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100122/fe82ea38/undec.obj


More information about the Haskell-Cafe mailing list