Re: ghc6 behavior with circular instance declaration

2003-10-23 Thread Marcin 'Qrczak' Kowalczyk
W liście z śro, 22-10-2003, godz. 06:15, Kenny pisze: > instance (Myeq a,Myeq [a]) => Myeq [a] where > myeq (x:xs) (y:ys) = (myeq x y)&&(myeq xs ys) > > I want to make the 2nd call of myeq to be of an instance function > from the context instead of a recursive call. Why? Since there can be at

RE: ghc6 behavior with circular instance declaration

2003-10-23 Thread Kenny
Hi Simon, --- Simon Peyton-Jones <[EMAIL PROTECTED]> wrote: > I don't know why you would possibly want this. yes, in this example there isn't any obvious reason to motivate us writing such instance, but I am interested in how GHC now handles coinduction in type class. It will be neat if we can

RE: ghc6 behavior with circular instance declaration

2003-10-23 Thread Simon Peyton-Jones
| -- convententionally, we write: | {- | instance (Myeq a) => Myeq [a] where | myeq (x:xs) (y:ys) = (myeq x y)&&(myeq xs ys) | -} | | instance (Myeq a,Myeq [a]) => Myeq [a] where | myeq (x:xs) (y:ys) = (myeq x y)&&(myeq xs ys) | | | | I want to make the 2nd call of myeq to be of an | i

ghc6 behavior with circular instance declaration

2003-10-22 Thread Kenny
Hi all, currently I got this program of Eq: module Myeq where class Myeq a where myeq :: a -> a -> Bool instance Myeq Int where myeq i j = (i==j) -- convententionally, we write: {- instance (Myeq a) => Myeq [a] where myeq (x:xs) (y:ys) = (myeq x y)&&(myeq xs ys) -} instance (Myeq