param classes with dependencies. I tried to generalize one of my old
packages for quantum *abstract* computations, where state vectors are
defined as functional objects, whose codomain has some arithmetic.
It is easy to see that you can define (f <+> g) = \x -> f x + g x
etc. It should be possible to curry this further, so I defined
class Vspace a v | v -> a
where
(<+>) :: v -> v -> v
(*>) :: a -> v -> v
-- etc.
instance Vspace a a where
(<+>) = (+)
(*>) = (*)
-- etc. No problem.
instance (Vspace a v) => Vspace a (c->v) where
f <+> g = \x -> f x <+> g x
(a *> f) x = a *> (f x)
-- ...
GHCi answers
Cannot unify the type-signature variable `v' with the type `c -> v'
Expected type: c -> v
Inferred type: v
When using functional dependencies to combine
Vspace a a, arising from the instance declaration at ./Qutils.hs:30
Vspace a (c -> v),
arising from the instance declaration at ./Qutils.hs:38
When trying to generalise the type inferred for `<+>'
Signature type: forall a c v.
(Vspace a v) =>
(c -> v) -> (c -> v) -> c -> v
Type to generalise: (c -> v) -> (c -> v) -> c -> v
Do YOU understand this, folks?
Muchas gracias.
Jerzy Karczmarczuk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe