Re: [Haskell] type inference & instance extensions

2009-01-27 Thread Jonathan Cast
On Tue, 2009-01-27 at 10:05 -0800, Corey O'Connor wrote: > On Tue, Jan 27, 2009 at 4:51 AM, wrote: > > Doug McIlroy wrote: > >> A fragment of an attempt to make pairs serve as complex numbers, > >> using ghc/hugs extensions: > >> > >> instance Num a => Num (a,a) where > >>

RE: [Haskell] type inference & instance extensions

2009-01-27 Thread Sittampalam, Ganesh
Corey O'Connor wrote: > On Tue, Jan 27, 2009 at 4:51 AM, wrote: >> Doug McIlroy wrote: >>> A fragment of an attempt to make pairs serve as complex numbers, >>> using ghc/hugs extensions: >>> >>> instance Num a => Num (a,a) where >>> (x,y) * (u,v) = (x*u-y*v, x*v+y*u) >>

Re: [Haskell] type inference & instance extensions

2009-01-27 Thread Corey O'Connor
On Tue, Jan 27, 2009 at 4:51 AM, wrote: > Doug McIlroy wrote: >> A fragment of an attempt to make pairs serve as complex numbers, >> using ghc/hugs extensions: >> >> instance Num a => Num (a,a) where >> (x,y) * (u,v) = (x*u-y*v, x*v+y*u) > The recent versions of GHC have a

Re: [Haskell] type inference & instance extensions

2009-01-27 Thread ChrisK
In ghc 6.10.1 the ~ constraint is working: {-# LANGUAGE TypeFamilies #-} {-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} module D where instance (Num a, Num b, a ~ b) => Num (a,b) where (x,y) * (u,v) = (x*u-y*v, x*v+y*u) test1 = (1,1) * (2,2) test2 = (1,1.0)

[Haskell] type inference & instance extensions

2009-01-27 Thread oleg
Doug McIlroy wrote: > A fragment of an attempt to make pairs serve as complex numbers, > using ghc/hugs extensions: > > instance Num a => Num (a,a) where > (x,y) * (u,v) = (x*u-y*v, x*v+y*u) > > Unfortunately, type inference isn't strong enough to cope with > > (1,1

RE: [Haskell] type inference & instance extensions

2009-01-19 Thread Sittampalam, Ganesh
Lennart Augustsson wrote: >> I had hoped that the code below (GHC 6.10+) would work, but it just >> sends GHC into a loop when you actually try to typecheck (1,1). I >> don't know if that's a bug in GHC or a misunderstanding on my part of >> how the typechecking should work. > A loop without turn

Re: [Haskell] type inference & instance extensions

2009-01-19 Thread Lennart Augustsson
A loop without turning on a flag to allow it must be a bug. -- Lennart On Mon, Jan 19, 2009 at 2:04 PM, Sittampalam, Ganesh wrote: > Doug McIlroy wrote: >> A fragment of an attempt to make pairs serve as complex numbers, >> using ghc/hugs extensions: >> >> instance Num a => Num (a,a) w

RE: [Haskell] type inference & instance extensions

2009-01-19 Thread Sittampalam, Ganesh
Doug McIlroy wrote: > A fragment of an attempt to make pairs serve as complex numbers, > using ghc/hugs extensions: > > instance Num a => Num (a,a) where > (x,y) * (u,v) = (x*u-y*v, x*v+y*u) > > Unfortunately, type inference isn't strong enough to cope with > > (

Re: [Haskell] type inference & instance extensions

2009-01-19 Thread Malcolm Wallace
Doug McIlroy wrote: > instance Num a => Num (a,a) where > (x,y) * (u,v) = (x*u-y*v, x*v+y*u) > > Unfortunately, type inference isn't strong enough to cope with > > (1,1)*(1,1) I'm guessing it is because (fromInteger 1, fromInteger 1) :: (Num a, Num b) => (a

[Haskell] type inference & instance extensions

2009-01-19 Thread Doug McIlroy
A fragment of an attempt to make pairs serve as complex numbers, using ghc/hugs extensions: instance Num a => Num (a,a) where (x,y) * (u,v) = (x*u-y*v, x*v+y*u) Unfortunately, type inference isn't strong enough to cope with (1,1)*(1,1) Why shouldn't it be strengt