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

Eugene Kirpichov ekirpichov at gmail.com
Wed Nov 2 11:10:38 CET 2011


+gtk2hs-users

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

> Oh. This is pretty crazy, I wonder what they're doing with GMP so much...
>
> I modified the Haskell program to use cairo directly, even with safe
> calls, and it now takes the same time as the C program.
>
> {-# LANGUAGE ForeignFunctionInterface #-}
> module Main where
>
> import qualified Graphics.Rendering.Cairo as C
> import Control.Monad
> import Foreign
> import Foreign.C.Types
> import Foreign.C.String
>
> foreign import ccall "cairo.h cairo_image_surface_create"
> cairo_image_surface_create :: CInt -> CInt -> CInt -> IO (Ptr ())
> foreign import ccall "cairo.h cairo_create" cairo_create :: Ptr () -> IO
> (Ptr ())
> foreign import ccall "cairo.h cairo_set_source_rgb" cairo_set_source_rgb
> :: Ptr () -> CDouble -> CDouble -> CDouble -> IO ()
> foreign import ccall "cairo.h cairo_rectangle" cairo_rectangle :: Ptr ()
> -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
> foreign import ccall "cairo.h cairo_fill" cairo_fill :: Ptr () -> IO ()
> foreign import ccall "cairo.h cairo_surface_write_to_png"
> cairo_surface_write_to_png :: Ptr () -> CString -> IO ()
>
> main = do
>   s <- cairo_image_surface_create 0 1024 768
>   cr <- cairo_create s
>   cairo_set_source_rgb cr 0 255 0
>   forM_ [0,2..1024] $ \x -> do
>     forM_ [0,2..768] $ \y -> do
>       cairo_rectangle cr x y 1 1
>       cairo_fill cr
>   pic <- newCString "picture.png"
>   cairo_surface_write_to_png s pic
>
> On Wed, Nov 2, 2011 at 1:58 PM, Vincent Hanquez <tab at snarc.org> wrote:
>
>> On 11/02/2011 09:51 AM, Eugene Kirpichov wrote:
>>
>>> Hi Claude,
>>>
>>> I suspected that the issue could be about unsafe foreign imports - all
>>> imports in the cairo bindings are "safe".
>>> I compiled myself a version of cairo bindings with the "rectangle" and
>>> "fill" functions marked as unsafe.
>>>
>>> Unfortunately that didn't help the case at all, even though the core
>>> changed FFI calls from "__pkg_ccall_GC" to "__pkg_ccall". The performance
>>> stayed the same; the overhead is elsewhere.
>>>
>>>  doing a ltrace, i think the reason is pretty obvious, there's a lot of
>> GMP calls:
>>
>> __gmpz_init(0x7f5043171730, 1, 0x7f5043171750, 0x7f5043171740,
>> 0x7f50431d2508) = 0x7f50431d2530
>> __gmpz_mul(0x7f5043171730, 0x7f5043171750, 0x7f5043171740,
>> 0x7f50431d2538, 0x7f50431d2508) = 1
>> __gmpz_init(0x7f5043171728, 1, 0x7f5043171748, 0x7f5043171738,
>> 0x7f50431d2538) = 0x7f50431d2568
>> __gmpz_mul(0x7f5043171728, 0x7f5043171748, 0x7f5043171738,
>> 0x7f50431d2570, 0x7f50431d2538) = 1
>> __gmpn_gcd_1(0x7f50431d2580, 1, 1, 1, 1)     = 1
>> <repeated thousand of time>
>>
>> before each call cairo calls.
>>
>> just to make sure, the C version doesn't exhibit this behavior.
>>
>> --
>> Vincent
>>
>>
>> ______________________________**_________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe>
>>
>
>
>
> --
> 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/1393ee2e/attachment.htm>


More information about the Haskell-Cafe mailing list