Chris Taylor
Chris Taylor

Reputation: 47402

Make functions an instance of vector type class

I have a custom type class for mathematical vectors

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

class Vector v a where

    infixl 6 <+>
    (<+>) :: v -> v -> v  -- vector addition

    infixl 6 <->
    (<->) :: v -> v -> v  -- vector subtraction

    infixl 7 *>
    (*>)  :: a -> v -> v  -- multiplication by a scalar

    dot   :: v -> v -> a  -- inner product

and I want to make numbers a and functions a -> vector into an instance of the class. Numbers are easy:

instance Num a => Vector a a where
    (<+>) = (+)
    (<->) = (-)
    (*>)  = (*)
    dot   = (*)

and I thought functions would also be easy (well, except for dot, but I can live with that)

instance Vector b c => Vector (a -> b) c where
    f <+> g = \a -> f a <+> g a
    f <-> g = \a -> f a <-> g a
    c *>  f = \a -> c *> f a
    dot     = undefined

However, I get the following error:

Ambiguous type variable `a0' in the constraint:
  (Vector b a0) arising from a use of `<+>'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: f a <+> g a
In the expression: \ a -> f a <+> g a
In an equation for `<+>': f <+> g = \ a -> f a <+> g a

How can I tell GHC that the instance is valid for all types a? Where am I supposed to add the type signature?

Upvotes: 8

Views: 613

Answers (2)

AndrewC
AndrewC

Reputation: 32475

Type families are definitely the loveliest way of solving this problem

{-# LANGUAGE TypeFamilies, FlexibleContexts #-} 
class VectorSpace v where
    type Field v

    infixl 6 <+>
    (<+>) :: v -> v -> v  -- vector addition

    infixl 6 <->
    (<->) :: v -> v -> v  -- vector subtraction

    infixl 7 *>
    (*>)  :: Field v -> v -> v  -- multiplication by a scalar

    dot   :: v -> v -> Field v  -- inner product

Mathematically, to make a vector space out of functions, you have to reuse the same field:

instance VectorSpace b => VectorSpace (a -> b) where
    type Field (a -> b) = Field b
    f <+> g = \a -> f a <+> g a
    f <-> g = \a -> f a <-> g a
    c *>  f = \a -> c *> f a
    dot     = error "Can't define the dot product on functions, sorry."

...and the nice thing about type families is that they work very much how you would explain. Let's make the direct product of two vector spaces:

instance (VectorSpace v,VectorSpace w, Field v ~ Field w,Num (Field v)) => VectorSpace (v,w) where
    type Field (v,w) = Field v
    (v,w) <+> (v',w') = (v <+> v',w <+> w')
    (v,w) <-> (v',w') = (v <-> v',w <-> w')
    c *> (v,w) = (c *> v, c*> w)
    (v,w) `dot` (v',w') = (v `dot` v') + (w `dot` w')

You could replace the Num context with a custom algebraic class, but Num captures the concept of a Field moderately well.

Upvotes: 6

Mikhail Glushenkov
Mikhail Glushenkov

Reputation: 15078

I was able to make the following small example (patterned after Conal Elliott's vector-space package) compile:

{-# LANGUAGE TypeFamilies #-}

module Main
       where

class Vector v where
  type Scalar v

  infixl 6 <+>
  (<+>) :: v -> v -> v  -- vector addition

  infixl 7 *>
  (*>)  :: (Scalar v) -> v -> v  -- multiplication by a scalar

instance Vector v => Vector (a -> v) where
  type Scalar (a -> v) = (a -> Scalar v)
  f <+> g = \a -> f a <+> g a
  (*>) c f  = \a -> c a *> f a -- Can't deduce that Scalar v ~ Scalar (a -> v)

It may be possible to make this work with functional dependencies instead of type families.

Upvotes: 2

Related Questions