
Continuing in my quest to understand type design in Haskell, here's another episode that leaves me scratching my head: module Foo where class Vect v a where (<+>) :: Floating a => v a -> v a -> v a data Vector a = Vector a a a instance Vect Vector a where (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (x1+x2) (y1+y2) (z1+z2) instance Vect [Vector a] a where (<+>) l1 l2 = zipWith (<+>) l1 l2 The problem is the last instance declaration. Hugs says "Illegal type in class constraint", which is not very explicit (which class constraint?). GHCI is a bit more verbose: Kind error: Expecting kind `* -> *', but `[Vector a]' has kind `*' When checking kinds in `Vect [Vector a] a' In the instance declaration for `Vect [Vector a] a' I have vague memories of seeing mentioned the concept of "kind", but I can't remember where. Any help would be appreciated! Konrad.

module Foo where
class Vect v a where (<+>) :: Floating a => v a -> v a -> v a
data Vector a = Vector a a a
instance Vect Vector a where (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (x1+x2) (y1+y2) (z1+z2)
instance Vect [Vector a] a where (<+>) l1 l2 = zipWith (<+>) l1 l2
The problem is the last instance declaration. Hugs says "Illegal type in class constraint", which is not very explicit (which class constraint?). GHCI is a bit more verbose:
Kind error: Expecting kind `* -> *', but `[Vector a]' has kind `*' When checking kinds in `Vect [Vector a] a' In the instance declaration for `Vect [Vector a] a'
I have vague memories of seeing mentioned the concept of "kind", but I can't remember where. Any help would be appreciated!
Konrad.
Hi Konrad, As you have mentioned Haskell's types have kinds, although they are almost always hidden from view. The kinds are there to help the compiler check whether types are well formed (including such things as instance declarations). The syntax for kinds is very simple: kind = * | kind -> kind The kind of all fully applied type constructors is *. Eg, the kind of Int, Float, Double, 'Maybe a', [Char], [a], 'Either Bool ()', is *. If a type constructor has arguments then its kind has an arrow (or more) in it. The kind of 'Maybe' is *->* (read: the Maybe type constructor takes a (type) argument of kind * and returns a type of kind *). Notice in your type scheme for <+> that the "v" type is applied to the "a" type. Because type "v" is applied to an argument (whose kind defaults to *), the kind of "v" is (*->*). Why does "a" have kind *, and not something else? Well, that's for another discussion. All the gory details are in the Haskell report. So whatever type (constructor) you try to instantiate "v" with must also have this kind. The type constructor Vector has this kind, so everything is fine there. But the type [Vector a] has only kind * (because the list type constructor is fully applied here). One way around this might be to define a new type: newtype ListVector a = LV [Vector a] instance Vect ListVector a where (<+>) (LV l1) (LV l2) = LV $ zipWith (<+>) l1 l2 Though is is bit ugly to have to mention the LV constructor all the time. Cheers, Bernie.

