FunPtr to C function with #arguments determined at runtime?

Hello cafe, I've been poking around and I haven't seen this addressed anywhere except obliquely in the end of section 8.5.1 of the report, where it says that variable argument C functions aren't supported: http://www.haskell.org/onlinereport/haskell2010/haskellch8.html The scenario is pretty simple. I generate C code at runtime. I compile it to a .so. I know how many arguments it expects (but only at runtime), and I get a FunPtr back from 'dlsym'. How do I call it? I was hoping there would be some "Raw" lower level FFI layer that I could use to invoke a C function without automagic marshaling and all the other goodness provided by the normal "foreign import" mechanism. Failing that, will I just have to generate complex wrappers on the C side which I call N times to load up N arguments into some stateful container before finally launching the function? Thanks, -Ryan

Hi,
I think libffi might be the answer here. Please see Hackage and Haskell
wiki for details.
Cheers,
Krzysztof Skrzetnicki
17-02-2013 12:18, "Ryan Newton"
Hello cafe,
I've been poking around and I haven't seen this addressed anywhere except obliquely in the end of section 8.5.1 of the report, where it says that variable argument C functions aren't supported:
http://www.haskell.org/onlinereport/haskell2010/haskellch8.html
The scenario is pretty simple. I generate C code at runtime. I compile it to a .so. I know how many arguments it expects (but only at runtime), and I get a FunPtr back from 'dlsym'. How do I call it?
I was hoping there would be some "Raw" lower level FFI layer that I could use to invoke a C function without automagic marshaling and all the other goodness provided by the normal "foreign import" mechanism.
Failing that, will I just have to generate complex wrappers on the C side which I call N times to load up N arguments into some stateful container before finally launching the function?
Thanks, -Ryan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Quoth Ryan Newton
The scenario is pretty simple. I generate C code at runtime. I compile it to a .so. I know how many arguments it expects (but only at runtime), and I get a FunPtr back from 'dlsym'. How do I call it?
I was hoping there would be some "Raw" lower level FFI layer that I could use to invoke a C function without automagic marshaling and all the other goodness provided by the normal "foreign import" mechanism.
I feel that I might be confused about the problem, but since I don't see anyone direct answers -- in order to call a FunPtr, you can use foreign import ccall "dynamic", to create a regular function. As described in the library documentation for Foreign.Ptr, which I bet you've seen, so you know this. You can cast the FunPtr to whatever type you like, so you can call the function with an argument list different from its initial declaration. There are two types of support you don't get, as I see it: 1) Haskell isn't going to make it really super convenient to use a variably typed function, and 2) there's the argument promotion issue mentioned in the document you cited. On that second point, however you go about this, you'll need to thoroughly understand what that means, but it won't strictly prevent you from calling this function, just puts you on notice that the FFI is blind to the argument types and will make default assumptions, so your C function needs to support that. On the first point, of course that's how Haskell is - and from a design point of view, if you're writing C code to be called from Haskell, wouldn't there be better ways to accommodate variable inputs than the argument list? Donn

The scenario is pretty simple. I generate C code at runtime. I compile it to a .so. I know how many arguments it expects (but only at runtime), and I get a FunPtr back from 'dlsym'. How do I call it? I feel that I might be confused about the problem, but since I don't see anyone direct answers -- in order to call a FunPtr, you can use foreign import ccall "dynamic", to create a regular function. As described in the library documentation for Foreign.Ptr, which I bet you've seen, so you know this.
You can cast the FunPtr to whatever type you like, so you can call the
function with an argument list different from its initial declaration.
My problem is that I can't create a type representing what I want at the Haskell type-check time, and I need such a type for either casting or a foreign import. For example, let's say the function takes a number of Int arguments between 1 and 1000. If I find out at runtime that I need a function with 613 Int arguments, I would need to create the type (Int -> Int ... -> IO ()) to cast to. I suppose there may be some way to create such a dependent type with Typeable/Data.Dynamic, since it's monomorphic. Or in theory you could dynamically generate new Haskell code to create the type (System.Eval.Haskell)... libffi, which Krzysztof mentioned, is a good solution: http://www.haskell.org/haskellwiki/Library/libffi Because it allows you to pass a list of arguments callFFI :: FunPtr a -> RetType b -> [Arg] -> IO b But it does introduce an extra dependency on a C library (read, deployment liability). It "cabal install'd" the first time on my linux box, but my mac said "The pkg-config package libffi is required but it could not be found." (even though libffi.dylib is definitely installed globally). Anyway, in this case it wasn't *too *painful to just generate a bunch of extra boilerplate C functions for (1) creating a data structure to hold the arguments, (2) loading them in one at a time, and (3) deallocating the structure when the call is done. Yuck. But no extra dependencies. Cheers, -Ryan

Quoth Ryan Newton
Anyway, in this case it wasn't *too *painful to just generate a bunch of extra boilerplate C functions for (1) creating a data structure to hold the arguments, (2) loading them in one at a time, and (3) deallocating the structure when the call is done. Yuck. But no extra dependencies.
If I understand you right, that's a better direction in my view - and when I've done stuff like this I've allocated and marshalled the data structure from the Haskell side fairly painlessly with Foreign.Storable(poke) etc., and the .hsc preprocessor macros for struct access (#poke, etc.) Donn

