On Thu, 2005-02-10 at 13:11 +0000, Simon Marlow wrote:
> Please test if you're able to, and give us feedback.

I've noticed that running main of the attached code, using Proxy
data-types to simulate context parameters (see previous email) still
sends something into an infinite loop; is this my fault or GHCs?

-Si.

-- 
Simon David Foster <[EMAIL PROTECTED]>
{-# 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, func2D' :: b -> a -> String }
data DictClassB a = DictClassB { func2D :: a -> String }

class Sat a where
    dict :: a

instance Sat (ctx String) => Data ctx String
instance Sat (ctx Int) => Data ctx Int

--instance ClassA a b => (Data (DictClassA a) b)

-- 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) => Sat (DictClassA a b) where
    dict = DictClassA { funcD = func, classBD = dict, func2D' = func2' }

func2' :: ClassA a b => b -> a -> String
func2' x ctx = func2 x

instance ClassB a => Sat (DictClassB a) where
    dict = DictClassB { func2D = func2 }

instance ClassA a String where
    func _ _ = "hello"

instance ClassA Int Int where
    func _ _ = "hello"
    
instance ClassB String where
    func2 _ = "bye"
    
instance ClassB Int where
    func2 _ = "bye"
    

main = do print $ func "hello" (5::Int)
          print $ func2D' ((dict::DictClassA Int String)) "hello" 5
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to