Context for type parameters of type constructors

Sorry for sending this twice, but it seems to me that the newsgroup
fa.haskell only logs the discussion of haskell and haskell-cafe.
---------- Forwarded message ----------
Date: Mon, 29 Mar 2004 01:18:27 -0800
From: googlegroups@henning-thielemann.de (Henning Thielemann)
Newsgroups: fa.haskell
Subject: Context for type parameters of type constructors
NNTP-Posting-Host: 134.102.210.249
Message-ID:
module VectorSpace where
class VectorSpace v where zero :: v a add :: v a -> v a -> v a scale :: a -> v a -> v a
I haven't added context requirements like (Num a) to the signatures of 'zero', 'add', 'scale' because I cannot catch all requirements that instances may need. The problematic part is the 'scale' operation because it needs both a scalar value and a vector. Without the 'scale' operation 'v' could be simply a type (*) rather than a type constructor (* -> *). Now let's try some instances:
data (Num a) => VList a = VList [a]
instance VectorSpace VList where zero = VList (repeat 0) add (VList x) (VList y) = VList (zipWith (+) x y) scale s (VList x) = VList (map (s*) x)
data (Num a) => VFunc b a = VFunc (b->a)
instance VectorSpace (VFunc b) where zero = VFunc (\_ -> 0) add (VFunc f) (VFunc g) = VFunc (\x -> (f x) + (g x)) scale s (VFunc f) = VFunc (\x -> s*(f x))
But now GHC complains: $ ghc -c VectorSpace.lhs VectorSpace.lhs:37: Could not deduce (Num a) from the context (VectorSpace VList) arising from the literal `0' at VectorSpace.lhs:30 Probable fix: Add (Num a) to the class or instance method `zero' In the first argument of `repeat', namely `0' In the first argument of `VList', namely `(repeat 0)' In the definition of `zero': zero = VList (repeat 0) ... I hoped that when I declare VList within the context (Num a) then it is always asserted that a VList is built on a Num type. If it is necessary to add (Num a) somewhere in the instance declaration - then where? Btw. I'm using $ ghc --version The Glorious Glasgow Haskell Compilation System, version 6.0

On Mon, Mar 29, 2004 at 06:00:57PM +0200, Henning Thielemann wrote:
Thus I setup a type constructor VectorSpace in the following way:
module VectorSpace where
class VectorSpace v where zero :: v a add :: v a -> v a -> v a scale :: a -> v a -> v a
I haven't added context requirements like (Num a) to the signatures of 'zero', 'add', 'scale' because I cannot catch all requirements that instances may need.
The problematic part is the 'scale' operation because it needs both a scalar value and a vector. Without the 'scale' operation 'v' could be simply a type (*) rather than a type constructor (* -> *).
Right. 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. If you use multi-parameter type classes, then in your instance declaration you can specify exactly what requirements you need. For instance:
class VectorSpace v a where zero :: v add :: v -> v -> v scale :: a -> v -> v
instance VectorSpace IntArray Int where ...
instance (Num a) => VectorSpace (GenericArray a) a where ...
Peace, Dylan

On Tue, 30 Mar 2004, Dylan Thurston wrote:
If you use multi-parameter type classes, then in your instance declaration you can specify exactly what requirements you need. For instance:
class VectorSpace v a where zero :: v add :: v -> v -> v scale :: a -> v -> v
Multi-parameter type classes aren't Haskell 98, are they? I tried to stay away from them. I didn't get the point yet why the context for 'data' is not sufficient for the 'instance' method definition.

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?

On Sat, Apr 03, 2004 at 01:35:44PM +0200, Henning Thielemann wrote:
(I like to omit -fallow-undecidable-instances before knowing what it means)
There's a nice section in the GHC user's manual on it. I can't add anything to that.
-- a classical linear space class VectorSpace v a where zero :: v add :: v -> v -> v scale :: a -> v -> v
You might want to add a functional dependency, if you only have one type of scalars per vertor space:
class VectorSpace v a | v -> awhere zero :: v add :: v -> v -> v scale :: a -> v -> v
But then again, you might not.
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'
Well, you know how to fix this... Another way to fix it is to add a dummy type constructor:
newtype Vector a = Vector a
instance Num a => VectorSpace (Vector a) a
Later:
instance Num a => VectorSpace [a] a where
By the way, depending how you resolve the issue above, you might want instead
instance (RealFloat a, VectorSpace b a) => VectorSpace [b] a where ...
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. ... 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':
This is exactly what is fixed by adding the functional dependency above. Alternatively, if you want to consider varying the scalars, you can add 'a' as a dummy type variable to 'Quantity':
data Quantity v a = Quantity v
instance (Show v, Fractional a, Normed v a) => Show (Quantity v a) where show (Quantity v) = let nv::a = norm v in (show (scale (1/nv) v)) ++ "*" ++ (show nv)
GHC still won't accept this without prompting, but now at least you can provide a complete type: *VectorSpace> show (Quantity [1,2,3] :: Quantity [Double] Double) "[0.16666666666666666,0.3333333333333333,0.5]*6.0" Note that this makes sense semantically: if you have a vector space over both, say, the reals and the complexes, you need to know which base field to work over when you normalize.
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' ...
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)'
Hmm, I don't know how to fix up this version. Peace, Dylan
participants (2)
-
dpt@lotus.bostoncoop.net
-
Henning Thielemann