Restricted Types and Infinite Loops

Ralf Laemmel Ralf.Laemmel at cwi.nl
Thu Feb 17 20:18:14 EST 2005


Hi Simon SD,
cc Simon PJ,

(Since the _evaluation_ does not terminate (rather than type checking),
this seems to imply that evaluation-time dictionary construction does 
not terminate. Right?)

Anyhow, do this change, and your code works.

diff SDF.save SDF.hs
10c10
< class (Data (DictClassA a) b, ClassB b) => ClassA a b where
---
 > class (Data (DictClassA a) b) => ClassA a b where

*Test> func2D (classBD (dict::DictClassA Int String)) "hello"
"bye"
*Test> Leaving GHCi.

(BTW, this even works with GHC 6.2 as opposed to the examples from the 
SYB3 paper.)

Here I assume that you don't _really_ depend on ClassB to be a 
superclass of ClassA. (Why would you?)
This is a simpler recursion scheme in terrms of class/instance constraints.

Regards,
Ralf

Simon David Foster wrote:

>Hi,
>
>(I've attached the full code for this problem)
>
>First I'll explain the problem description, I have two class ClassA and
>ClassB, the former has two parameters and the latter has one. The second
>parameter of ClassA is constrained by ClassB.
>
>class ClassB a where
>class ClassB b => ClassA a b where
>
>Because I wish to effectively pass the context of ClassA around, I need
>to create a pair of dictionary types (as in Restricted Data Types in
>Haskell, Hughes 99), one to represent ClassA (DictClassA) and one to
>represent ClassB (DictClassB). DictClassA also contains a term of type
>DictClassB since ClassA is a subclass of ClassB. I should then be able
>to call all the functions of ClassB via the appropriate term of
>DictClassA, like so (assuming we want to use func2);
>
>*Test> func2D (classBD (dict::DictClassA Int String)) "hello"
>"bye"
>
>So far so good, but now suppose I want Class A to have the further
>constraint
>
>class (Data (DictClassA a) b, ClassB b) => ClassA a b where
>
>(so as to make ClassA a subclass of Data)
>
>If we now try and do
>
>*Test> func2D (classBD (dict::DictClassA Int String)) "hello"
>
>We go into an infinite loop. Why? The expression still type-checks ok
>and I can't see what it is trying to do. All the functions of ClassA can
>be accessed ok, but not ClassB. 
>
>*Test> funcD ((dict::DictClassA Int String)) "hello" 5
>"hello"
>
>Is it something to do with ClassB only having one parameter?
>
>I'm running GHC 20041231.
>
>-Si.
>
>  
>
>------------------------------------------------------------------------
>
>{-# OPTIONS -fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances #-}
>module Test where
>
>import Data.Typeable
>
>-- Skeleton of the Data class
>class (Typeable a, Sat (ctx a)) => Data ctx a
>
>-- Our main class with 2 parameters
>class (Data (DictClassA a) b, ClassB b) => ClassA a b where
>    func :: b -> a -> String
>
>-- The class which contrains ClassA
>class ClassB a where
>    func2 :: a -> String
>
>data DictClassA a b = DictClassA { funcD :: b -> a -> String, classBD :: DictClassB b }
>data DictClassB b = DictClassB { func2D :: b -> String }
>
>class Sat a where
>    dict :: a
>
>instance Sat (ctx String) => Data ctx String
>
>-- Trying to access any of functions in ClassA works fine, but trying to get at anything in ClassB causes and infinite loop.
>instance (Data (DictClassA a) b, ClassA a b, ClassB b) => Sat (DictClassA a b) where
>    dict = DictClassA { funcD = func, classBD = dict }
>
>instance ClassB b => Sat (DictClassB b) where
>    dict = DictClassB { func2D = func2 }
>
>instance ClassA a String where
>    func _ _ = "hello"
>
>instance ClassB String where
>    func2 _ = "bye"
>
>------------------------------------------------------------------------
>
>_______________________________________________
>Glasgow-haskell-users mailing list
>Glasgow-haskell-users at haskell.org
>http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>  
>


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




More information about the Glasgow-haskell-users mailing list