Marcin 'Qrczak' Kowalczyk:
> > Ah, I was once doing such overloading of IO functions. I tried but
> > was not able to adapt it to "threaded" foreign calls.
>
> Help! Now it looks easier, but still I can't get it.
You seem to like puzzles?-) I almost gave up on this one,
and now it looks so simple...
> Conversion of the return value will be later, now only these.
> I want to produce something like
> call :: Call f h => f -> h
> instance Call (IO a) (IO a)
> instance (Arg fa ha, Call ff hf) => Call (fa -> ff) (ha -> hf)
>
> I don't have an idea which functions to put in a class to tie the
> recursion! The problem is that arg needs IO just here, and in a
> class IO is hidden deep inside the function type.
Right. So one of the problems is how to get it out of there. But first,
let's see whether I got your additional requirements, compared to my
first solution:
- threaded (in IO) conversion of parameters,
foreign call might modify parameters
(that should already be possible with the original code: parameter-/
result-conversion and foreign function were in IO; the recursive case
built up a prelude for parameter conversion, the base case executed
that threaded prelude before calling the foreign function)
- separate parameters for the foreign function
(in contrast to the single parameter area in my code)
- more than one foreign type, dependent on the original parameter type
Modified code that seems to address these is attached, but it was a bit
tricky to get there, so it might be helpful to outline the approach:
I assume a binary type relation (ForeignForType tf t), telling us which
foreign type tf corresponds to which Haskell type t, and how to convert
between the two (in IO).
The next step is to try and write down the family of call(n)-functions in
such a way that we can look for an inductive definition.
In the base case for the call(n)-functions, we've got a foreign function
with no parameters, so we only need to execute it and convert the return
value. I got rid of the type dummies from the first variant, so we'll need
some explicit type declarations when we use call(n). The signatures for
(call(n) ff) and ff should have the same arity (IO _ here), but the
parameter and result types in the foreign function will be related to the
types in the result signature by the ForeignForType-relation.
call(0) ff = do {rf <- ff; fromForeign rf}
Instead of accumulating all parameters in a buffer, as in the previous
variant, we assume here that ff has been partially applied to its
(converted) parameters. Can we make that work in the recursive
case? We want to take one parameter p, convert it, and apply ff to
the converted pf before calling the recursion:
call(n+1) ff p = call(n) (do ... pf <- toForeign p; .. ff pf .. ??)
There is a slight problem here, as (ff pf) may only be a partial
application (with further parameters waiting to be added in call(n)).
So we don't want to execute (ff pf) here, but the converted pf is
only available inside the io-monad.. I think this is the problem you
alluded to.
My workaround: we're only chaining up the parameter conversions
here, so the whole io-script won't be executed before we reach the
base case. We have to get ff into this fragment of the io-script, so
that we can apply it to pf, but we don't need to execute it just yet,
so we can just return the partial application (ff pf) as the result of
this io-script fragment. This means that the types change, and the
base case has to be modified slightly, too:
call(0) :: ForeignForType tf t => IO (IO tf) -> IO t
call(0) ioff = do { ff <- ioff; rf <- ff; fromForeign rf }
call(n+1) :: ForeignForType tf t, ??? bf b => IO (tf -> bf) -> t -> b
call(n+1) ioff p =
call(n) (do
{ff <- ioff
;pf <- toForeign p
;return (ff pf)
})
The types are a bit tricky now: t is the current parameter/result-type,
tf is its foreign equivalent (related by ForeignForType). The parameter
to call(n) is now an io-script that will return a (partially applied)
foreign function.
So, in the base case, the parameter returns an io-action that
returns a foreign type tf, and after conversion, the result of call(0)
is an io-action returning the corresponding type t.
In the recursive case, the first parameter returns a function from
a foreign type tf to a remaining, equally foreign, signature bf.
Conversion takes us from t to tf, partial application turns
(tf->bf) into bf and (t->b) into b. The recursive call should take
care of relating bf to b (and give us the missing type relation).
Assuming the ideas are correct, we are almost there now, just
need to translate the pseudo-code into a type class and its
instances.. My first idea is always to capture the similarity in
the types in parameterized type-constructors - as usual, this
doesn't quite work, so I omit this step here..
Next stop, we only give the raw structure of the types in the
signature of callN, trying to tie the necessary knots in the
class and instance heads by relating foreign signatures to
high-level signatures. This works a little better, but the
ForeignForType-constraint gets in the way - we need to talk
about parts of the signature, and we can't have non-variable
types as parameters in a class head..
Next try, we make the CallN class and the type of its member
callN more general than we would like to, hoping to capture
the constraints in the instances. This is the variant in the
attachment - the class doesn't tell us a lot, and the constraints
end up in the instances, where they seem to belong (at least
Haskell wants them there..).
I've found simplified examples in which this scheme seems to
work as expected (see attachment, tested in Hugs-Nov-1999,
Hugs-mode), so I better stop here before it all falls apart again;-)
Of course, I've omitted some minor wrong paths and dead alleys..
In brief, you make an educated guess, bump into some limitation of
Haskell's type class system, and restructure the whole program to get
around the limitation. Repeat until finished (or tired..).
> Maybe some additional type parameters with functional
> dependencies could help here. I've already done a similar case,
> <http://qrczak.ids.net.pl/Printf.hs>, but that was easier.
Functional dependencies might help to get rid of some type
declarations. In the current code, Haskell's type class mechanism
cannot guess the foreign type from its high-level equivalent.
I'm not sure whether this second variant matches all your
requirements, but it seems to be two steps closer, even if the
types differ from your spec.
The two main problems were (a) to get the io-type out of the
way, to interleave parameter type conversions in io and partial
applications of the foreign function to the converted parameters
in a sensible way, and (b) to capture the simultaneous recursion
over two related type-signatures with (extended) Haskell's type
class mechanism. The latter looks like a zipWith at the level of
types, so we are even back to our subject-line.
Claus
PS. Even if this should do what you want, I'm not sure how
much type-class machinery and partial applications you'll
want to introduce at the ground level of a foreign function
interface. Unless compilers are very good at getting all
this machinery out of the way, the word overhead comes
to mind.
tut2.hs