Restricted Types and Infinite Loops

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.
--
Simon David Foster

Further, even if I *do* make ClassB two parameter so there should be no ambiguity, GHC still goes into an infinite loop. This happens even with the very latest CVS. Plus I tried creating a proxy function for func2 with type func2' :: Class A a b => a -> b -> String, which calls the calls func2 and placing this in the dictionary instead, but with the same problem. I don't understand why the resolution here should be any different to when func2 is directly within ClassA. The system does stop going into infinite loops if I create only fully decidable instances of ClassA, i.e. where the first parameter is quantified as well. But I need it to be general so I can have different contexts. Is there anyway around this problem without actually putting func2 into ClassA itself? -Si. On Thu, 2005-01-27 at 14:11 +0000, 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.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users -- Simon David Foster

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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Ralf Lammel ralfla@microsoft.com Microsoft Corp., Redmond, Webdata/XML http://www.cs.vu.nl/~ralf/

On Fri, 2005-02-18 at 02:18 +0100, Ralf Laemmel wrote:
Here I assume that you don't _really_ depend on ClassB to be a superclass of ClassA. (Why would you?)
Ok, here's what the real class head is (or was before I butchered it to make it work); class (Data (DictXMLData h) a, XMLNamespace a) => XMLData h a where We want to do this so that it is unnecessary to store XML Namespaces in the XMLData instances (which is supposed to be for only encoding). There are two reasons why this is necessary; * 1 - We have another class XSDType a, which gives types an XSD Type. This also depends on the types having a namespace. If we don't have this class dependency, we end up with repeated data. * 2 - In various contexts, you will require a different namespace for a particular element, but the same encoder. For example, when creating a SOAP Envelope, the "int" data-type could have the SOAP Encoding namespace or it could have the XSD Namespace. Further it may not have a namespace at all, in which case the default instance (XMLNamespace a) will take over. By taking the dependency out you bind a particular namespace to an encoder. For now, the various encoders for XSD data-types are in the XSD Module, this means that any user that wants to encode an int or string must import the XSD module, since we can't centralise the encoder.
This is a simpler recursion scheme in terrms of class/instance constraints.
Maybe, but sadly it doesn't achieve my goal. I could do Namespaces via a
hook, but that makes the construction and encoding of namespace tables
almost impossible.
Thanks,
-Si.
--
Simon David Foster

I seem to remember that if you define the class: class DictXMLData h => XMLData h ... instance (Data d a,XMLNamespace a) => XMLData d where ... then providing you annotate the instance functions with the relavent scoped type variables (d and a) then the compiler will infer XMLNamespace correctly for those instances that use it from the XMLData constraint. Keean. Simon David Foster wrote:
On Fri, 2005-02-18 at 02:18 +0100, Ralf Laemmel wrote:
Here I assume that you don't _really_ depend on ClassB to be a superclass of ClassA. (Why would you?)
Ok, here's what the real class head is (or was before I butchered it to make it work);
class (Data (DictXMLData h) a, XMLNamespace a) => XMLData h a where
We want to do this so that it is unnecessary to store XML Namespaces in the XMLData instances (which is supposed to be for only encoding). There are two reasons why this is necessary;
* 1 - We have another class XSDType a, which gives types an XSD Type. This also depends on the types having a namespace. If we don't have this class dependency, we end up with repeated data. * 2 - In various contexts, you will require a different namespace for a particular element, but the same encoder. For example, when creating a SOAP Envelope, the "int" data-type could have the SOAP Encoding namespace or it could have the XSD Namespace. Further it may not have a namespace at all, in which case the default instance (XMLNamespace a) will take over. By taking the dependency out you bind a particular namespace to an encoder.
For now, the various encoders for XSD data-types are in the XSD Module, this means that any user that wants to encode an int or string must import the XSD module, since we can't centralise the encoder.
This is a simpler recursion scheme in terrms of class/instance constraints.
Maybe, but sadly it doesn't achieve my goal. I could do Namespaces via a hook, but that makes the construction and encoding of namespace tables almost impossible.
Thanks,
-Si.

Having looked at some of my source code this relies on Data having a functional dependancy such that: class Data d a | d -> a ... So it might not work for what you want. Keean. Keean Schupke wrote:
I seem to remember that if you define the class:
class DictXMLData h => XMLData h ...
instance (Data d a,XMLNamespace a) => XMLData d where ...
then providing you annotate the instance functions with the relavent scoped type variables (d and a) then the compiler will infer XMLNamespace correctly for those instances that use it from the XMLData constraint.
Keean.
Simon David Foster wrote:
On Fri, 2005-02-18 at 02:18 +0100, Ralf Laemmel wrote:
Here I assume that you don't _really_ depend on ClassB to be a superclass of ClassA. (Why would you?)
Ok, here's what the real class head is (or was before I butchered it to make it work);
class (Data (DictXMLData h) a, XMLNamespace a) => XMLData h a where
We want to do this so that it is unnecessary to store XML Namespaces in the XMLData instances (which is supposed to be for only encoding). There are two reasons why this is necessary;
* 1 - We have another class XSDType a, which gives types an XSD Type. This also depends on the types having a namespace. If we don't have this class dependency, we end up with repeated data. * 2 - In various contexts, you will require a different namespace for a particular element, but the same encoder. For example, when creating a SOAP Envelope, the "int" data-type could have the SOAP Encoding namespace or it could have the XSD Namespace. Further it may not have a namespace at all, in which case the default instance (XMLNamespace a) will take over. By taking the dependency out you bind a particular namespace to an encoder.
For now, the various encoders for XSD data-types are in the XSD Module, this means that any user that wants to encode an int or string must import the XSD module, since we can't centralise the encoder.
This is a simpler recursion scheme in terrms of class/instance constraints.
Maybe, but sadly it doesn't achieve my goal. I could do Namespaces via a hook, but that makes the construction and encoding of namespace tables almost impossible.
Thanks,
-Si.
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Whoops, I should have tried it first. Amazingly, this seems to works.
But I'm not sure I understand why, a still depends on XMLNamespace,
because of the dictionary instance;
instance (Data (DictXMLData b) a, XMLHook b a, XMLData b a, XMLNamespace
a) => Sat (DictXMLData b a) where
But I guess it's because the dependency on XMLNamespace comes in the
instances, rather than the class head.
-Si.
--
Simon David Foster
participants (3)
-
Keean Schupke
-
Ralf Laemmel
-
Simon David Foster