[GHC] #8336: Sinking pass does not
GHC
ghc-devs at haskell.org
Fri Sep 20 13:43:59 CEST 2013
#8336: Sinking pass does not
------------------------------+--------------------------------------------
Reporter: jstolarek | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Runtime performance bug
Unknown/Multiple | Test Case:
Difficulty: Unknown | Blocking:
Blocked By: |
Related Tickets: |
------------------------------+--------------------------------------------
Compiling this program:
{{{
{-# LANGUAGE BangPatterns, MagicHash, CPP #-}
{-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
module HashStr where
import Foreign.C
import GHC.Exts
import Data.Word
#define hASH_TBL_SIZE 4091
hashStr :: Ptr Word8 -> Int -> Int
-- use the Addr to produce a hash value between 0 & m (inclusive)
hashStr (Ptr a#) (I# len#) = loop 0# 0#
where
loop h n | n GHC.Exts.==# len# = I# h
| otherwise = loop h2 (n GHC.Exts.+# 1#)
where !c = ord# (indexCharOffAddr# a# n)
!h2 = (c GHC.Exts.+# (h GHC.Exts.*# 128#)) `remInt#`
hASH_TBL_SIZE#
}}}
produces following Cmm code for `hashStr` function:
{{{
{offset
cut:
goto cux;
cux:
_stC::I64 = R3;
_stB::I64 = R2;
_stF::I64 = 0;
_stE::I64 = 0;
goto stD;
stD:
if (_stF::I64 == _stC::I64) goto cuH; else goto cuI;
cuH:
R1 = _stE::I64;
call (P64[Sp])(R1) args: 8, res: 0, upd: 8;
cuI:
_stM::I64 = %MO_S_Rem_W64(%MO_UU_Conv_W8_W64(I8[_stB::I64 +
_stF::I64]) + (_stE::I64 << 7),
4091);
_stF::I64 = _stF::I64 + 1;
_stE::I64 = _stM::I64;
goto stD;
}
}}}
The problem here is that three last assignments:
{{{
_stM::I64 = %MO_S_Rem_W64(%MO_UU_Conv_W8_W64(I8[_stB::I64 + _stF::I64]) +
(_stE::I64 << 7), 4091);
_stF::I64 = _stF::I64 + 1;
_stE::I64 = _stM::I64;
}}}
could be optimized as:
{{{
_stE::I64 = %MO_S_Rem_W64(%MO_UU_Conv_W8_W64(I8[_stB::I64 + _stF::I64]) +
(_stE::I64 << 7), 4091);
_stF::I64 = _stF::I64 + 1;
}}}
We should improve sinking pass so that it can optimize such cases. See
Note [dependent assignments] in CmmSink.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8336>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list