[GHC] #7814: panic in PPC NCG

GHC cvs-ghc at haskell.org
Fri Apr 5 23:42:13 CEST 2013


#7814: panic in PPC NCG
--------------------------------+-------------------------------------------
Reporter:  heisenbug            |          Owner:          
    Type:  bug                  |         Status:  new     
Priority:  normal               |      Component:  Compiler
 Version:  7.7                  |       Keywords:          
      Os:  Unknown/Multiple     |   Architecture:  powerpc 
 Failure:  Building GHC failed  |      Blockedby:          
Blocking:                       |        Related:          
--------------------------------+-------------------------------------------

Comment(by heisenbug):

 {{{
 ==================== Liveness annotations added ====================
 stg_sel_0_upd_entry() //  [R1]
         { [(cb,
             stg_sel_0_upd_info:
                 const 0;
                 const 1507328;),
            (ce,
             block_ce_info:
                 const 0;
                 const 2097152;)]
           # firstId          = Just cb
           # liveVRegsOnEntry = Just [(cb, []), (ce, [(nv, %vI_nv)]),
                                      (cj, [(cc, %vI_cc)]), (cl, [(cc,
 %vI_cc), (nv, %vI_nv)]),
                                      (cn, [(cf, %vI_cf), (nv, %vI_nv)]),
                                      (co, [(cf, %vI_cf), (nv, %vI_nv)])]
           # liveSlotsOnEntry = fromList []
         }
     [NONREC
         cb:     bcl     20,31,1f
             1:  mflr    %vI_nv
                     # born:    %vI_nv

                 lwz     %vI_nG, _nF-(1b)(%vI_nv)
                     # born:    %vI_nG

                 add     %vI_nv, %vI_nv, %vI_nG
                     # r_dying: %vI_nG

                 mr      %vI_cc, 14
                     # born:    %vI_cc

                 addi    %vI_ns, 22, -12
                     # born:    %vI_ns

                 cmplw   %vI_ns, 24
                     # r_dying: %vI_ns

                 blt     _cj

                 b       _cl  # r_dying: %vI_cc %vI_nv
                      ,
      NONREC
         ce:     addi    22, 22, 12

                 mr      %vI_cf, 14
                     # born:    %vI_cf

                 b       _co  # r_dying: %vI_cf %vI_nv
                      ,
      NONREC
         cj:     mr      14, %vI_cc
                     # r_dying: %vI_cc

                 lwz     %vI_nt, -12(27)
                     # born:    %vI_nt

                 mtctr   %vI_nt
                     # r_dying: %vI_nt

                 bctr    ,
      NONREC
         cl:     addis   %vI_nu, %vI_nv,
 .LC_stg_upd_frame_info-(.LCTOC1)+0 at ha
                     # born:    %vI_nu

                 lwz     %vI_nw,
 .LC_stg_upd_frame_info-(.LCTOC1)+0 at l(%vI_nu)
                     # born:    %vI_nw
                     # r_dying: %vI_nu

                 stw     %vI_nw, -8(22)
                     # r_dying: %vI_nw

                 stw     %vI_cc, -4(22)

                 lwz     %vI_cf, 8(%vI_cc)
                     # born:    %vI_cf
                     # r_dying: %vI_cc

                 andi.   %vI_nx, %vI_cf, 3
                     # born:    %vI_nx

                 cmpwi   %vI_nx, 0
                     # r_dying: %vI_nx

                 bne     _co

                 b       _cn  # r_dying: %vI_cf %vI_nv
                      ,
      NONREC
         cn:     addis   %vI_ny, %vI_nv, .LC_block_ce_info-(.LCTOC1)+0 at ha
                     # born:    %vI_ny
                     # r_dying: %vI_nv

                 lwz     %vI_nz, .LC_block_ce_info-(.LCTOC1)+0 at l(%vI_ny)
                     # born:    %vI_nz
                     # r_dying: %vI_ny

                 stw     %vI_nz, -12(22)
                     # r_dying: %vI_nz

                 mr      14, %vI_cf

                 addi    22, 22, -12

                 lwz     %vI_nA, 0(%vI_cf)
                     # born:    %vI_nA
                     # r_dying: %vI_cf

                 mtctr   %vI_nA
                     # r_dying: %vI_nA

                 bctr    ,
      NONREC
         co:     li      %vI_nB, -4
                     # born:    %vI_nB

                 and     %vI_nC, %vI_cf, %vI_nB
                     # born:    %vI_nC
                     # r_dying: %vI_cf %vI_nB

                 lwz     14, 4(%vI_nC)
                     # r_dying: %vI_nC

                 addi    22, 22, -8

                 addis   %vI_nD, %vI_nv, .LC_stg_ap_0_fast-(.LCTOC1)+0 at ha
                     # born:    %vI_nD
                     # r_dying: %vI_nv

                 lwz     %vI_nE, .LC_stg_ap_0_fast-(.LCTOC1)+0 at l(%vI_nD)
                     # born:    %vI_nE
                     # r_dying: %vI_nD

                 mtctr   %vI_nE
                     # r_dying: %vI_nE

                 bctr    ]
 }
 section "text" {
     _nF:
         const .LCTOC1-1b;
 }
 }}}


 Some observations:

   1.) in 'co' %vI_nv is clearly live (used in the 'addis' instruction)
   2.) it is correctly marked live on entry: (co, [(cf, %vI_cf), (nv,
 %vI_nv)])
   3.) coming from 'ce' (by a branch 'b _co') %vI_nv is indicated as dying
 (this looks wrong)
   4.) by hacking away the panic, this gets emitted:
 {{{
 .Lco:
         li      30, -4
         and     31, 31, 30
         lwz     14, 4(31)
         addi    22, 22, -8
         addis   31, %vI_nv, .LC_stg_ap_0_fast-(.LCTOC1)+0 at ha
         lwz     31, .LC_stg_ap_0_fast-(.LCTOC1)+0 at l(31)
         mtctr   31
         bctr
 }}}

 Observe the %vI_nv survived! (This is the only occurrence).

 I guess 3.) causes 4.)

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



More information about the ghc-tickets mailing list