[Haskell-cafe] Re: Problem with fundeps.

Keean Schupke k.schupke at imperial.ac.uk
Mon Jan 3 06:37:43 EST 2005


I would suggest defining types for unit and functions...

data Scalar a = Scalar a
data Function c v = Function c v

instance VSpace a (Scalar a) ... -- replaces 'a'
instance VSpace a (Function c a) ... -- replaces c -> a
instance VSpace a v => a (Function c v) ... -- replaces c -> v

Here Scalar is just a 'special' identity, and 'Function' is a 'special'
arrow (->) ...

    Keean.

karczma at info.unicaen.fr wrote:

> Ashley Yakeley writes:
>
>> GHCi is correct to complain:
>>
>>> class Vspace a v | v -> a
>>
>>
>> OK, the first parameter ("a") depends on the second ("v").
>
>
> This is what I want. For a given set of vectors, the associated
> scalars are unique, otherwise I would have problems with norm.
> But I have problems anyway...
>
>>
>>> instance Vspace a a where
>>
>>
>> And this determines it: the first parameter must always be the same 
>> as the second.
>>
>>> instance (Vspace a v) => Vspace a (c->v) where
>>
>>
>> This is incompatible with the previous instance declaration, since 
>> "a" is not the same as "c -> v". 
>
>
> Why "always the same"? This is just *this* instance.
> If I eliminate Vspace a a, and I write
> instance (Num a)=>Vspace a (c->a) where
> (f <+> g) x = f x + g x
> (a *> f) x = a * f x
> and then I tried to generalize, by
> instance (Vspace a v) => Vspace a (c->v) where
> (f <+> g) x = f x <+> g x
> -- ...
> I get another error, even less understandable. Can you
> guess it without testing?...
> I permitted all extensions, overlapping instances, etc.
>
> Jerzy Karczmarczuk
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list