type class problem / GHC bug

2003-11-08 Thread Brandon Michael Moore
Hi everyone I've built GHC from CVS and I'm getting some odd errors about overlapping instances. This is different from 6.0.1, but it's not obvious it is wrong, so I'm probably missing something here. The example is class A x class (A x) => B x instance A x instance B x The new GHC complains th

Re: type class problem

2003-10-01 Thread Martin Sulzmann
There's another possible fix which makes use of scoped variables. instance (RT r1 t1, RT r2 t2, TPair t t1 t2) => RT (RPair r1 r2) t where rtId (RPair r1 r2) t = "RT (RPair " ++ rtId r1 t1 ++ " " ++ rtId r2 t2 ++")" where (t1::t1,t2::t2) = prj t ^^ scoped vari

Re: type class problem

2003-09-30 Thread oleg
Dean Herington wrote: > Can someone explain why the following doesn't work? > {-# OPTIONS -fglasgow-exts #-} > class R r where > rId :: r -> String > class (R r) => RT r t where > rtId :: r -> t -> String > data RPair r1 r2 = RPair r1 r2 > instance (R r1, R r2) => R (RPair r1 r2) where >

type class problem

2003-09-29 Thread Dean Herington
Can someone explain why the following doesn't work? Is there some other way to achieve the same effect (declaring a set of instances for pair-like types in one go)? Thanks. Dean swan(108)% cat Test1.hs {-# OPTIONS -fglasgow-exts #-} class R r where rId :: r -> String class (R r) => RT r t

Type Class Problem

2003-09-10 Thread Brandon Michael Moore
Hello everyone I think I'm close to useful results on the instance restrictions. First there's an obvious extension to the Haskell98 rule. The H98 rule says the instance head must be a type constructor applied to type variables, and the context must mention only those type variables. This gives a

RE: Type class problem

2003-09-02 Thread Simon Peyton-Jones
| > b) at the moment dictionaries have the property that you can always | > evaluate them using call-by-value; if they could be recursively | > defined (as you suggest) that would no longer be the case | > | > Mind you, GHC doesn't currently take advantage of (b), so maybe it | > should be

RE: Type class problem

2003-09-02 Thread Simon Peyton-Jones
| I'm wondering if the general method of avoiding non-termination can be | made to work in these more complex cases. | | Incidentally, the constraint solver stack overflow problem can be | turned to our advantage. The typechecker's exhausting the stack should | be considered a failure to match the

RE: Type class problem

2003-08-30 Thread Brandon Michael Moore
On 28 Aug 2003, Carl Witty wrote: > On Thu, 2003-08-28 at 13:10, Brandon Michael Moore wrote: > > Unfortunately I don't have a useful syntatic condition on instance > > declarations that insures termination of typechecking. If types are > > restriced to products, sums, and explicit recursion, then

RE: Type class problem

2003-08-28 Thread Carl Witty
On Thu, 2003-08-28 at 13:10, Brandon Michael Moore wrote: > Unfortunately I don't have a useful syntatic condition on instance > declarations that insures termination of typechecking. If types are > restriced to products, sums, and explicit recursion, then termination is > ensured if we restrict th

RE: Type class problem

2003-08-28 Thread Brandon Michael Moore
On Fri, 22 Aug 2003, Simon Peyton-Jones wrote: > > Brandon writes > > | An application of Mu should be showable if the functor maps showable > types > | to showable types, so the most natural way to define the instance > seemed > | to be > | > | instance (Show a => Show (f a)) => Show (Mu f) wher

RE: Type class problem

2003-08-27 Thread oleg
Simon Peyton-Jones wrote: > > instance (Show (f (Mu f))) => Show (Mu f) where > >show (In x) = show x > > > > instance Show (N (Mu N)) where > >show Z = "Z" > >show (S k) = "S "++show k > But again, it's fragile isn't it? You are dicing with non-termination > if you have instance dec

RE: Type class problem

2003-08-22 Thread Simon Peyton-Jones
Brandon writes | An application of Mu should be showable if the functor maps showable types | to showable types, so the most natural way to define the instance seemed | to be | | instance (Show a => Show (f a)) => Show (Mu f) where | show (In x) = show x | | Of course that constraint didn't w

Re: Type class problem

2003-08-17 Thread Brandon Michael Moore
On Sun, 17 Aug 2003 [EMAIL PROTECTED] wrote: > > > I defined type recursion and naturals as > > > >newtype Mu f = In {unIn :: f (Mu f)} > > >data N f = S f | Z > > >type Nat = Mu N > > > An application of Mu should be showable if the functor maps showable types > > to showable types, so the most

Re: Type class problem

2003-08-17 Thread oleg
> I defined type recursion and naturals as > >newtype Mu f = In {unIn :: f (Mu f)} > >data N f = S f | Z > >type Nat = Mu N > An application of Mu should be showable if the functor maps showable types > to showable types, so the most natural way to define the instance seemed > to be > instance

Type class problem

2003-08-14 Thread Brandon Michael Moore
To try some of the examples from paper "Recursion Schemes from Comonads", I wanted to define instances of Show and Observable for types defined as the fixed point of a functor. I defined type recursion and naturals as >newtype Mu f = In {unIn :: f (Mu f)} >data N f = S f | Z >type Nat = Mu N An