[GHC] #14226: Common Block Elimination pass doesn't eliminate common blocks

GHC ghc-devs at haskell.org
Wed Sep 13 18:54:36 UTC 2017


#14226: Common Block Elimination pass doesn't eliminate common blocks
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.4.1
       Component:  Compiler          |              Version:  8.2.1
  (CodeGen)                          |
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Old description:

> In #14222 it was noted that something appears to be broken in
> `CmmCommonBlockElim`. Consider the program from that ticket,
> {{{#!hs
> module T14221 where
>
> import Data.Text as T
>
> isNumeric :: Text -> Bool
> isNumeric t =
>     T.all isNumeric' t && T.any isNumber t
>   where
>     isNumber c = '0' <= c && c <= '9'
>     isNumeric' c = isNumber c
>                 || c == 'e'
>                 || c == 'E'
>                 || c == '.'
>                 || c == '-'
>                 || c == '+'
> }}}
> This program produces six copies of a block of the form,
> {{{#!c
>       c6JT:
>           R2 = I64[R1 + 7];
>           R1 = P64[Sp + 8];
>           Sp = Sp + 16;
>           call $wloop_all_s6CQ_info(R2, R1) args: 8, res: 0, upd: 8;
> }}}
> in the `-ddump-opt-cmm` output, which are manifest in the assembler as,
> {{{#!asm
> block_c6JT_info:
> _c6JT:
>         movq 7(%rbx),%r14
>         movq 8(%rbp),%rbx
>         addq $16,%rbp
>         jmp $wloop_all_s6CQ_info
> }}}
>
> CBE really ought to be catching these.

New description:

 In #14222 it was noted that something appears to be broken in
 `CmmCommonBlockElim`. Consider the program from that ticket,
 {{{#!hs
 module T14221 where

 import Data.Text as T

 isNumeric :: Text -> Bool
 isNumeric t =
     T.all isNumeric' t && T.any isNumber t
   where
     isNumber c = '0' <= c && c <= '9'
     isNumeric' c = isNumber c
                 || c == 'e'
                 || c == 'E'
                 || c == '.'
                 || c == '-'
                 || c == '+'
 }}}
 This program produces six copies of a block of the form,
 {{{
       c6JT:
           R2 = I64[R1 + 7];
           R1 = P64[Sp + 8];
           Sp = Sp + 16;
           call $wloop_all_s6CQ_info(R2, R1) args: 8, res: 0, upd: 8;
 }}}
 in the `-ddump-opt-cmm` output, which are manifest in the assembler as,
 {{{#!asm
 block_c6JT_info:
 _c6JT:
         movq 7(%rbx),%r14
         movq 8(%rbp),%rbx
         addq $16,%rbp
         jmp $wloop_all_s6CQ_info
 }}}

 CBE really ought to be catching these.

--

Comment (by bgamari):

 I had a quick look at this; it turns out that the reason that CBE doesn't
 work is 73f836f5d57a3106029b573c42f83d2039d21d89, which modifies the hash
 function to include local registers. This may sound familiar to you,
 nomeata, as you wrote it to address #10397.

 Sadly this means that our ability to CBE is quite limited. It seems like
 we should likely revisit this decision.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14226#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list