
Hi, I am writing a little IPC system to make Haskell values and functions remotely invokable. To do so, I need (or so I believe) to make my objects accessible via a generic interface as in: class AFun f where afun :: Data a => f -> ([Dynamic] -> a) So my generic object is something that takes an array of parameters, that being Dynamic can be anything, and returns a Data, that I can easily serialise and send back on the wire. I start by defining an instance for functions: instance (Typeable a,AFun b) => AFun (a->b) where afun f (p:ps) = let Just v = fromDynamic p in afun (f v) ps afun _ _ = error "Too few arguments" So far so good, but when I try to define an instance for values: instance Data v => AFun v where afun f [] = f afun _ _ = error "Too many arguments" I get: Couldn't match expected type `a' against inferred type `v' `a' is a rigid type variable bound by the type signature for `afun' at /home/titto/.quid2/state/ubuntu.local.8080/wikidata/haskell/package/haskelld/src/HaskellD/Test.hs:7:17 `v' is a rigid type variable bound by the instance declaration .... Why is that? a and v are both declared to be a Data, why should they not match? The full code follows: {-# LANGUAGE FlexibleInstances ,UndecidableInstances ,OverlappingInstances #-} import Data.Data import Data.Dynamic class AFun f where afun :: Data a => f -> ([Dynamic] -> a) instance (Typeable a,AFun b) => AFun (a->b) where afun f (p:ps) = let Just v = fromDynamic p in afun (f v) ps afun _ _ = error "Too few arguments" instance Data v => AFun v where afun f [] = f afun _ _ = error "Too many arguments" Thanks in advance, titto

The problem lies in the definition of your class:
class AFun f where afun :: Data a => f -> ([Dynamic] -> a)
You are saying that afun can return any type "a" that the user wants as long as it is an instance of "Data", whereas here
instance Data v => AFun v where afun f [] = f afun _ _ = error "Too many arguments"
you are restricting the type returned by afun. What you probably want is a class that looks more like class Data r => AFun f r where afun :: f -> ([Dynamic] -> r) so that the return type is explicitly included in the definition of the type. Also, you might consider requiring that the argument and result be instances of Binary rather than Data, since this gives you fast binary serialization for free. Then you could write a class like class (Binary a, Binary b) => AFun a b where afun :: f -> (a -> b) And your code can take care of the serialization/deserialization and then just hand the values of the correct type over to afun. Cheers, Greg

Am Mittwoch 04 November 2009 22:03:09 schrieb Pasqualino "Titto" Assini:
Hi,
I am writing a little IPC system to make Haskell values and functions remotely invokable.
To do so, I need (or so I believe) to make my objects accessible via a generic interface as in:
class AFun f where afun :: Data a => f -> ([Dynamic] -> a)
So my generic object is something that takes an array of parameters, that being Dynamic can be anything, and returns a Data, that I can easily serialise and send back on the wire.
I start by defining an instance for functions:
instance (Typeable a,AFun b) => AFun (a->b) where afun f (p:ps) = let Just v = fromDynamic p in afun (f v) ps afun _ _ = error "Too few arguments"
So far so good, but when I try to define an instance for values:
instance Data v => AFun v where afun f [] = f afun _ _ = error "Too many arguments"
I get:
Couldn't match expected type `a' against inferred type `v' `a' is a rigid type variable bound by the type signature for `afun' at /home/titto/.quid2/state/ubuntu.local.8080/wikidata/haskell/package/haskell d/src/HaskellD/Test.hs:7:17 `v' is a rigid type variable bound by the instance declaration ....
Why is that? a and v are both declared to be a Data, why should they not match?
afun's type sgnature says "whatever type you (the caller) want, I can give it to you, as long as it's a member of Data" But v is one particular type belonging to Data, and it's the only one, the implementation of afun can provide. Maybe you want class (Data a) => AFun f a | f -> a where afun :: f -> ([Dynamic] -> a) or, with type families: class AFun f where type RType f :: * afun :: (Data (RType f)) => f -> ([Dynamic] -> RType f) I'm not quite sure whether that compiles, let alone does what you want, but it might be worth a try.
participants (3)
-
Daniel Fischer
-
Gregory Crosswhite
-
Pasqualino "Titto" Assini