Hello,

I'm trying to make two simple classe which would help me to transform unserializable datatypes to serializable ones.
The classes are:
class (Binary b) => Binarizable a b | a -> b where
  toBinary :: a -> b

class (Binarizable a b, Monad m) => Unbinarizable a b m | a -> b where
  fromBinary :: b -> m a

The idea is simple: if we have a type 'a' which cannot be serialized (for instance because it contains functions), we may turn it into a 'b' type which is instance of Binary, with of course a loss of information.
And then, Unbinarizable enables us to get the original 'a' type back. fromBinary has to run inside a monad so that it can somehow recover the lost information.

Now, for instance, in a simple role playing game, we would have the datatype :
data GameObject = GameObject {
  objIdentifier :: String,
  objEffect :: Character -> Character
}

It can't obviously be declared instance of Binary, since the field objEffect is a function. So -- since an objIdentifier must be unique -- we can declare it instance of Binarizable/Unbinarizable:
instance Binarizable GameObject String where
  toBinary = objIdentifier

instance (MonadReader [GameObject] m) => Unbinarizable GameObject String m where
  fromBinary name = liftM getIt ask
    where getIt = maybe err id . find ((== name) . objIdentifier)
          err   = error $ "Unbinarize: The object '" ++ name ++ "' doesn't exist!"

To be unbinarized, we need to have a ReaderMonad which grants us access to the list of all the objects, so that we may find the object from its identifier.


Well, here comes the trouble:
GameStructs.hs:16:9:
    Functional dependencies conflict between instance declarations:
      instance (Binary a) => Binarizable a a
        -- Defined at MagBots/GameStructs.hs:16:9-37
      instance Binarizable GameObject String
        -- Defined at MagBots/GameStructs.hs:38:9-37

GameStructs.hs:19:9:
    Functional dependencies conflict between instance declarations:
      instance (Binary a, Monad m) => Unbinarizable a a m
        -- Defined at MagBots/GameStructs.hs:19:9-50
      instance (MonadReader [GameObject] m) =>
               Unbinarizable GameObject String m
        -- Defined at MagBots/GameStructs.hs:41:9-73

I don't see why the functional dependencies conflict, since GameObject is not an instance of Binary...