[Haskell-cafe] Functional dependencies and overloading of operation

Kristoffer Føllesdal kfollesdal at gmail.com
Sun Feb 28 21:00:42 UTC 2016


I  am trying to use Functional dependencies to overload a operation on Vector space and its basis (Use the Vector spaces module Math.Algebras.VectorSpace <https://hackage.haskell.org/package/HaskellForMaths-0.4.8/docs/Math-Algebras-VectorSpace.html>). I have tried to mimic the example for matrices and vectors from https://wiki.haskell.org/Functional_dependencies <https://wiki.haskell.org/Functional_dependencies>. 
I have tried different ways of defining classes and instances, but I do not get it to work. 

What I want is to have the «same» function for these cases: 

operation :: a -> a -> Vect k a
operation :: a -> Vect k a -> Vect k a
operation :: Vect k a -> a -> Vect k a
operation :: Vect k a -> Vect k a -> Vect k a

Her are som sample code to illustrate what I want. Do anybody have an idea to how to solve it?

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}

import Math.Algebras.VectorSpace

linearExtension :: (Eq k, Num k, Ord a)
             => (a -> a -> Vect k a) -> Vect k a -> Vect k a -> Vect k a
linearExtension f xs ys = linear (\x -> linear (f x) ys) xs

data Tree t = Root t [Tree t] deriving(Eq, Show, Ord)

op :: (Eq k, Num k, Ord t) => Tree t -> Tree t -> Vect k (Tree t)
op x y = return x <+> return y

opA :: (Eq k, Num k, Ord t) => Vect k (Tree t) -> Vect k (Tree t) -> Vect k (Tree t)
opA = linearExtension op

class Operation a b c | a b -> c where
  (<.>) :: a -> b -> c

instance (Ord t) => Operation (Tree t) (Tree t) (Vect k (Tree t)) where
  (<.>)= op

instance (Ord t) => Operation (Vect k (Tree t)) (Vect k (Tree t)) (Vect k (Tree t)) where
  (<.>) = opA

instance (Ord t) => Operation (Tree t) (Vect k (Tree t)) (Vect k (Tree t)) where
  (<.>) x = opA (return x)

instance (Ord t) => Operation (Vect k (Tree t)) (Tree t) (Vect k (Tree t)) where
  (<.>) x y = opA x (return y)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160228/bf70981a/attachment.html>


More information about the Haskell-Cafe mailing list