[Haskell-cafe] ANNOUNCE: cinvoke 0.1 released
Remi Turk
rturk at science.uva.nl
Sun Mar 6 14:38:54 CET 2011
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/
More information about the Haskell-Cafe
mailing list