Restricted Types and Infinite Loops

Ralf Laemmel Ralf.Laemmel at cwi.nl
Fri Feb 18 15:31:39 EST 2005


Hi Simon (PJ),
cc Simon (DF),

I rather reckon we are facing a bug here.
The attached minimalised Foo.hs shows the offending code pattern.
With GHC 6.2 we get "*** Exception: <<loop>>
With GHC 6.4 we get "   (still waiting for the rest of the string)

The scenario is about class/instance-head-level recursion
through superclassing and instance constraints.
Nothing too weird.
There are no _explicit_ recursive dictionaries.

An observations though.
The relevant class head does not just mention a recursive superclass,
but also an innocent superclass ClassB. If we move this innocent
superclass constraint to the instance level (see Bar.hs), then
we get termination with both 6,2 and 6.4.

Another issue.
This feature seems to need multi-parameter classes really!

Ralf

Simon Peyton-Jones wrote:

>Simon
>
>You've found an interesting case. 
>
>First, you are skating on thin ice here.  GHC's ability to build
>recursive dictionaries is quite experimental, and you are relying on it
>completely.  
>
>But you're right: it "should" work.  I can see why it isn't but I have
>not got it clear enough in my head to know the best way to fix it.
>Still less do I have a formal story about what should type-check
>(without loops) and what should not.
>
>So this is going to continue to fail in 6.4, but it's on my list to look
>at.
>
>Simon
>  
>

-- 
Ralf Lammel
ralfla at microsoft.com
Microsoft Corp., Redmond, Webdata/XML
http://www.cs.vu.nl/~ralf/

-------------- next part --------------
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

{-

Try:

(sat::Int -> String -> String) undefined "hello"

-}


module Foo where

class (Sat (a -> b -> String), ClassB b) => ClassA a b

class ClassB a
 where
  fun :: a -> String

class Sat x
 where
   sat :: x

instance ClassA a b => Sat (a -> b -> String)
 where
  sat = const fun

instance ClassA a String

instance ClassB String
 where
  fun = id
-------------- next part --------------
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

{-

Try:

(sat::Int -> String -> String) undefined "hello"

-}


module Foo where

class Sat (a -> b -> String) => ClassA a b

class ClassB a
 where
  fun :: a -> String

class Sat x
 where
   sat :: x

instance (ClassA a b, ClassB b) => Sat (a -> b -> String)
 where
  sat = const fun

instance ClassA a String

instance ClassB String
 where
  fun = id


More information about the Glasgow-haskell-users mailing list