
22 Jan
2010
22 Jan
'10
6:24 a.m.
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