
the next lap ... On Tue, 30 Mar 2004, Dylan Thurston wrote:
I recommend you use multi-parameter type classes, with a type of the scalars and the type of the vectors. For the method you're using, you need to add a 'Num a' context. You say that you 'cannot catch all requirements that instances may need', but certainly any instance will need that context.
Following your advice I tried to solve the problem with a multi-parameter type classes. Btw. I need this stuff for computations with physical values, i.e. numeric values equipped with physical units. Pure computation with physical values is no problem at all only converting the values to strings is what causes all the trouble! I compiled this text with ghc -fglasgow-exts -c VectorSpace.lhs (I like to omit -fallow-undecidable-instances before knowing what it means)
module VectorSpace where
import Data.Complex
Here is the new vector space class. Now 'v' is the vector type and 'a' is a compliant scalar type.
-- a classical linear space class VectorSpace v a where zero :: v add :: v -> v -> v scale :: a -> v -> v
instance Num a => VectorSpace a a where zero = 0 add = (+) scale = (*)
Here the compiler complains the first time: VectorSpace.lhs:27: Illegal instance declaration for `VectorSpace a a' (There must be at least one non-type-variable in the instance head Use -fallow-undecidable-instances to permit this) In the instance declaration for `VectorSpace a a'
instance RealFloat a => VectorSpace (Complex a) a where zero = 0 add = (+) scale s (x:+y) = (s*x) :+ (s*y)
instance Num a => VectorSpace [a] a where zero = repeat 0 add = zipWith (+) scale s = map (s*)
instance Num a => VectorSpace (b -> a) a where zero _ = 0 add f g x = (f x) + (g x) scale s f x = s*(f x)
To stay conform to mathematical systematics I separated the definition of the norm from the 'VectorSpace' definition.
-- a vector space equipped with a norm class VectorSpace v a => Normed v a where norm :: v -> a
instance Num a => Normed a a where norm = abs
instance RealFloat a => Normed (Complex a) a where norm = magnitude
instance Num a => Normed [a] a where -- fails for infinite lists norm = sum.(map abs)
Now I introduce a new datatype for a vector valued quantity. The 'show' function in this simplified example may show the vector with the magnitude separated from the vector components.
data Quantity v = Quantity v
instance (Show v, Fractional a, Normed v a) => Show (Quantity v) where show (Quantity v) = let nv::a = norm v in (show (scale (1/nv) v)) ++ "*" ++ (show nv)
The problem which arises here is that the type 'a' is used for internal purposes of 'show' only. Thus the compiler can't decide which instance of 'Normed' to use if I call 'show': Prelude VectorSpace> show (Quantity [1,2,3]) <interactive>:1: No instance for (Normed [t] a) arising from use of `show' at <interactive>:1 In the definition of `it': it = show (Quantity [1, 2, 3]) So I tried the approach which is more similar to what I tried before with a single-parameter type class: I use a type constructor 'v' instead of a vector type 'v' but now by the two-parameter type class I mention the type 'a' explicitly which allows for context restrictions on instantation later.
class VectorSpaceC v a where zeroC :: v a addC :: v a -> v a -> v a scaleC :: a -> v a -> v a
One consequence is now that I cannot use the scalar type 'a' as vector type, too. Instead I need some type constructor 'Identity' which I can make an instance of class 'VectorSpace'. So let's immediately switch to the complex numbers.
instance RealFloat a => VectorSpaceC Complex a where zeroC = 0 addC = (+) scaleC s (x:+y) = (s*x) :+ (s*y)
class VectorSpaceC v a => NormedC v a where normC :: v a -> a
instance RealFloat a => NormedC Complex a where normC = magnitude
But the 'Show' instance causes new trouble:
data QuantityC v a = QuantityC (v a)
instance (Fractional a, NormedC v a, Show (v a)) => Show (QuantityC v a) where show (QuantityC v) = let nv = normC v in (show (scaleC (1/nv) v)) ++ "*" ++ (show nv)
It lead the compiler eventually fail with: VectorSpace.lhs:138: Non-type variables in constraint: Show (v a) (Use -fallow-undecidable-instances to permit this) In the context: (Fractional a, NormedC v a, Show (v a)) While checking the context of an instance declaration In the instance declaration for `Show (QuantityC v a)' Does exist a clean solution for the problem at all?