[Haskell] [Haskell-cafe] ANNOUNCE: cinvoke 0.1 released

Gábor Lehel illissius at gmail.com
Tue Mar 8 13:01:58 CET 2011


On Sun, Mar 6, 2011 at 2:38 PM, Remi Turk <rturk at science.uva.nl> wrote:
> I am happy to finally announce cinvoke 0.1, a binding to the
> C library cinvoke[1], allowing functions to be loaded and called
> whose names and types are not known before run-time.
>
> Why?
>
> Sometimes you can't use the Haskell foreign function interface
> because you parse the type of the function from somewhere else,
> i.e. you're writing an interpreter for a language that has an FFI
> itself.
>
> What?
>
> The main function it exports is:
>
>  cinvoke :: Symbol -> RetType b -> [Arg] -> IO b
>
> And because code is worth a thousand words, here's a small program
> that uses libc to write a 1Gb buffer of random garbage to a file:
>
>> module Main where
>>
>> import Foreign.CInvoke
>>
>> main = do
>>     cxt <- newContext
>>     libc <- loadLibrary cxt "libc.so.6"
>>     malloc <- loadSymbol libc "malloc"
>>     creat  <- loadSymbol libc "creat"
>>     write  <- loadSymbol libc "write"
>>     free   <- loadSymbol libc "free"
>>     let sz = 2^30
>>     buf <- cinvoke malloc (retPtr retVoid)
>>                                     [argCSize sz]
>>     fd  <- cinvoke creat  retCInt   [argString "/tmp/test", argCUInt 0o644]
>>     n   <- cinvoke write  retCSize  [argCInt fd, argPtr buf, argCSize sz]
>>     cinvoke free (retPtr retVoid) [argPtr buf]
>
> It hopefully works on any machine on which cinvoke works,
> but has only been tested on linux x86_64.
> As the current version of cinvoke only installs a static library,
> it does not work from GHCi at the moment (without hacking cinvoke
> to build a shared library).
> More interesting examples are included in examples/ in the
> package.
>
> Where?
> Hackage: http://hackage.haskell.org/package/cinvoke
>
> Cheers, Remi
>
> [1] http://www.nongnu.org/cinvoke/

Is there any information on how this (and libffi I guess) compare to
GHC's FFI in terms of performance? Is it equivalent? Once you've
loaded a function with loadSymbol and are cinvoking it with various
arguments, versus a plain "foreign import" of the same. (Also, I
assume cinvoke corresponds to the FFI's 'unsafe' calls, i.e. if the
function tries to call back into the GHC runtime then Bad Things will
happen, and it'll block threads on the same 'Capability' if it runs
too long?)


>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



-- 
Work is punishment for failing to procrastinate effectively.



More information about the Haskell mailing list