[Haskell-cafe] Ridiculously slow FFI, or cairo binding?

Eugene Kirpichov ekirpichov at gmail.com
Wed Nov 2 10:19:08 CET 2011


I forgot to specify my environment.

Windows Server 2008 R2 x64, ghc 7.0.3.

However, I observed the same speed differences on a 64-bit ubuntu with ghc
6.12 - I profiled my application with cairo-trace, and cairo-perf-trace
drew in a fraction of a second the picture that my Haskell program spend a
dozen seconds drawing.

On Wed, Nov 2, 2011 at 1:17 PM, Eugene Kirpichov <ekirpichov at gmail.com>wrote:

> Hello,
>
> I've got two very simple programs that draw a very simple picture using
> cairo, doing a couple hundred thousand of cairo calls.
> One program is in C++. The other is in Haskell and uses the cairo library
> bindings.
>
> The C++ program completes in a fraction of a second, the Haskell program
> takes about 7-8 seconds to run. They produce exactly the same output.
>
> What could be at fault here? Why are the cairo bindings working so slow?
> (I suppose there isn't too much cairo-specific stuff here, perhaps it's a
> general FFI question?)
>
> #include "cairo.h"
> int main() {
>    cairo_surface_t *surface =
> cairo_image_surface_create(CAIRO_FORMAT_ARGB32, 1024, 768);
>    cairo_t *cr = cairo_create(surface);
>    cairo_set_source_rgb(cr, 0, 255, 0);
>    for(int x = 0; x < 1024; x += 2) for(int y = 0; y < 768; y += 2) {
>        cairo_rectangle(cr, x, y, 1, 1);
>        cairo_fill(cr);
>    }
>    cairo_surface_write_to_png(surface, "picture.png");
>    return 0;
> }
>
> module Main where
>
> import qualified Graphics.Rendering.Cairo as C
> import Control.Monad
>
> main = C.withImageSurface C.FormatARGB32 1024 768 $ \s -> do
>  C.renderWith s $ do
>    C.setSourceRGBA 0 255 0 255
>    forM_ [0,2..1024] $ \x -> do
>      forM_ [0,2..768] $ \y -> do
>        C.rectangle x y 1 1
>        C.fill
>  C.surfaceWriteToPNG s "picture.png"
>
> --
> Eugene Kirpichov
> Principal Engineer, Mirantis Inc. http://www.mirantis.com/
> Editor, http://fprog.ru/
>
>


-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111102/a5171f39/attachment.htm>


More information about the Haskell-Cafe mailing list