<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN">
<html>
  <head>

    <meta http-equiv="content-type" content="text/html; charset=ISO-8859-1">
  </head>
  <body text="#000000" bgcolor="#ffffff">
    Hi,<br>
    <br>
    While trying to figure out why some of my code is very slow I have
    found that it is something related to division.<br>
    Digging a bit deeper I found an example which shows some unexpected
    magic and a lack of the expected one.<br>
    Before raising any tickets in trac I would like to consult with you
    regarding what I see. Maybe I am misunderstanding the way GHC is
    supposed to work.<br>
    <br>
    -------------------<br>
    <blockquote>module Test where<br>
      <br>
      import Data.Int<br>
      import GHC.Exts<br>
      import GHC.Prim<br>
      <br>
      foo :: Int -&gt; Int<br>
      foo a =<br>
      &nbsp; let<br>
      &nbsp;&nbsp;&nbsp; b = a `quot` 1111<br>
      &nbsp;&nbsp;&nbsp; c = b `quot` 1113<br>
      &nbsp;&nbsp;&nbsp; d = c `quot` 1117<br>
      &nbsp; in d<br>
      <br>
      bar :: Int -&gt; Int<br>
      bar !a' =<br>
      &nbsp; let<br>
      &nbsp;&nbsp;&nbsp; !(I# a) = a'<br>
      &nbsp;&nbsp;&nbsp; !(b) = quotInt# a 1111#<br>
      &nbsp;&nbsp;&nbsp; !(c) = quotInt# b 1113#<br>
      &nbsp;&nbsp;&nbsp; !(d) = quotInt# c 1117#<br>
      &nbsp; in I# d<br>
    </blockquote>
    -------------------<br>
    <br>
    Here 'foo' is a function written in a common way and 'bar' is
    essentially identical one, written in a low-level style.<br>
    * My understanding is that these functions are equivalent in terms
    of what they do. The only difference is in the code being generated.<br>
    <br>
    Unexpected magic is in the Core dump:<br>
    -------------------<br>
    <blockquote>Test.$wfoo =<br>
      &nbsp; \ (ww_sxw :: GHC.Prim.Int#) -&gt;<br>
      &nbsp;&nbsp;&nbsp; case ww_sxw of wild1_ax0 {<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp; __DEFAULT -&gt;<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; case GHC.Prim.quotInt# wild1_ax0 1111 of wild2_Xxc {<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; __DEFAULT -&gt;<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; case GHC.Prim.quotInt# wild2_Xxc 1113 of wild3_Xxt {<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; __DEFAULT -&gt; GHC.Prim.quotInt# wild3_Xxt 1117;<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (-9223372036854775808) -&gt; (-8257271295304186)<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; };<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (-9223372036854775808) -&gt; (-7418931981405)<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; };<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (-9223372036854775808) -&gt; (-6677706553)<br>
      &nbsp;&nbsp;&nbsp; }<br>
      <br>
      Test.bar =<br>
      &nbsp; \ (a'_ah5 :: GHC.Types.Int) -&gt;<br>
      &nbsp;&nbsp;&nbsp; case a'_ah5 of _ { GHC.Types.I# ipv_ste -&gt;<br>
      &nbsp;&nbsp;&nbsp; GHC.Types.I#<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (GHC.Prim.quotInt#<br>
      &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; (GHC.Prim.quotInt# (GHC.Prim.quotInt# ipv_ste 1111) 1113)
      1117)<br>
      &nbsp;&nbsp;&nbsp; }<br>
    </blockquote>
    -------------------<br>
    Question 1: what is the meaning of those magic numbers
    -9223372036854775808, -6677706553, -7418931981405,
    -8257271295304186?<br>
    Question 2: under which circumstances those strange branches of
    execution will be used and what those results would mean?<br>
    Question 3: why is the Core for 'foo' so different to 'bar'?<br>
    <br>
    The lack of expected magic is in the assembler code:<br>
    -------------------<br>
    <blockquote>&nbsp;&nbsp;&nbsp; addq $16,%r12<br>
      &nbsp;&nbsp;&nbsp; cmpq 144(%r13),%r12<br>
      &nbsp;&nbsp;&nbsp; ja .Lcz1<br>
      &nbsp;&nbsp;&nbsp; movl $1117,%ecx<br>
      &nbsp;&nbsp;&nbsp; movl $1113,%r10d<br>
      &nbsp;&nbsp;&nbsp; movl $1111,%r11d<br>
      &nbsp;&nbsp;&nbsp; movq 7(%rbx),%rax<br>
      &nbsp;&nbsp;&nbsp; cqto<br>
      &nbsp;&nbsp;&nbsp; idivq %r11<br>
      &nbsp;&nbsp;&nbsp; cqto<br>
      &nbsp;&nbsp;&nbsp; idivq %r10<br>
      &nbsp;&nbsp;&nbsp; cqto<br>
      &nbsp;&nbsp;&nbsp; idivq %rcx<br>
      &nbsp;&nbsp;&nbsp; movq $ghczmprim_GHCziTypes_Izh_con_info,-8(%r12)<br>
      &nbsp;&nbsp;&nbsp; movq %rax,0(%r12)<br>
      &nbsp;&nbsp;&nbsp; leaq -7(%r12),%rbx<br>
      &nbsp;&nbsp;&nbsp; addq $8,%rbp<br>
      &nbsp;&nbsp;&nbsp; jmp *0(%rbp)<br>
    </blockquote>
    -------------------<br>
    Question: can't it use cheap multiplication and shift instead of
    expensive division here? I know that such optimisation is
    implemented at least to some extent for C--. I suppose it also won't
    do anything smart for expressions like a*4 or a/4 for the same
    reason.<br>
    <br>
    <br>
    With kind regards,<br>
    Denys Rtveliashvili
  </body>
</html>