
I am a newcomer to Haskell and I'm offering my perspective on the troubles I
endured trying to make Haskell interface to some simple C programs.
It is my hope, that by documenting this, someone else will benefit from my
mistakes and errors and climb the learning curve somewhat faster than me.
I was attracted to Haskell, after playing around with OCAML,
and realizing that functional programming offers some
nice advantages to scientific programming. Mainly because the notation and
thinking is very mathematical.
But first, in order to evaluate the suitability of this language for my
purposes, I had to verify that the foreign function interface (FFI) was
suitable.
There are a number of numerical libraries, all in imperative languages,
that I
want to link to.
I quickly discovered that the documentation on Haskell's FFI
is rather poor currently. This topic is simply not of interest to the
academics I suppose. It took many hours of searching to find this document:
http://www.cs.caltech.edu/courses/cs11/material/haskell/papers/tackling_the_...
This little tutorial was a goldmine of information about monads and an
introduction to the FFI. (No template solutions for my problem sorry to
say.)
It was certainly dismaying to see that even the simplest IO requires at
least a
minimal understanding of monads, and adds a bunch of extra semantics to
the
problem. However none of the solutions offered, even the automated ones,
seemed to handle the case of passing numerical arrays to C, and having them
get updated and passed back. That is my primary interest in the FFI
and yet no obvious solution or example could be found after days of
internet
searching and pouring over tutorials etc.
My conclusion, after hours of studying the hierarchical libraries was that
I needed to use the StorableArray type which led me to this site,
http://www.haskell.org/haskellwiki/Arrays#StorableArray_.28module_Data.Array...
This site proposes the following curious piece of code:
{-# OPTIONS_GHC -fglasgow-exts #-}
import Data.Array.Storable
import Foreign.Ptr
import Foreign.C.Types
main = do arr <- newArray (1,10) 37 :: IO (StorableArray Int Int)
readArray arr 1 >>= print
withStorableArray arr $ \ptr ->
memset ptr 0 40
readArray arr 1 >>= print
foreign import ccall unsafe "string.h"
memset :: Ptr a -> CInt -> CSize -> IO ()
After having freshly read the tutorial on monads I thought I was ready for
this, but I ran into some parsing problems. I don't have a full grasp
of the precedence rules for the operators, >>= , $ and function
evaluation
are, and whether they group left to right or right to left. A little type
parsing on the inputs and outputs allowed me to resolve all but the line
withStorableArray arr $ \ptr ->
memset ptr 0 40
Which should resolve to a monad if I understand the do notation correctly.
My first assumption was that $ has lower precedence than function
application,
but a higher precendence than >> or >>=, so I assumed the grouping,
(withStorableArray arr) $ (\ptr -> (memset ptr 0 40))
Now withStorableArray has the type specification
StorableArray i e -> (Ptr e -> IO a) -> IO a ,
so it should be obvious how to use it (Not).
At any rate it takes
two arguments so I might assume that (withStorableArray arr) curries
the first argument so
that this expression is a function of type
(Ptr e -> IO a) -> IO a .
Because of the type of the array, it appears that
a = Int. However (\ptr -> (memset ptr 0 40)) should be a function of type
Ptr a -> IO(a) in order to qualify as the second argument of
withStorableArray.
This almost fits, but not quite. memset should return type
IO(Int) for this to work correctly, however according to it's type
declaration
it returns IO (). Shouldn't the compiler complain about this?
So after about 10 hours of wrestling with syntax, including messing up
the initial capitalization of module names, indenting in do lists,
forgetting
to put commas in tuples and lists I finally got the following example to
compile without error or warning
Matrix.hs
__________
import Foreign
import Foreign.C
import Foreign.C.Types (CInt, CDouble )
import Data.Array.Storable
foreign import ccall "matrix_c.h sumarr" sumarr :: Ptr CDouble -> CDouble
main = do
arr <- newListArray (1 , 3) [3,2,1]:: IO (StorableArray Int CDouble)
-- extract the pointer to arr
dsum <- withStorableArray arr (\ptr -> return (sumarr ptr ))
print dsum
matrix_c.c
------------------
#include
ghc -c matrix_c.o matrix_c.c ghc -O -o Matrix.exe -fglasgow-exts Matrix.hs matrix_c.o
It runs correctly
Matrix 5.0
Notes: ---------------------------------------------- Matrix.exe fails to work correctly if the header file matrix_c.h is not included in the foreign import statement The hack? where the second argument of withStorableArray is a -> IO() instead of a -> IO(a) allows the do clause to be simplified to main = do arr <- newListArray (1 , 3) [3,2,1]:: IO (StorableArray Int CDouble) withStorableArray arr $ print . sumarr If one changes the array in[] in the C code, e.g. double sumarr(double *in) { in[0] = -10.0 ; return(in[0] + in[1]) ; } The array is changed inside the haskell program as a side effect. main = do arr <- newListArray (1 , 3) [3,2,1]:: IO (StorableArray Int CDouble) -- extract the pointer to arr withStorableArray arr $ print . sumarr (readArray arr 1 ) >>= print I suppose this is one way to 'pass' arrays back to Haskell.

mattcbro:
I am a newcomer to Haskell and I'm offering my perspective on the troubles I endured trying to make Haskell interface to some simple C programs. It is my hope, that by documenting this, someone else will benefit from my mistakes and errors and climb the learning curve somewhat faster than me.
I was attracted to Haskell, after playing around with OCAML, and realizing that functional programming offers some nice advantages to scientific programming. Mainly because the notation and thinking is very mathematical.
But first, in order to evaluate the suitability of this language for my purposes, I had to verify that the foreign function interface (FFI) was suitable. There are a number of numerical libraries, all in imperative languages, that I want to link to.
I quickly discovered that the documentation on Haskell's FFI is rather poor currently. This topic is simply not of interest to the academics I suppose. It took many hours of searching to find this document: http://www.cs.caltech.edu/courses/cs11/material/haskell/papers/tackling_the_... This little tutorial was a goldmine of information about monads and an introduction to the FFI. (No template solutions for my problem sorry to say.)
haskell.org is the center of all things haskell. * Visit haskell.org * Click on "Books and tutorials" * Scroll to "Using Monads" * First entry in the list is this paper. You'll also find many many more articles, tutorials and code examples on haskell.org Please let us know if things aren't arranged in the most obvious manner.
It was certainly dismaying to see that even the simplest IO requires at least a minimal understanding of monads, and adds a bunch of extra semantics to the problem. However none of the solutions offered, even
Hmm. Monads are fairly easy, but have a scary name. Perhaps check out the "Yet Another Haskell Tutorial" ? Though by the soudns of it you might be passed this stage already :)
the automated ones, seemed to handle the case of passing numerical arrays to C, and having them get updated and passed back. That is my primary interest in the FFI and yet no obvious solution or example could be found after days of internet searching and pouring over tutorials etc.
Regarding arrays, generally you'd use a Foreign array, allocate it on the C side, and access it via a Foreign Ptr, no marshalling. Also, feel free to ask advice on haskell-cafe@haskell.org, or on the #haskell irc channel. There's lots of experts only too happy to help out. -- Don