On Monday 18 August 2003 09:25, Bernard James POPE wrote:
The kinds are there to help the compiler check whether types are well formed (including such things as instance declarations).
The syntax for kinds is very simple: ...
Thanks for the explanation! It seems that what I need (but what apparently doesn't exist) is the equivalent of a lambda expression for type constructors, then I could write something like instance Vect (\a -> [Vector a]) a where ...
One way around this might be to define a new type:
newtype ListVector a = LV [Vector a]
instance Vect ListVector a where (<+>) (LV l1) (LV l2) = LV $ zipWith (<+>) l1 l2
Though is is bit ugly to have to mention the LV constructor all the time.
It's not just ugly, it destroys the generality of my code. I would like to be able to have generic list processing functions (think of "map") produce lists of vectors and then be able to apply the functions in class "Vect" to them. If I introduce a new type, then I will have to put wrapper functions in many places. I really want a type that is a list *and* an instance of class Vect. In fact, what I'd really like to have is even more general: instance Vect v a => Vect [Vect v a] where ... i.e. defining that a list of any Vect instance is itself a Vect instance. But I could live with the case that I presented initially. Konrad.

I think what you want are functional dependencies. On Mon, 18 Aug 2003, Konrad Hinsen wrote:
On Monday 18 August 2003 09:25, Bernard James POPE wrote:
The kinds are there to help the compiler check whether types are well formed (including such things as instance declarations).
The syntax for kinds is very simple: ...
Thanks for the explanation! It seems that what I need (but what apparently doesn't exist) is the equivalent of a lambda expression for type constructors, then I could write something like
instance Vect (\a -> [Vector a]) a where ...
One way around this might be to define a new type:
newtype ListVector a = LV [Vector a]
instance Vect ListVector a where (<+>) (LV l1) (LV l2) = LV $ zipWith (<+>) l1 l2
Though is is bit ugly to have to mention the LV constructor all the time.
It's not just ugly, it destroys the generality of my code. I would like to be able to have generic list processing functions (think of "map") produce lists of vectors and then be able to apply the functions in class "Vect" to them. If I introduce a new type, then I will have to put wrapper functions in many places. I really want a type that is a list *and* an instance of class Vect.
In fact, what I'd really like to have is even more general:
instance Vect v a => Vect [Vect v a] where ...
i.e. defining that a list of any Vect instance is itself a Vect instance. But I could live with the case that I presented initially.
Konrad.
The class you had, class (Num a) => Vector v a where <+> :: v a -> v a -> v a <*> :: a -> va -> v a requires that v be a type constructor that gives vectors when applied to a ring. Using functional dependencies you can write a types class that says a type is a vector containing elements of type a: class (Num a) => Vector v a | v -> a where <+> :: v -> v -> v <*> :: a -> v -> v The type of <+> wouldn't be allowed without the dependancy v -> a, becuase a is never mentioned in the type so there would be no way to figure out what instance to use. The dependancy says "knowing the v type of an instance uniquely determines the a type". The compiler checks that your instance declarations satisfy this, and use the information when resolving overloading. you can still declare an instance for your vector type instance (Num a) => Vector (Vector a) a where <+> = ... <*> = ... (Notice that this declare an instance for all a) You can also declare instances for v that are not type constructors data Point = Point Float Float Float instance Vector Point Float where (Point x y z) <+> (Point x2 y2 z2) = Point (x+x2) (y+y2) (z+z2) a <*> (Point x y z) = Point (a*x) (a*y) (a*z) And, you can declare an instance for lists: instance (Vector v a) => Vector [v] a where as <+> bs = zipWith (<+>) as bs a <*> vs = map (a<*>) vs With GHC this requires -fglasgow-exts (and maybe -fundecidable-instances), with Hugs you need +98. The GHC users guide, the Haskell Wiki, and the paper "Type Classes: Exploring the Design Space" are all good places for more information. Brandon

On Monday 18 August 2003 19:26, Brandon Michael Moore wrote:
I think what you want are functional dependencies. ...
Bingo! That's what I needed. I had tried something like that before, but I had started from a fundamental misunderstanding: I had assumed that class Vect v a where... would automatically make 'v' a type constructor, and all my experiments using that assumption plus dependencies produced rather useless results. What I have now satisfies all my needs (at least my current needs...), and it works with GHC. Hugs hangs in some places, but I guess that's another problem entirely.
The GHC users guide, the Haskell Wiki, and the paper "Type Classes: Exploring the Design Space" are all good places for more information.
Thanks, I'll look at all that... Konrad.

On Monday, August 18, 2003, at 04:56 PM, Konrad Hinsen wrote:
Continuing in my quest to understand type design in Haskell, here's another episode that leaves me scratching my head:
module Foo where
class Vect v a where (<+>) :: Floating a => v a -> v a -> v a
data Vector a = Vector a a a
instance Vect Vector a where (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (x1+x2) (y1+y2) (z1+z2)
instance Vect [Vector a] a where (<+>) l1 l2 = zipWith (<+>) l1 l2
This seems to work (with -fglasgow-exts): module Foo where class Vect v where (<+>) :: v -> v -> v data Vector a = Vector a a a deriving (Show, Eq) instance Floating a => Vect (Vector a) where (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (x1+x2) (y1+y2) (z1+z2) instance Floating a => Vect [Vector a] where (<+>) l1 l2 = zipWith (<+>) l1 l2 *Foo> (Vector 5 6 7) <+> (Vector 1 2 3) Vector 6.0 8.0 10.0 *Foo> [Vector 1 2 3, Vector 10 20 30] <+> [Vector 100 200 300, Vector 4 5 6] [Vector 101.0 202.0 303.0,Vector 14.0 25.0 36.0] ... or does example not do something which you want it to do? -- % Andre Pang : trust.in.love.to.save

On Monday 18 August 2003 19:10, Andre Pang wrote:
This seems to work (with -fglasgow-exts):
module Foo where
class Vect v where (<+>) :: v -> v -> v
data Vector a = Vector a a a deriving (Show, Eq)
instance Floating a => Vect (Vector a) where (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (x1+x2) (y1+y2) (z1+z2)
instance Floating a => Vect [Vector a] where (<+>) l1 l2 = zipWith (<+>) l1 l2
*Foo> (Vector 5 6 7) <+> (Vector 1 2 3) Vector 6.0 8.0 10.0 *Foo> [Vector 1 2 3, Vector 10 20 30] <+> [Vector 100 200 300, Vector 4 5 6] [Vector 101.0 202.0 303.0,Vector 14.0 25.0 36.0]
... or does example not do something which you want it to do?
Well, yes, because my original example was cut down to illustrate the problem I had. The full version of the class Vect is class Vect v a where (<+>) :: Floating a => v a -> v a -> v a (<->) :: Floating a => v a -> v a -> v a (<*>) :: Floating a => a -> v a -> v a I need the parametrization on a in order to be able to define the type of scalar multiplication. I do have the choice of "class Vect v" or "class Vect v a", both seem to do the same in this context, but in both cases "v" has the role of a type constructor. Konrad.

On Tuesday, August 19, 2003, at 03:33 AM, Konrad Hinsen wrote:
On Monday 18 August 2003 19:10, Andre Pang wrote:
This seems to work (with -fglasgow-exts):
module Foo where
class Vect v where (<+>) :: v -> v -> v
data Vector a = Vector a a a deriving (Show, Eq)
instance Floating a => Vect (Vector a) where (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (x1+x2) (y1+y2) (z1+z2)
instance Floating a => Vect [Vector a] where (<+>) l1 l2 = zipWith (<+>) l1 l2
*Foo> (Vector 5 6 7) <+> (Vector 1 2 3) Vector 6.0 8.0 10.0 *Foo> [Vector 1 2 3, Vector 10 20 30] <+> [Vector 100 200 300, Vector 4 5 6] [Vector 101.0 202.0 303.0,Vector 14.0 25.0 36.0]
... or does example not do something which you want it to do?
Well, yes, because my original example was cut down to illustrate the problem I had. The full version of the class Vect is
class Vect v a where (<+>) :: Floating a => v a -> v a -> v a (<->) :: Floating a => v a -> v a -> v a (<*>) :: Floating a => a -> v a -> v a
I need the parametrization on a in order to be able to define the type of scalar multiplication.
I do have the choice of "class Vect v" or "class Vect v a", both seem to do the same in this context, but in both cases "v" has the role of a type constructor.
Ah. What about the code I gave above, and in addition to that: class (Floating a, Vect v) => VectMult v a where (<*>) :: a -> v -> v instance VectMult (Vector Float) Float where (<*>) n (Vector x y z) = Vector (n*x) (n*y) (n*z) ? -- % Andre Pang : trust.in.love.to.save

On Mon, Aug 18, 2003 at 07:33:47PM +0200, Konrad Hinsen wrote:
Well, yes, because my original example was cut down to illustrate the problem I had. The full version of the class Vect is
class Vect v a where (<+>) :: Floating a => v a -> v a -> v a (<->) :: Floating a => v a -> v a -> v a (<*>) :: Floating a => a -> v a -> v a
I need the parametrization on a in order to be able to define the type of scalar multiplication.
Would this suffice? module Foo where class Vect v a | v -> a where (<+>), (<->) :: Floating a => v -> v -> v (<*>) :: Floating a => a -> v -> v data Vector a = Vector a a a deriving (Show) instance Vect (Vector a) a where (<+>) = fzipWith (+) (<->) = fzipWith (-) (<*>) = fmap . (*) instance Vect [Vector a] a where (<+>) = zipWith (<+>) (<->) = zipWith (<->) (<*>) = fmap . (<*>) instance Functor Vector where fmap f (Vector x y z) = Vector (f x) (f y) (f z) class Functor z => Ziptor z where fzipWith :: (a -> b -> c) -> z a -> z b -> z c instance Ziptor Vector where fzipWith f (Vector x1 y1 z1) (Vector x2 y2 z2) = Vector (f x1 x2) (f y1 y2) (f z1 z2) Hm, did anyone else ever want a Ziptor class? (I didn't, until now ;)) Happy hacking, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

On Monday 18 August 2003 22:24, Remi Turk wrote:
Would this suffice? ...
I guess so - it looks like what Brandon proposed, up to cosmetic differences. Still, those cosmetic differences give me the chance to ask another question.
instance Functor Vector where fmap f (Vector x y z) = Vector (f x) (f y) (f z)
Under what conditions would Haskell programmers make some type an instance of Functor? Whenever it could possibly be done (i.e. whenever fmap makes sense)? Or just when fmap would be used frequently for some type? In this case, I can't think of any other use for fmap than defining scalar multiplication. There is no other vector operation that applies some operation to each element and returns another vector. Would it be considered "better" to define fmap nevertheless, and then use it in scalar multiplication, or would one prefer to define the mapping operation into its only application? Konrad.

G'day all. On Tue, Aug 19, 2003 at 12:31:08PM +0200, Konrad Hinsen wrote:
Under what conditions would Haskell programmers make some type an instance of Functor? Whenever it could possibly be done (i.e. whenever fmap makes sense)? Or just when fmap would be used frequently for some type?
Like anything else in software development, it's a judgement call. The questions you have to ask might include: - Does it make sense? - Is it an appropriate abstraction for this type? - Would I want to encourage another programmer to use it? - Do I want to use it myself? - Would it unnecessarily limit the possible implementations of this abstract type? The last point is particularly important to consider. A Set-like type, for example, is mathematically a functor, but any implementation of fmap will in general change the relative orderings, hash values etc of member elements. This means that supporting fmap efficiently might rule out many interesting implementations of this container. If in doubt, don't implement it (yet). Cheers, Andrew Bromage
participants (6)
-
Andre Pang
-
Andrew J Bromage
-
Bernard James POPE
-
Brandon Michael Moore
-
Konrad Hinsen
-
Remi Turk