ghc hung by FunctionalDependencies/UndecidableInstances
Simon Peyton-Jones
simonpj at microsoft.com
Thu Oct 29 05:53:59 EDT 2009
No, it's behaving exactly as expected. If you omit UndecidableInstances the program is rejected. If you add that flag you are saying "you are allowed to diverge if I screw up". And indeed you wrote a looping type problem.
I added some comments below that may help explain.
Simon
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, UndecidableInstances #-}
module X() where
class C a b | a -> b where f :: a -> b
newtype T a = T a
instance (C a b, Eq b) => Eq (T a) where (==) = undefined
g x = (undefined :: d -> d -> d -> ()) (T x) (f x) (undefined :: Eq e => e)
-- f :: C a b => a -> b
-- x :: a
-- b ~ T a
-- C a b
-- b ~ e
-- Eq e
{-
Hence need (C a (T a), Eq (T a))
Apply instance for Eq
= (C a (T a), C a g, Eq g)
Apply functional dependency: g ~ T a
= (C a (T a), C a (T a), Eq (T a))
And now we are back where we started
-}
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
| users-bounces at haskell.org] On Behalf Of Roland Zumkeller
| Sent: 29 October 2009 04:55
| To: glasgow-haskell-users at haskell.org
| Subject: ghc hung by FunctionalDependencies/UndecidableInstances
|
| Hi,
|
| ghc seems to hang and eat memory when fed the following code:
|
| {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
| UndecidableInstances #-}
| class C a b | a -> b where f :: a -> b
| newtype T a = T a
| instance (C a b, Eq b) => Eq (T a) where (==) = undefined
| g x = (undefined :: a -> a -> a -> ()) (T x) (f x) (undefined :: Eq a => a)
|
| Is this a bug?
|
| Best,
|
| Roland
|
| --
| http://alacave.net/~roland/
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list