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

Eugene Kirpichov ekirpichov at gmail.com
Wed Nov 2 12:19:28 CET 2011


Sorry for re-sending, my previous attempt got ignored by gtk2hs-devel
mailing list as I wasn't subscribed. Now I am.

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

> Yay!!!
>
> I made a small change in Types.chs and got my original cairo-binding-based
> program to be just as blazing fast. The only problem I have with this is
> that I used multiparameter type classes.
>
> Dear gtk2hs team! Is it possible to incorporate my changes? I'm pretty
> sure people will be happy by an order-of-magnitude speedup. Probably the
> stuff could be wrapped in #define's for those who aren't using GHC and
> can't use multiparameter type classes?
>
> I am pretty sure I could have done the same with rewrite rules, but I
> tried for a while and to no avail.
>
> FAILED SOLUTION: rewrite rules
> cFloatConv :: (RealFloat a, RealFloat b) => a -> b
> cFloatConv  = realToFrac
> {-# NOINLINE cFloatConv #-}
> {-# RULES "cFloatConv/float2Double" cFloatConv = float2Double #-}
> {-# RULES "cFloatConv/double2Float" cFloatConv = double2Float #-}
> {-# RULES "cFloatConv/self"         cFloatConv = id           #-}
>
> For some reason, the rules don't fire. Anyone got an idea why?
>
> SUCCEEDED SOLUTION: multiparameter type classes
>
> I rewrote cFloatConv like this:
>
> import GHC.Float
> class (RealFloat a, RealFloat b) => CFloatConv a b where
>   cFloatConv :: a -> b
>   cFloatConv = realToFrac
>
> instance CFloatConv Double Double where cFloatConv = id
> instance CFloatConv Double CDouble
> instance CFloatConv CDouble Double
> instance CFloatConv Float Float where cFloatConv = id
> instance CFloatConv Float Double where cFloatConv = float2Double
> instance CFloatConv Double Float where cFloatConv = double2Float
>
> and replaced a couple of constraints in functions below by usage of
> CFloatConv.
>
>
> On Wed, Nov 2, 2011 at 2:25 PM, Felipe Almeida Lessa <
> felipe.lessa at gmail.com> wrote:
>
>> +gtk2hs-devel
>>
>> On Wed, Nov 2, 2011 at 8:15 AM, Eugene Kirpichov <ekirpichov at gmail.com>
>> wrote:
>> > Any idea how to debug why all the GMP calls?
>> > I'm looking at even the auto-generated source for cairo bindings, but I
>> > don't see anything at all that could lead to *thousands* of them.
>>
>> Found them.  Look at the Types module and you'll see
>>
>>  cFloatConv :: (RealFloat a, RealFloat b) => a -> b
>>  cFloatConv  = realToFrac
>>
>> This function (or its cousins peekFloatConv, withFloatConv...) are
>> used *everywhere*.
>>
>> Looking at this module with ghc-core we see that GHC compiled a
>> generic version of cFloatConv:
>>
>> Graphics.Rendering.Cairo.Types.$wcFloatConv
>>  :: forall a_a3TN b_a3TO.
>>     (RealFloat a_a3TN, RealFrac b_a3TO) =>
>>     a_a3TN -> b_a3TO
>> [GblId,
>>  Arity=3,
>>
>>  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=3, Value=True,
>>         ConLike=True, Cheap=True, Expandable=True,
>>         Guidance=IF_ARGS [3 3 0] 12 0}]
>> Graphics.Rendering.Cairo.Types.$wcFloatConv =
>>  \ (@ a_a3TN)
>>    (@ b_a3TO)
>>    (w_s5zg :: RealFloat a_a3TN)
>>    (ww_s5zj :: RealFrac b_a3TO)
>>    (w1_s5zA :: a_a3TN) ->
>>    fromRational
>>      @ b_a3TO
>>      ($p2RealFrac @ b_a3TO ww_s5zj)
>>      (toRational
>>         @ a_a3TN
>>         ($p1RealFrac
>>            @ a_a3TN ($p1RealFloat @ a_a3TN w_s5zg))
>>         w1_s5zA)
>>
>> Note that this is basically cFloatConv = fromRational . toRational.
>>
>> *However*, GHC also compiled a Double -> Double specialization:
>>
>> Graphics.Rendering.Cairo.Types.cFloatConv1
>>  :: Double -> Double
>> [GblId,
>>  Arity=1,
>>
>>  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
>>         ConLike=True, Cheap=True, Expandable=True,
>>         Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
>>         Tmpl= \ (eta_B1 [Occ=Once!] :: Double) ->
>>                 case eta_B1 of _ { D# ww_a5v3 [Occ=Once] ->
>>                 case $w$ctoRational ww_a5v3
>>                 of _ { (# ww2_a5v8 [Occ=Once], ww3_a5v9 [Occ=Once] #) ->
>>                 $wfromRat ww2_a5v8 ww3_a5v9
>>                 }
>>                 }}]
>> Graphics.Rendering.Cairo.Types.cFloatConv1 =
>>  \ (eta_B1 :: Double) ->
>>    case eta_B1 of _ { D# ww_a5v3 ->
>>    case $w$ctoRational ww_a5v3
>>    of _ { (# ww2_a5v8, ww3_a5v9 #) ->
>>    $wfromRat ww2_a5v8 ww3_a5v9
>>    }
>>    }
>>
>> ...which is also equivalent to fromRational . toRational however with
>> the type class inlined!  Oh, god...
>>
>> Cheers,
>>
>> --
>> Felipe.
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> 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/fff65dc8/attachment.htm>


More information about the Haskell-Cafe mailing list