[Haskell-cafe] Non-termination due to context
Emil Axelsson
emax at chalmers.se
Fri Jan 22 06:24:37 EST 2010
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
More information about the Haskell-Cafe
mailing list