#1052: NCG doesn't realise shift instructions trash shifted input?
-------------------------------+--------------------------------------------
    Reporter:  igloo           |       Owner:          
        Type:  bug             |      Status:  new     
    Priority:  normal          |   Milestone:  6.8     
   Component:  Compiler (NCG)  |     Version:  6.6     
    Severity:  normal          |    Keywords:          
  Difficulty:  Unknown         |    Testcase:  arith011
Architecture:  x86_64 (amd64)  |          Os:  Linux   
-------------------------------+--------------------------------------------
It looks like the NCG on amd64/Linux doesn't realise that shifting
 instructions trash the shifted input (spotted due to arith011). With this
 input file:

 {{{
 module Main where

 import Data.Bits
 import GHC.Exts

 main = print ((2 :: Int) `qrotate` 1)

 {-# NOINLINE qrotate #-}
 (I# x#) `qrotate` (I# i#) =
     (I# (word2Int# (a# `or#` b#)), W# a#, W# b#)
     where
     x'# = int2Word# x#
     i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
     a# = x'# `uncheckedShiftL#` i'#
     b# = x'# `uncheckedShiftRL#` (wsib -# i'#)

     wsib = 64#
 }}}

 compiling with `-O -fglasgow-exts -v9` if I merge the Cmm and Asm output I
 get:

 {{{
 R2 == rsi
 R3 == rdi

 _sTh = R3;            movq %rdi,%rax  rax=_sTh
 _sTj = _sTh & 63;     andq $63,%rax   rax=_sTj
 _sTl = _sTj;          rax=_sTl
 _sTp = R2;            movq %rsi,%rcx  rcx=_sTp
                       movq %rcx,64(%rsp)
 _sTs = 64 - _sTl;     movl $64,%ecx
                       subq %rax,%rcx
                       movq 64(%rsp),%rdx
 _sTu = _sTp >> _sTs;  shrq %cl,%rdx
                       movq %rdx,%rcx     \
                       movq %rcx,72(%rsp) / why?
                       movq %rax,%rcx
 _sTx = _sTp << _sTl;  shlq %cl,%rdx   but rdx contains _sTp >> _sTs!
 I64[Hp + (-40)] = base_GHCziWord_Wzh_con_info;
 I64[Hp + (-32)] = _sTu;
 I64[Hp + (-24)] = base_GHCziWord_Wzh_con_info;
 I64[Hp + (-16)] = _sTx;
 _sTz = _sTx | _sTu;
 _sTB = _sTz;
 I64[Hp + (-8)] = base_GHCziBase_Izh_con_info;
 I64[Hp + 0] = _sTB;
 R1 = Hp + (-8);
 R2 = Hp + (-24);
 R3 = Hp + (-40);
 jump (I64[Sp + 0]);
 }}}


 Thanks
 Ian

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1052>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to