Considering that the GHC FFI is already built on libffi (I'm reasonably
sure) it seems unnecessary for the Hackage library to depend on an external
version. Is it not already getting linked in?
On Sun, Feb 17, 2013 at 6:53 PM, Ryan Newton
The scenario is pretty simple. I generate C code at runtime. I compile it
to a .so. I know how many arguments it expects (but only at runtime), and I get a FunPtr back from 'dlsym'. How do I call it? I feel that I might be confused about the problem, but since I don't see anyone direct answers -- in order to call a FunPtr, you can use foreign import ccall "dynamic", to create a regular function. As described in the library documentation for Foreign.Ptr, which I bet you've seen, so you know this.
You can cast the FunPtr to whatever type you like, so you can call the
function with an argument list different from its initial declaration.
My problem is that I can't create a type representing what I want at the Haskell type-check time, and I need such a type for either casting or a foreign import. For example, let's say the function takes a number of Int arguments between 1 and 1000. If I find out at runtime that I need a function with 613 Int arguments, I would need to create the type (Int -> Int ... -> IO ()) to cast to. I suppose there may be some way to create such a dependent type with Typeable/Data.Dynamic, since it's monomorphic. Or in theory you could dynamically generate new Haskell code to create the type (System.Eval.Haskell)...
libffi, which Krzysztof mentioned, is a good solution:
http://www.haskell.org/haskellwiki/Library/libffi
Because it allows you to pass a list of arguments
callFFI :: FunPtr a -> RetType b -> [Arg] -> IO b
But it does introduce an extra dependency on a C library (read, deployment liability). It "cabal install'd" the first time on my linux box, but my mac said "The pkg-config package libffi is required but it could not be found." (even though libffi.dylib is definitely installed globally).
Anyway, in this case it wasn't *too *painful to just generate a bunch of extra boilerplate C functions for (1) creating a data structure to hold the arguments, (2) loading them in one at a time, and (3) deallocating the structure when the call is done. Yuck. But no extra dependencies.
Cheers, -Ryan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Newton
My problem is that I can't create a type representing what I want at the Haskell type-check time, and I need such a type for either casting or a foreign import. For example, let's say the function takes a number of Int arguments between 1 and 1000. If I find out at runtime that I need a function with 613 Int arguments, I would need to create the type (Int -> Int ... -> IO ()) to cast to. I suppose there may be some way to create such a dependent type with Typeable/Data.Dynamic, since it's monomorphic. Or in theory you could dynamically generate new Haskell code to create the type (System.Eval.Haskell)...
Simpler. This is our goal: main :: IO () main = withFunction (push 3 $ push 4 $ done) The withFunction function constructs a function at run-time, say, by reading a file, yet this is completely type-safe, statically checked code and also looks quite nice. First make a clear separation between the producer and consumer of a type. The producer constructs the type, the consumer uses it. Then you can use either existentials or higher-rank types. Let's say the user enters a number, and we want to treat it as Integer if possible, otherwise as Double. This is the traditional approach: withNum :: String -> b -> (Integer -> b) -> (Double -> b) -> b withNum str none ki kd | [(x, _)] <- reads str = ki x | [(x, _)] <- reads str = kd x | otherwise = none Here is an improved variant: withNum :: String -> b -> (forall a. (Num a) => a -> b) -> b withNum str none k | [(x, _)] <- reads str = k (x :: Integer) | [(x, _)] <- reads str = k (x :: Double) | otherwise = none This is almost the same function, but with an important difference. For both cases the same continuation is called, because withNum accepts only functions that can promise to work "for all" numeric types. In other words, the function must be polymorphic enough. What really happens here is that I determine the type at run-time depending on the string. That's how lightweight dependent types work. Meet withFunction from the teaser. It reveals only its type signature for now: withFunction :: (forall a. (Push a) => a -> IO b) -> IO b The withFunction function lifts something from value level and constructs a function of the correct type from it. Whatever the continuation receives is a function of the proper type. However, you can't just call the function yet, because withFunction's argument promises that it works for every type 'a'. So it can't just pass it an Int. That's where the Push class comes in. Here is a very simple, non-fancy Int-only way to define it: class Push a where push :: Int -> (forall b. (Push b) => b -> IO c) -> a -> IO c done :: a -> IO () instance (Push a) => Push (Int -> a) where push x k f = k (f x) done _ = throwIO (userError "Messed up my arguments, sorry") instance Push (IO ()) where push _ _ _ = throwIO (userError "Messed up my arguments, sorry") done = id Don't worry about the scary types. They are actually pretty simple: The push function, if possible, applies the given Int (first argument) to the given function (third argument). It passes the result to the continuation (second argument), which again promises to work for every Push. For non-functions a run-time exception is raised (obviously you can't do that at compile time, so this is the best we can get). Here is an example withFunction together with its application: withFunction k = let f :: Int -> Int -> IO () f x y = print x >> print y in k f main :: IO () main = withFunction (push 3 $ push 4 $ done) Ain't that nice? Of course the FunPtr is now implicit in whatever withFunction constructs it from. While you still need the foreign declaration you now get type-safety for types determined at run-time. If the constructed function takes another Int argument, push is the way to apply it. I hope this helps. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
participants (5)
-
Daniel Peebles
-
Donn Cave
-
Ertugrul Söylemez
-
Krzysztof Skrzętnicki
-
Ryan Newton