[Haskell-cafe] ANNOUNCE: metaplug

Axel Mannhardt michaxm at googlemail.com
Tue Oct 16 08:03:52 EDT 2007


Hello,

There is one limitation to this, however. compileCall expects to compile a
> dynamic via GHC.dynCompileExpr;
> what this means is your resource must be monomorphic (for Typeable to
> work.) As of right now, the easiest
> way I can see to get around this is to simply define a datatype like such:
>
> data Plugin {
> rsrc :: ... -- your type here
> } deriving Typeable


I have the same problem, although from a different direction. I am only
interested in an eval-myDynamicFunction functionality not general modules,
so I did it on a per function basis, using hs-plugins eval.
A typeable data wrapper would be fine for me, although I have not yet found
a non-ugly way to import needed modules for the plugin, as the plugin source
would not be necessarily in the same place as the API. But thats rather an
implementation detail.

The real problem is, that I do not know, if there is an appropriate way to
represent functions with a dynamic parameter count. As of now, I think it
would need a bigger amount of hacking than it is worth to get rid of the
workarounds I already have, but it would be interesting anyway.


> (unsafeCoerce# is an option but there's not a version
> of compileCall to support this as of right now. I might add it if it seems
> needed.)
>

As I am relatively new, and since I have not found any introduction what
unsafeCoerce is actually capable of (and how), I have ignored this
possibility. Could someone give me some pointers? (the most useful thing I
found is http://osdir.com/ml/lang.haskell.glasgow.bugs/2005-03/msg00048.html
)

The approach I stopped working at was:


type TestSpecs = (String, String, String)

data FunctionTest = forall a b
. (Show a, Show b,
Eq b) =>
                    FunctionTest (String
, [a], (a
->b), [b])
deriving Typeable

readFunctionTest :: TestSpecs
-> IO (Either [String]
(Maybe FunctionTest))
readFunctionTest (
params,fn,predicted) = eval_
 str ["FunctionTest"] ["-i"++libDir] [] [libDir]

    where str = "FunctionTest("++show
fn++", "++params++", "
++fn++", "++predicted++")"


applyFunctionTest :: FunctionTest -> [Bool
]
applyFunctionTest (FunctionTest (_
,parameters,function,predicted)
) = zipWith (==) (map
 function parameters) predicted

..what works for general Functions with one Parameter. The wrapper ensures
that the function takes one value to produce another value comparable to the
other given value. So far, this looks ok to me, I can 'read' a function once
and apply it to multiple tests. However, if the function has more than one
curried parameter, it has to be extended. I see the following approaches:

-Do everything inside the eval (returning a [Bool] for example). That works,
and I use it right now, but apart from being ugly, the function has to be
read more than once. This might be a non-practical issue though.

-Introduce constructors for each parameter count (up to a limit).

FunctionTest2 (String,
[(a,a')], (a->a'->
b), [b])
applyFunctionTest
 (FunctionTest2 ...{-this might be generalizeable-}

That is a lot more redundant and not as general as the inside-eval approach,
but the function has to be read only once.

-Convert any functions into ones that take one list/tuple parameter within
the eval (assume there is no type ambiguity for simplicity). Partial
application is not the goal here anyway and information about the parameter
count could be obtained from the "parameter"-parameter or from additional
information in the function String itself.
But for that a wrapper has to be added to the code inside eval that turns a
function with unknown parameter count into the one actually exported. The
type of this transformer function could be distinguished at eval compile
time, but that means the implementation would have to be included in each
eval...

uncurry3 fn (a, b, c) = fn a b c
uncurryN = --would be defined using template Haskell or recursive data
structures or something else I do not know yet

--simpler as a list
uncurryL fn [] = fn
uncurryL fn (x:xs) = uncurryL (fn (fromValue x)) xs
-- but then the values would have to be wrapped for type ambiguity:
data Value = IntV Int | ...


I had a look on some techniques to deal with dynamic parameter count, but
they are either decided at runtime (as my understanding of QuickCheck and
its recursive data types is) or they do not represent functions with unknown
parameter count but only process one at a time (as Printf does). Tell me if
I am wrong.

So, I end up with three possibilities how to do the job (although I have not
tried to implement all of them), but I am unhappy with each. How would one
express a type "a->...->b" in Haskell (GHC)? Are you able to express the
second approach without the redundant FunctionTestN definitions? I am
willing to do ugly things, as long as I can restrict the effects to that
particular place.

Thanks,
Axel
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071016/f0daf370/attachment.htm


More information about the Haskell-Cafe mailing list