[Haskell-beginners] The cost of generality, or how expensive is realToFrac?

Greg greglists at me.com
Sat Sep 18 20:41:36 EDT 2010


> It would be interesting to see what core GHC produces for that (you can get 
> the core with the `-ddump-simpl' command line flag [redirect stdout to a 
> file] or with the ghc-core tool [available on hackage]).
> If it runs as fast as realToFrac :: Double -> Float (with optimisations), 
> GHC must have rewritten realToFrac to double2Float# and it should only do 
> that if there are rewrite rules for GLclampf.

I'm not sure if you literally meant you wanted to see the output or not, but I've attached a zip of the dump files and my simple source file.  The dump file naming is cryptic, but the first letters refer to the definition of 'convert' where:

fTF:   use the floatToFloat function in the source file
rTF:   use the standard realToFrac 
fRtR: use (fromRational . toRational)

The next three characters indicate the type signature of convert:

d2f: Double -> Float
d2g: Double -> GL.GLclampf

I'd summarize the results, but apparently I took the blue pill and can't make heads or tails of what I'm seeing in the dump format...

> In that case, the problem is probably that GHC doesn't see the realToFrac 
> applications because they're too deeply wrapped in your coordToCoord2D 
> calls.

> If that is the problem, it might help to use {-# INLINE #-} pragmas on 
> coordToCoord2D, fromCartesian2D and toCartesian2D.
> Can you try with realToFrac and the {-# INLINE #-} pragmas?

I tried inlining the functions you suggest with little effect.  The realToFrac version (in this case I just set floatToFloat=realToFrac to save the search and replace effort) is just too heavily loaded to see any difference at all (98+% of CPU is spent in realToFrac).  The same inlining using my definition of floatToFloat gave me a 10% improvement from 50% -> 46% of the CPU spent in floatToFloat and an inverse change in allocation to match.

Best I can tell, the inlining is being recognized, but just not changing much.

>> 
>> And still ran faster than floatToFloat.  However there's no denying that
>> floatToFloat runs *much* faster than realToFrac in the larger
>> application.  Profiling shows floatToFloat taking about 50% of my CPU
> 
> That's too much for my liking, a simple conversion from Double to Float 
> shouldn't take long, even if the Float is wrapped in newtypes (after all, 
> the newtypes don't exist at runtime).

Agreed.  The rest of the application right now isn't doing a lot of work yet though-- I'm generating (pre-calculating, if Haskell is doing it's job) a list of 360*180 points on a sphere and dumping that to OpenGL which should be doing most of the dirty work in hardware.  I'm not entirely sure why floatToFloat recalculates every iteration and isn't just cached, but I'm guessing it's because the floatToFloat is being done in an OpenGL callback within the IO monad.  Eventually I'll be providing time-varying data anyway, so the conversions will have to be continuously recalculated in the end.  

That comes out to 65000 conversions every 30ms, or about 2 million conversions a second.  I'd probably just leave it at that except, as you've demonstrated, there is at least a factor of 3 or 4 to be gained somehow-- realToFrac can provide it under the right conditions.

>> {-# RULES
>> "floatToFloat/id" floatToFloat=id
>> "floatToFloat x2" floatToFloat . floatToFloat = floatToFloat
>>  #-}
>> 
>> Neither of which seems to fires in this application,
> 
> GHC reports fired rules with -ddump-simpl-stats.
> Getting rules to fire is a little brittle, GHC does not try too hard to 
> match expressions with rules, and if several rules match, it chooses one 
> arbitrarily, so your rules may have been missed because the actual code 
> looked different (perhaps because other rewrite rules fired first).

Yeah, I've been looking at the -ddump-simp-stats output.  If I'm reading the documentation right, rules are enabled simply by invoking ghc with -O or -O2, right?  I'm now not convinced any of my rewrite rules are firing-- or at least I can't seem to get them to again.

>> I get a compile time error that I can't make sense of.  It's asking me
>> to put a context on my rule, but I can't find any references on how to
>> do that...
>> 
>> -----------
>> 
>>     Could not deduce (Num a)
>>       from the context (Coord2D (Vertex2 a), Coord2D (a, a))
>>       arising from a use of `pair2vertex'
>>                    at GCB/OpenGL/Geometry.hs:32:40-50
>>     Possible fix:
>>       add (Num a) to the context of the RULE "coordToCoord2D/p2v2"
>>     In the expression: pair2vertex
>>     When checking the transformation rule "coordToCoord2D/p2v2"
> 
> Yes, there's a Num constraint on pair2vertex, but not on coordToCoord2D, so 
> it's not type correct.
> You could try removing the Num constraint from pair2vertex or add the 
> constraint to the rule,
> 
> {-# RULES
> "coordToCoord2D/p2v2" forall a. Num a =>  (coordToCoord2D :: (a,a) -> 
> GL.Vertex2 a) = pair2vertex
>   #-}
> 
> (well, I don't know whether that's the correct way, but you can try).

No, that doesn't do it.  I tried a few variations on that and it always chokes on the => symbol or whatever other syntax I try to use.  The Num constraint was added because it was needed on related functions (3 element vertices where the z was stuffed with 0, for example), so I got rid of those and the Num constraint.  Doesn't matter, the rule still doesn't fire...  =(

Cheers--
 Greg


-------------- next part --------------
A non-text attachment was scrubbed...
Name: TypeConversions.zip
Type: application/zip
Size: 8904 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/beginners/attachments/20100918/ad811812/TypeConversions-0001.zip


More information about the Beginners mailing list