[Haskell-cafe] Haskell integration with C/C++ (GSOC)

Anthony Cowley acowley at seas.upenn.edu
Thu Apr 5 16:06:24 CEST 2012


On Thursday, April 5, 2012 at 1:53 AM, Sutherland, Julian wrote:
> Hey Guys,
> 
> I'm Julian, I am reaching the end of my second year as a JMC (Joint Mathematics and Computer science) Student at Imperial College London
> and I'd like to apply to GSOC for a project involving Haskell and I just wanted to run my idea past the community.

[snip] 
> I found an example of such a bug, which I will test further before reporting it.
> It seems to be the opposite of the following bug:
> http://hackage.haskell.org/trac/ghc/ticket/5594
> 
> i.e. the stdout buffer isn't always correctly flushed when calling C/C++ in a program whose main is written in Haskell.
> 
> For example, when running the code:
> 
> main.hs:
> module Main where
> 
> import Foreign.C.Types
> import System.IO
> 
> foreign import ccall "inc" c_inc :: CInt -> CInt
> 
> main :: IO ()
> main = do
> putStr "Enter n: " 
> -- hFlush stdout
> s <-getLine
> putStrLn . show . c_inc . read $ s
> 
> inc.c:
> 
> int inc(int i) __attribute__ ((const));
> 
> int inc(int i)
> {
> return i + 1;
> }
> 
> Built with
> Makefile:
> all: 
> gcc -c -o inc.o inc.c
> ghc --make -main-is Main main.hs inc.o -o test
> rm *.hi *.o
> 
> The output comes out as:
> [julek at cryptid inc]$ ./test 
> 2
> Enter n: 3
> 
> But when the " hFlush stdout" line is commented back in, the output is:
> [julek at cryptid inc]$ ./test 
> Enter n: 2
> 3
> 
> which is correct, but the extra line shouldn't be necessary.
> 
> I am currently using ghc 7.4.1 which is the newest version, so this is a current bug.

I think this is a consequence of line buffering rather than a bug. If you write your own increment function in Haskell, you get the same behavior. If you `hSetBuffering stdout NoBuffering` before your `putStr` call, you should get the behavior you wanted. I've seen similar issues with programs written in many languages; it's just one of those gotchas to be aware of when dealing with console UI.

As to the rest of your proposal, when you started out talking about calling Haskell from C or C++, I hoped you would focus on the pain of linking the final executable. This seems to me a more fundamental -- and addressable -- stumbling block than the richness of interaction with C++. As things stand, it is quite a hassle to use a Haskell library of any complexity called from C. Improved interaction with C++ could indeed be valuable, but, unless something has changed recently, work is still needed to improve the more basic C -> Haskell FFI story.

Anthony



More information about the Haskell-Cafe mailing list