
Am Samstag 17 April 2010 22:01:23 schrieb Limestraƫl:
Yes! Sorry, I forgot a bit: Binary types are automatically made instances of Binarizable/Unbinarizable (that's my line 16):
instance (Binary a) => Binarizable a a where toBinary = id
instance (Binary a, Monad m) => Unbinarizable a a m where fromBinary = return
And that is your problem. The compiler only looks at the context (Binary a) *after* it has chosen an instance. When somewhere in the code it encounters "toBinary x", it looks for an instance declaration "instance Binarizable a b where" which matches x's type. Since you have "instance Binarizable a a", you have a matching instance and that is selected. *Now* the compiler looks at the context and barfs if x's type is not an instance of Binary.
To me, the functional dependency in: class (Binary b) => Binarizable a b | a -> b meant that for each a, there only one type b that can match.
Yes, that's what the functional dependency says.
That's what I want: for every Binary type 'a', the matching Binary is also 'a'
And that instance says "for every type 'a', the matching type is also 'a', and furthermore, 'a' is an instance of Binary". Contexts on a class and functional dependencies don't work as one would naively expect.
And for GameObject, the sole matching type is String. In other words, GameObject implies String. I would have undestood the error if GameObject was also an instance of Binary (then the two instances would match), but it's not the case...
The context isn't considered until after matching.
Is my FunDep wrong?
At least, the FunDep plus the generic instance is not what you want. Probably, what you want can be done with some type wizardry, but I don't know how. Perhaps the following will work: {-# LANGUAGE OverlappingInstances, TypeFamilies, MultiParamTypeClasses #-} class Binarizable a where type ToBin a toBinary :: a -> ToBin a class (Monad m) => Unbinarizable a m where type FromBin a fromBinary :: FromBin a -> m a instance Binarizable GameObject where type ToBin GameObject = String toBinary g = ... instance (Binary a) => Binarizable a where type ToBin a = a toBinary x = x instance (MonadReader [GameObject] m) => Unbinarizable GameObject m where type FromBin GameObject = String fromBinary s = ... instance (Monad m, Binary a) => Unbinarizable a m where type FromBin a = a fromBinary x = return x With OverlappingInstances, the most specific match is chosen, so for GameObjects, the special instance is selected.
I done this especially because I didn't wanted to declare each type one by one instance of Binarizable, Haskell type system normally enables me to automatically define a Binary as an instance of Binarizable.