Make functions an instance of vector type class

做~自己de王妃 提交于 2020-01-12 15:48:34

问题


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?


回答1:


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.




回答2:


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.



来源:https://stackoverflow.com/questions/13029532/make-functions-an-instance-of-vector-type-class

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!