<html><head><meta http-equiv="Content-Type" content="text/html charset=utf-8"></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space;" class="">I  am trying to use Functional dependencies to overload a operation on Vector space and its basis (Use the Vector spaces module <a href="https://hackage.haskell.org/package/HaskellForMaths-0.4.8/docs/Math-Algebras-VectorSpace.html" class="">Math.Algebras.VectorSpace</a>). I have tried to mimic the example for matrices and vectors from <a href="https://wiki.haskell.org/Functional_dependencies" class="">https://wiki.haskell.org/Functional_dependencies</a>. <div class="">I have tried different ways of defining classes and instances, but I do not get it to work. <br class=""><div class=""><br class=""></div><div class="">What I want is to have the «same» function for these cases: </div><div class=""><br class=""></div><div class="">operation :: a -> a -> Vect k a</div><div class="">operation :: a -> Vect k a -> Vect k a</div><div class="">operation :: Vect k a -> a -> Vect k a</div><div class="">operation :: Vect k a -> Vect k a -> Vect k a</div><div class=""><br class=""></div><div class="">Her are som sample code to illustrate what I want. Do anybody have an idea to how to solve it?</div></div><div class=""><br class=""></div><div class=""><div class="">{-# LANGUAGE MultiParamTypeClasses #-}</div><div class="">{-# LANGUAGE FlexibleInstances #-}</div><div class="">{-# LANGUAGE FunctionalDependencies #-}</div><div class=""><br class=""></div><div class="">import Math.Algebras.VectorSpace</div><div class=""><br class=""></div><div class="">linearExtension :: (Eq k, Num k, Ord a)</div><div class="">             => (a -> a -> Vect k a) -> Vect k a -> Vect k a -> Vect k a</div><div class="">linearExtension f xs ys = linear (\x -> linear (f x) ys) xs</div><div class=""><br class=""></div><div class="">data Tree t = Root t [Tree t] deriving(Eq, Show, Ord)</div><div class=""><br class=""></div><div class="">op :: (Eq k, Num k, Ord t) => Tree t -> Tree t -> Vect k (Tree t)</div><div class="">op x y = return x <+> return y</div><div class=""><br class=""></div><div class="">opA :: (Eq k, Num k, Ord t) => Vect k (Tree t) -> Vect k (Tree t) -> Vect k (Tree t)</div><div class="">opA = linearExtension op</div><div class=""><br class=""></div><div class="">class Operation a b c | a b -> c where</div><div class="">  (<.>) :: a -> b -> c</div><div class=""><br class=""></div><div class="">instance (Ord t) => Operation (Tree t) (Tree t) (Vect k (Tree t)) where</div><div class="">  (<.>)= op</div><div class=""><br class=""></div><div class="">instance (Ord t) => Operation (Vect k (Tree t)) (Vect k (Tree t)) (Vect k (Tree t)) where</div><div class="">  (<.>) = opA</div><div class=""><br class=""></div><div class="">instance (Ord t) => Operation (Tree t) (Vect k (Tree t)) (Vect k (Tree t)) where</div><div class="">  (<.>) x = opA (return x)</div><div class=""><br class=""></div><div class="">instance (Ord t) => Operation (Vect k (Tree t)) (Tree t) (Vect k (Tree t)) where</div><div class="">  (<.>) x y = opA x (return y)</div></div></body></html>