[Haskell] type inference & instance extensions

Simon Peyton-Jones simonpj at microsoft.com
Wed Jan 28 12:44:30 EST 2009


[Redirecting to GHC users]

The <<loop>> is a bug. Thank you! I'll Trac it.

Simon

| -----Original Message-----
| From: haskell-bounces at haskell.org [mailto:haskell-bounces at haskell.org]
| On Behalf Of Sittampalam, Ganesh
| Sent: Monday, January 19, 2009 2:05 PM
| To: haskell at haskell.org
| Subject: RE: [Haskell] type inference & instance extensions
|
| 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)*(1,1)
| >
| > Why shouldn't it be strengthened to do so?
|
| The problem is that type classes are an "open" system. Although it's
| obvious that your instance is the only one in this code that can be
| used to type-check (1,1), that doesn't preclude new code adding an
| instance that could make it behave differently.
|
| 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.
|
| {-# LANGUAGE FlexibleInstances, TypeFamilies #-}
|
| instance (a~b, Num a) => Num (a, b) where
|   fromInteger k = (fromInteger k, fromInteger 0)
|   (x,y) * (u,v) = (x*u-y*v, x*v+y*u)
|
| PS: Sorry, I didn't mean to say "typecheck (1,1)". I meant to say
| "evaluate (1,1)*(1,1)" - I had a suspicion that some kind of infinite
| polymorphic recursion through the Num instance is happening and
| accidentally turned that thought into a completely different statement.
|
|
| Ganesh
|
| =======================================================================
| =======
| Please access the attached hyperlink for an important electronic
| communications disclaimer:
|
| http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
| =======================================================================
| =======
|
| _______________________________________________
| Haskell mailing list
| Haskell at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell



More information about the Glasgow-haskell-users mailing list