[Haskell-cafe] Functional dependencies and overloading of operation
Erik Hesselink
hesselink at gmail.com
Mon Feb 29 19:39:38 UTC 2016
In the future you might get more responses if you also post the error
message. I pasted your code, commented out the external stuff, and
got:
• Illegal instance declaration for
‘Operation (Tree t) (Tree t) (Vect k (Tree t))’
The coverage condition fails in class ‘Operation’
for functional dependency: ‘a b -> c’
Reason: lhs types ‘Tree t’, ‘Tree t’
do not jointly determine rhs type ‘Vect k (Tree t)’
Un-determined variable: k
• In the instance declaration for
‘Operation (Tree t) (Tree t) (Vect k (Tree t))’
So it's saying that, while you state with `a b -> c` that types `a`
and `b` together determine `c`, this is not the case for the `(Tree t)
(Tree t)` instance, since they don't determine what type variable `k`
should be. I don't know the package or domain you're working with, but
that might help you get further.
Erik
On 28 February 2016 at 22:00, Kristoffer Føllesdal <kfollesdal at gmail.com> wrote:
> 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). I have tried to mimic the example for matrices
> and vectors from 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)
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list