On February 18, 2009 12:42:02 Tyson Whitehead wrote:
> On February 18, 2009 04:29:42 Max Bolingbroke wrote:
> > Yes - GHC wants to share the work of (maxBound-x)`div`10 between
> > several partial applications of "digit". This is usually a good idea,
> > but in this case it sucks because it's resulted in a massively
> > increased arity. IMHO GHC should fix this by:
> > * Marking divInt# INLINE in the base library. This would result in
> > your code would just containing uses of quotInt#
> > * Making some operations cheap even if they may fail
> > (PrimOp.primpOpIsCheap should change). Though this might mean that we
> > turn non-terminating programs into terminating ones (such operations
> > get pushed inside lambdas) but this is consistent with our treatment
> > of lambdas generally.
>
> I am guess this is because quot maps directly onto the x86 idiv instruction
> due to both of them truncating towards zero, while div, with its truncation
> towards negative infinity, does not.  Running with -ddump-asm seems to back
> this up as quotInt# compiles down to an idiv instruction and divInt# to a
> call through base_GHCziBase_divIntzh_info.  Unfortunately for me, I always
> seem to instinctively go with div and mod ahead of quot and rem.

I see what you mean about div as it is defined through divMod which is in turn 
defined through quotRem in Prelude.

n `div` d =  q  where (q,_) = divMod n d
divMod n d =  if signum r == negate (signum d) then (q-1, r+d) else qr
    where qr@(q,r) = quotRem n d

However, GHC almost seems to be doing its own thing as, as I mentioned above, 
it turns it into a divInt# (which is not in GHC.Prim) in the tidy core, which 
then turns into a call through base_GHCziBase_divIntzh_info in the assembler.

(note that I'm just looking at the source from the haskell.org libraries link)

Cheers!  -Tyson

Attachment: signature.asc
Description: This is a digitally signed message part.

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to