| > the automated ones, seemed to handle the case of passing numerical | > arrays to C, and having them get updated and passed back. That is my | > primary interest in the FFI and yet no obvious solution or example | > could be found after days of internet searching and pouring over | > tutorials etc. | | Regarding arrays, generally you'd use a Foreign array, allocate it on | the C side, and access it via a Foreign Ptr, no marshalling. | | Also, feel free to ask advice on haskell-cafe@haskell.org, or on the | #haskell irc channel. There's lots of experts only too happy to help | out. All true. Still, Matthew is by-definition correct: he was strongly motivated, and yet failed to find the relevant material. Indeed, concerning the question of passing array values between C and Haskell, there may be no overview or tutorial, thus far. Matthew, the entire Haskell.org website is a Wiki. You might spare someone else the pain that you went through by starting a "Duffers guide to the Haskell FFI" that contains the information you wished you'd known on day 1. I'm sure you'd get lots of help on the #haskell IRC if you did so. Simon

On Mon, 15 May 2006, Simon Peyton-Jones wrote:
| > the automated ones, seemed to handle the case of passing numerical | > arrays to C, and having them get updated and passed back. That is my | > primary interest in the FFI and yet no obvious solution or example | > could be found after days of internet searching and pouring over | > tutorials etc. ... ... Indeed, concerning the question of passing array values between C and Haskell, there may be no overview or tutorial, thus far.
Or maybe it just hasn't come back from the cleaners after he poured over it. (ho ho ho) Seriously, when I went looking for information on the general subject, I think the worst problem was all the basically wrong information. I mean, I'm sure Green Card was a great step forward, but if you're trying to get started with FFI today, what you need to know about Green Card is that it's dead. Last heard from in an alpha release three years ago, and at least for someone using GHC to do simple FFI, it's unnecessary. But if you're at "Libraries and Tools/Interfacing other languages" on haskell.org, there's no hint of that. The "C" section in fact has five such libraries, but no hint that all you really need is to read the GHC user's guide. Donn Cave, donn@drizzle.com

