
Hello! I can't understand why the following dummy example doesn't work. {-# OPTIONS -XTypeSynonymInstances #-} {-# OPTIONS -XFlexibleInstances #-} module Main where import Data.Array.Unboxed class Particle p type ParticleC = (Double, Double, Double) instance Particle ParticleC class Configuration c where getParticleI :: (Particle p) => c -> Int -> p type Collection p = UArray (Int,Int) Double instance Configuration (Collection p) where getParticleI config i = (1,1,1) :: ParticleC

Hello Grigory, Monday, August 17, 2009, 10:35:33 AM, you wrote:
Hello! I can't understand why the following dummy example doesn't work.
http://haskell.org/haskellwiki/OOP_vs_type_classes shortly speaking, throw away your OOP experience and learn new paradigm from scratch. also, http://rsdn.ru/forum/decl/2517181.1.aspx -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi, One reason (there may be more) is as follows: Grigory Sarnitskiy wrote:
class Configuration c where getParticleI :: (Particle p) => c -> Int -> p
This type signature declares that for any type c that has a Configuration instance (and an Int), you can give me back something that is of *any type* p, provided I have a Particle instance for p. So if I was to declare: instance Particle Int Then I should be able to do: x :: Int x = getParticleI someConfigurationItem 6 But...
type Collection p = UArray (Int,Int) Double instance Configuration (Collection p) where getParticleI config i = (1,1,1) :: ParticleC
What you are doing in your instance, however, is always returning a ParticleC, which is a specific type rather than any type that belongs to Particle. There are several ways to solve this. A few examples: 1. Make getParticleI specifically return a ParticleC, rather than the type p. 2. Add a makeParticle function to the particle type-class. If you had: class Particle p where makeParticle :: (Double, Double, Double) -> p Then you could rewrite that last line as: getParticleI config i = makeParticle (1, 1, 1) And then the return would be of any type p that has a Particle instance. 3. Parameterise the collection over the particle, e.g. class Configuration c where getParticleI :: Particle p => c p -> Int -> p But currently Collection is not actually parameterised using the p parameter (the UArray has Double, not Particle), so I can't properly adjust your example for that. Hope that helps, Neil.

I'm not exactly sure what you're trying to do, but the problem is that
you're trying to return a specific value where the type signature is
polymorphic.
getParticleI returns a p, (with the constraint that p is a type in the
class Particle)
This means that getParticleI can be called in any context that needs a
Particle p, but your getParticleI returns (Double, Double, Double) so it
would only work in a context that needed a (Double, Double, Double), and the
type signature doesn't reflect that, so you get an error.
To emphasize the problem, say I make a ParticleD
type ParticleD = (Int, Int)
instance Particle ParticleD
let (a, b) = getParticleI myConfig 5 -- this is perfectly valid since
ParticleD is a Particle, but doesn't work with your getParticleI definition
because it returns a specific type (Double, Double, Double).
Do you see what I mean?
You can fix it by either fixing the type of getParticleI:
getParticleI :: c -> Int -> ParticleC
or by using multiparameter type classes
class Configuration c p where
getParticleI :: (Particle p) => c -> Int -> p
depending on what you're actually trying to do.
- Job
On Mon, Aug 17, 2009 at 2:35 AM, Grigory Sarnitskiy
Hello! I can't understand why the following dummy example doesn't work.
{-# OPTIONS -XTypeSynonymInstances #-} {-# OPTIONS -XFlexibleInstances #-} module Main where import Data.Array.Unboxed
class Particle p
type ParticleC = (Double, Double, Double) instance Particle ParticleC
class Configuration c where getParticleI :: (Particle p) => c -> Int -> p
type Collection p = UArray (Int,Int) Double instance Configuration (Collection p) where getParticleI config i = (1,1,1) :: ParticleC _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Bulat Ziganshin
-
Grigory Sarnitskiy
-
Job Vranish
-
Neil Brown