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
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