Matthew, the entire Haskell.org website is a Wiki. You might spare someone else the pain that you went through by starting a "Duffers guide to the Haskell FFI" that contains the information you wished you'd known on day 1. I'm sure you'd get lots of help on the #haskell IRC if you did so.
The old wiki has several FFI related articles. I myself contributed example code with callbacks and a data structure as I couldnt find one when I was playing with FFI. Perhaps it could be augmented to include an array example. (Also if anyone wants to make the example better, that would be great, I am no haskell expert). http://www.haskell.org/hawiki/FfiExample http://www.haskell.org/hawiki/FfiTutorial http://www.haskell.org/hawiki/FfiCookbook Also, perhaps this should be reachable somehow from the new wiki?
Simon
Tim Newsham http://www.lava.net/~newsham/

Done! Thanks for the tip. I added a wiki page on this with my overly simple examples. Perhaps I'll extend it as I learn more. http://www.haskell.org/hawiki/FfiWithArrays -- View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4402742 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

SevenThunders wrote:
Done! Thanks for the tip. I added a wiki page on this with my overly simple examples. Perhaps I'll extend it as I learn more.
[From section under matrix1.hs example]
Now as a Haskell newbie I've been informed that the input array that is the second argument of sumarr, should be wrapped in an IO monad to keep all access sequential.
No - everything is fine as you've got it at the moment. All access is already sequential because the result of your C function is an IO action rather than a pure value ie IO CDouble instead of CDouble
Doing so, however, breaks this code so that it won't compile. It seems to me that the withStorableArray access function will only return a pointer to the elements that is already wrapped in a monad.
Shouldn't this already guarantee unique (sequential) access to the pointer? Yes, because IO actions can only be *executed* in sequence even though they can be *created* in any old place (assuming you don't use forkIO etc but
afaiu withStorableArray just returns an IO action, which, when executed, will supply the function with the pointer it needs. The result of the IO action (the value contained inside the monadic value of type "IO CDouble") is the result of the function (in your case a CDouble) that's a different story altogether)
However, what is disturbing about this is what happens if we need to replicate the pointer argument over multiple arguments in C (or some other language).
This should be fine as long as the Ptr passed to the C function is not allowed to escape from the nesting given by withStorableArray - it is only valid while the IO action returned by withStorableArray is executing, because this is the only point at which the garbage collector is not allowed to move the array about.
Also the business of having to pass multiple mutable arrays into one C function call should be addressed. For now that remains a TBD in this tutorial.
void multarr(double *mat1Raw, double *mat2Raw, double *resultRaw){ // multiply mat1 by mat2 and store in result matrix // You could mutate all of the matrices here but for multiplication obviously only // the result needs to be mutated } foreign import ccall multarr :: Ptr Double -> Ptr Double -> Ptr Double -> IO () main = do mat1 <- newListArray ... mat2 <- newListArray ... result <- newListArray ... withStorableArray mat1 (\mat1Raw -> withStorableArray mat2 (\mat2Raw -> withStorableArray result (multarr mat1Raw mat2Raw))) The nested calls to withStorableArray can be avoided by defining your own helper functions eg: withStorableArray3 :: StorableArray i1 e1 -> StorableArray i2 e2 -> StorableArray i3 e3 -> (Ptr e1 -> Ptr e2 -> Ptr e3 -> IO a) -> IO a withStorableArray3 a1 a2 a3 f = withStorableArray a1 (\a1Raw -> withStorableArray a2 (\a2Raw -> withStorableArray a3 (f a1Raw a2Raw))) Regards, Brian. PS: In GHC it's better to use the command line option (or option pragma in the source module) -#include "matrix_c.h" because if you put the header in the import declaration in GHC you lose inlining optimizations.

Thats some good info. It probably should go on that wiki page. All I need now is an unlimited amount of spare time....... -- View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420914 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

[Seven, sorry for replying just to you. Now mailing and posting]
On 5/17/06, SevenThunders
Thats some good info. It probably should go on that wiki page. All I need now is an unlimited amount of spare time....... -- View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420914 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Please quote some part of the messages you replay to. I think you use some web-interface so you see what previous messages. Most list subscribers just get the text quoted above. What is this "good info"? I don't know. I (an most of others) will not bother to "view this message in context..." This is a mailing list, NOT a forum. Regards, -- V.Rudenko -- λ is the ultimate

A confusing thing is that the Haskell web site is primarily now using MedaWiki http://haskell.org/haskellwiki/Haskell It used to use MoinMoin (pages starting http://www.haskell.org/hawiki), and that's what you used. I think your new input will be more long-lasting if you use the former. We're trying to move stuff from the latter to the former. simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of | SevenThunders | Sent: 16 May 2006 04:14 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] RE: Troubles with FFI | | | Done! Thanks for the tip. | I added a wiki page on this with my overly simple examples. | Perhaps I'll extend it as I learn more. | | http://www.haskell.org/hawiki/FfiWithArrays | -- | View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4402742 | Sent from the Haskell - Haskell-Cafe forum at Nabble.com. | | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

Aarrgh! Are the formatting commands the same? I don't want to have to rewrite the whole thing. That is a bit confusing. -- View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420902 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

Hello Donald, Saturday, May 13, 2006, 11:47:34 AM, you wrote:
* Visit haskell.org * Click on "Books and tutorials" * Scroll to "Using Monads" * First entry in the list is this paper.
but novices don't know what monads is a Haskell way to do I/O and interface with C!
It was certainly dismaying to see that even the simplest IO requires at least a minimal understanding of monads,
i think that most of Haskell programmers don't know anything about monads except that they helps in doing I/O and other funny things :)
the automated ones, seemed to handle the case of passing numerical arrays to C, and having them get updated and passed back. That is my primary interest in the FFI and yet no obvious solution or example could be found after days of internet searching and pouring over tutorials etc.
Regarding arrays, generally you'd use a Foreign array, allocate it on the C side, and access it via a Foreign Ptr, no marshalling.
it's named StorableArray -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Matthew Bromberg wrote:
foreign import ccall "matrix_c.h sumarr" sumarr :: Ptr CDouble -> CDouble [snip] If one changes the array in[] in the C code, e.g. double sumarr(double *in) { in[0] = -10.0 ; return(in[0] + in[1]) ; } The array is changed inside the haskell program as a side effect.
main = do arr <- newListArray (1 , 3) [3,2,1]:: IO (StorableArray Int CDouble) -- extract the pointer to arr withStorableArray arr $ print . sumarr (readArray arr 1 ) >>= print
If you want to change the array in the C code, the foreign import should reflect the fact that something is being mutated by enclosing the result in the IO monad: foreign import ccall "matrix_c.h sumarr" sumarr :: Ptr CDouble ->IO CDouble ^^ (You don't need to change the type of the C function itself though) Also, the 'a' in withStorableArray:: StorableArray i e -> (Ptr e -> IO a) -> IO a is the result of your C function, which in this case is CDouble. It's not related to the type of elements of the array. So you could use: withStorableArray arr $ sumarr >>= print Operator precedences are given in http://haskell.org/onlinereport/standard-prelude.html I think FFI is one of these things that once you've understood it it seems really neat and well thought out but it's as you say very difficult to get into because you need to know everything all at once and the descriptions in the FFI addendum are extremely terse and also very general, since they deal with languages other than C as well. Regards, Brian.

On Sat, 13 May 2006, Matthew Bromberg wrote:
So after about 10 hours of wrestling with syntax, including messing up the initial capitalization of module names, indenting in do lists, forgetting to put commas in tuples and lists I finally got the following example to compile without error or warning
Matrix.hs
Are you aware of darcs get http://dis.um.es/~alberto/GSLHaskell ? This may be useful both for doing matrix computations as well as understanding how FFI works.

Yup I'm aware of it, and I'd love to use it. The only problem is that it's highly linux/unix specific as far as I can tell. Even the graphics libraries it uses only runs on 'nix right now. I just tried to load graphics.hgl and hello world program crashed GHCi and doesn't compile under the regular ghc due to some missing object files. I'm running windows xp 64, though most of the software I use runs under the 32 bit emulation mode. I'd consider linux, but I don't have linux licenses for Matlab or Maple and I have to interface to the corporate MS world. Thus my 'solution' will be to make a very light weight matrix class that only pulls in a few BLAS and Lapack routines coupled with a few file based routines with gnuplot as the output, or perhaps pathon _ gnuplot as the output. With any luck I'll be able to open source that, if it does anybody any good. After that I need to automate document creation from the output of math simulations. I'll use Latex as the engine for that. It's something I've done before to great effect. -- View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4401359 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

On Mon, 15 May 2006, SevenThunders wrote:
I'd consider linux, but I don't have linux licenses for Matlab or Maple and I have to interface to the corporate MS world. Thus my 'solution' will be to make a very light weight matrix class that only pulls in a few BLAS and Lapack routines coupled with a few file based routines with gnuplot as the output, or perhaps pathon _ gnuplot as the output. With any luck I'll be able to open source that, if it does anybody any good.
I have a wrapper for basic GNUPlot control: http://www.math.uni-bremen.de/~thielema/Research/GNUPlot.hs
After that I need to automate document creation from the output of math simulations. I'll use Latex as the engine for that. It's something I've done before to great effect.
lhs2TeX can be of help for starting Haskell computations and integrating the results into the document.

lemming:
On Mon, 15 May 2006, SevenThunders wrote:
I'd consider linux, but I don't have linux licenses for Matlab or Maple and I have to interface to the corporate MS world. Thus my 'solution' will be to make a very light weight matrix class that only pulls in a few BLAS and Lapack routines coupled with a few file based routines with gnuplot as the output, or perhaps pathon _ gnuplot as the output. With any luck I'll be able to open source that, if it does anybody any good.
I have a wrapper for basic GNUPlot control: http://www.math.uni-bremen.de/~thielema/Research/GNUPlot.hs
More secret modules! Could you stick a link to this on the haskell.org wiki please, under libraries and tools somewhere? -- Don

On Tue, 16 May 2006, Donald Bruce Stewart wrote:
lemming:
I have a wrapper for basic GNUPlot control: http://www.math.uni-bremen.de/~thielema/Research/GNUPlot.hs
More secret modules! Could you stick a link to this on the haskell.org wiki please, under libraries and tools somewhere?
I've put even more top secret modules to http://darcs.haskell.org/htam/ now, but don't hold me to account for anything they do or do not.

Thanks for the gnuplot stuff. I intend to try that out. Perhaps sooner than later. As for lhs2tex, since no windows installer is provided, it might be a bit trickier and my time is very limited. Also after reviewing the manual it seems to still be focused on literate programming more than active documents. Active document support in general seems to be hard to find in the open source world. I have Maple, but their new document mode is not very useful for producing quality typeset mathematics and figures. My best results have been using either programmatically generated latex macros for inclusion into a document, or to use search and replace on text based document formats (e.g. .rtf or I suppose .pdf) -- View this message in context: http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4421523 Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
participants (10)
-
Brian Hulley
-
Bulat Ziganshin
-
Donn Cave
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
Matthew Bromberg
-
SevenThunders
-
Simon Peyton-Jones
-
Tim Newsham
-
wld