[Haskell] Expecting more inlining for bit shifting

Samuel Bronson naesten at gmail.com
Wed Oct 11 13:04:04 EDT 2006


Simon Peyton-Jones <simonpj <at> microsoft.com> writes:

> 
> | So, my hypothesis is that the inliner doesn't recognise that
> | ``if (x >= 0) then ...'' is effectively a case analysis on x, and thus
> the
> | argument discount is not fired.  So we need to figure out how to
> extend
> | this criterion for when to apply the argument discount.
> 
> Correct.  GHC generates
> 	case (x# >=# 0#) of { True -> ...; False -> ... }
> But the argument discount only applies when we have
> 	case y of { ... }
> 
> So you really want a discount for the args of a primop.
> 
> The relevant file is coreSyn/CoreUnfold.lhs, and the function is
> calcUnfoldingGuidance.

Actually it is sizeExpr. (Even so, apparantly I've been figuring this out the
hard way...)

The brach that currently handles these is the

    size_up (Case e _ _ alts) = nukeScrutDiscount (size_up e) `addSize` 
			         foldr (addSize . size_up_alt) sizeZero alts

branch. I've got a patch that seems like it ought to do a bettter job, but it
doesn't seem to give the $wrotate functions any discount (the $wshift functions
having been tagged by the {-# INLINE shift #-} pragmas I added all over).
Unfortunately I left it at home and I'm at school right now :-(.
It does get run sometimes, but I'm not sure if it is run for rotate or that its
results are kept...

> 
> I see some notes there with primops, namely:
> 
> 	  PrimOpId op  -> primOpSize op (valArgCount args)
> 			  -- foldr addSize (primOpSize op) (map
> arg_discount args)
> 			  -- At one time I tried giving an arg-discount
> if a primop 
> 			  -- is applied to one of the function's
> arguments, but it's
> 			  -- not good.  At the moment, any unlifted-type
> arg gets a
> 			  -- 'True' for 'yes I'm evald', so we collect
> the discount even
> 			  -- if we know nothing about it.  And just
> having it in a primop
> 			  -- doesn't help at all if we don't know
> something more.
> 
> At the call site, the call
> 	f x y
> gets f's arg-discount for x if x is evaluated.  But in the case of
> primitive types we don't just want "evaluated", we want to know the
> value.  So one could refine that.  The relevant function is
> interestingArg in simplCore/SimplUtils.

I might point out that the current code would throw out those discounts (the
nukeSrutDiscounts in that case).

> 
> | (This whole idea of argument discounting seems rather ad hoc.  Is it
> not
> | possible try out an inline, and remove it if in the end it doesn't get
> | reduced in size sufficently?)
> 
> Yes, you could try that too.  It might result in a lot of wasted work,
> but it'd be a reasonable thing to try.  The relevant code is in
> simplCore/Simplify.lhs
> 
> Simon
> 






More information about the Glasgow-haskell-users mailing list