[GHC] #7814: panic in PPC NCG

#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: --------------------------------+------------------------------------------- I get panics in the NCG PPC register allocator while compiling these files: rts_dist_HC rts/dist/build/StgStdThunks.dyn_o rts_dist_HC rts/dist/build/StgStdThunks.thr_dyn_o rts_dist_HC rts/dist/build/StgStdThunks.l_dyn_o rts_dist_HC rts/dist/build/StgStdThunks.thr_l_dyn_o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/Classes.o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/CString.o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/Debug.o The panic message is like this: {{{ ghc-stage1: panic! (the 'impossible' happened) (GHC version 7.7.20130405 for powerpc-montavista-linux): allocateRegsAndSpill: Cannot read from uninitialized register %vI_nff }}} This makes the bootstapping of PPC cross compiler, ehm, delicate. There is a comment in compiler/nativeGen/RegAlloc/Linear/Main.hs:756 Nothing | reading -> pprPanic "allocateRegsAndSpill: Cannot read from uninitialized register" (ppr r) -- NOTE: if the input to the NCG contains some -- unreachable blocks with junk code, this panic -- might be triggered. Make sure you only feed -- sensible code into the NCG. In CmmPipeline we -- call removeUnreachableBlocks at the end for this -- reason. So we have a 'junk code' issue here. Any hints how I can debug this? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: --------------------------------+------------------------------------------- Changes (by heisenbug): * cc: ggreif@… (added) Comment: These are the options used: "inplace/bin/ghc-stage1" -fPIC -dynamic -optc-DTHREADED_RTS -eventlog -H64m -O0 -fasm -Iincludes -Iincludes/dist -Iincludes/dist- derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -package-name rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/StgStdThunks.cmm -o rts/dist/build/StgStdThunks.thr_l_dyn_o When I remove "-fPIC -dynamic" it compiles. Removing just one of these is not enough. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): This function alone triggers the panic: {{{ ==================== Post CPS Cmm ==================== [stg_sel_0_upd_entry() // [R1] { info_tbl: [(cc, label: stg_sel_0_upd_info rep:tag:23 HeapRep { ThunkSel 0 }), (ce, label: block_ce_info rep:StackRep [])] stack_info: arg_space: 4 updfr_space: Just 4 } {offset cc: _c1::P32 = R1; if ((Sp + -12) < SpLim) goto cj; else goto cl; cj: R1 = _c1::P32; call (stg_gc_enter_1)(R1) args: 4, res: 0, upd: 4; cl: I32[Sp - 8] = stg_upd_frame_info; P32[Sp - 4] = _c1::P32; _cf::P32 = I32[_c1::P32 + 8]; if (_cf::P32 & 3 != 0) goto co; else goto cn; cn: I32[Sp - 12] = ce; R1 = _cf::P32; Sp = Sp - 12; call (I32[_cf::P32])(R1) returns to ce, args: 4, res: 4, upd: 12; ce: Sp = Sp + 12; _cf::P32 = R1; goto co; co: R1 = I32[_cf::P32 & (-4) + 4]; Sp = Sp - 8; call stg_ap_0_fast(R1) args: 12, res: 0, upd: 12; } }] ==================== Optimised Cmm ==================== stg_sel_0_upd_entry() // [R1] { [(cb, stg_sel_0_upd_info: const 0; const 1507328;), (ce, block_ce_info: const 0; const 2097152;)] } {offset cb: _cc::P32 = R1; if ((Sp + -12) < SpLim) goto cj; else goto cl; cj: R1 = _cc::P32; call (I32[BaseReg - 12])(R1) args: 4, res: 0, upd: 4; cl: I32[Sp - 8] = I32[PicBaseReg + .LC_stg_upd_frame_info-.LCTOC1]; P32[Sp - 4] = _cc::P32; _cf::P32 = I32[_cc::P32 + 8]; if (_cf::P32 & 3 != 0) goto co; else goto cn; cn: I32[Sp - 12] = I32[PicBaseReg + .LC_block_ce_info-.LCTOC1]; R1 = _cf::P32; Sp = Sp - 12; call (I32[_cf::P32])(R1) returns to ce, args: 4, res: 4, upd: 12; ce: Sp = Sp + 12; _cf::P32 = R1; goto co; co: R1 = I32[_cf::P32 & (-4) + 4]; Sp = Sp - 8; call (I32[PicBaseReg + .LC_stg_ap_0_fast-.LCTOC1])(R1) args: 12, res: 0, upd: 12; } } }}} -ddump-asm dies not show anything -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): {{{ $ diff -u good bad --- good 2013-04-05 15:40:25.296498000 +0200 +++ bad 2013-04-05 15:40:34.172566000 +0200 @@ -15,11 +15,11 @@ if ((Sp + -12) < SpLim) goto cj; else goto cl; cj: R1 = _cc::P32; call (I32[BaseReg - 12])(R1) args: 4, res: 0, upd: 4; - cl: I32[Sp - 8] = stg_upd_frame_info; + cl: I32[Sp - 8] = I32[PicBaseReg + .LC_stg_upd_frame_info-.LCTOC1]; P32[Sp - 4] = _cc::P32; _cf::P32 = I32[_cc::P32 + 8]; if (_cf::P32 & 3 != 0) goto co; else goto cn; - cn: I32[Sp - 12] = block_ce_info; + cn: I32[Sp - 12] = I32[PicBaseReg + .LC_block_ce_info-.LCTOC1]; R1 = _cf::P32; Sp = Sp - 12; call (I32[_cf::P32])(R1) returns to ce, args: 4, res: 4, upd: 12; @@ -28,7 +28,7 @@ goto co; co: R1 = I32[_cf::P32 & (-4) + 4]; Sp = Sp - 8; - call stg_ap_0_fast(R1) args: 12, res: 0, upd: 12; + call (I32[PicBaseReg + .LC_stg_ap_0_fast-.LCTOC1])(R1) args: 12, res: 0, upd: 12; } } }}} The problem seems to be the !PicBaseReg. Above 'good' is without "-fPIC -dynamic" and 'bad' with them. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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@ha # born: %vI_nu lwz %vI_nw, .LC_stg_upd_frame_info-(.LCTOC1)+0@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@ha # born: %vI_ny # r_dying: %vI_nv lwz %vI_nz, .LC_block_ce_info-(.LCTOC1)+0@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@ha # born: %vI_nD # r_dying: %vI_nv lwz %vI_nE, .LC_stg_ap_0_fast-(.LCTOC1)+0@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@ha lwz 31, .LC_stg_ap_0_fast-(.LCTOC1)+0@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

#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): The problem is in !JoinToTargets: {{{ ==================== Registers allocated ====================joinToTargets: making fixup code in block: cl jmp instruction: bne _co src assignment: [(cf, InReg (RealRegSingle 30)), (nv, InReg (RealRegSingle 31))] dest assignment: [(cf, InReg (RealRegSingle 31))] movement graph: [(cf, InReg (RealRegSingle 30), [InReg (RealRegSingle 31)])] sccs of graph: [NONREC (cf, InReg (RealRegSingle 30), [InReg (RealRegSingle 31)])] joinToTargets: fixup code is: nI: mr 31, 30 b _co }}} Here is the entire output when I disable the panic: {{{ stg_sel_0_upd_info: .Lcb: bcl 20,31,1f 1: mflr 31 lwz 30, .LnF-(1b)(31) add 31, 31, 30 mr 30, 14 addi 29, 22, -12 cmplw 29, 24 blt .Lcj .Lcl: addis 29, 31, .LC_stg_upd_frame_info-(.LCTOC1)+0@ha lwz 29, .LC_stg_upd_frame_info-(.LCTOC1)+0@l(29) stw 29, -8(22) stw 30, -4(22) lwz 30, 8(30) andi. 29, 30, 3 cmpwi 29, 0 bne .LnI .Lcn: addis 31, 31, .LC_ce_info-(.LCTOC1)+0@ha lwz 31, .LC_ce_info-(.LCTOC1)+0@l(31) stw 31, -12(22) mr 14, 30 addi 22, 22, -12 lwz 31, 0(30) mtctr 31 bctr .text .align 2 .long 0 .long 2097152 ce_info: .Lce: addi 22, 22, 12 mr 31, 14 .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@ha lwz 31, .LC_stg_ap_0_fast-(.LCTOC1)+0@l(31) mtctr 31 bctr .Lcj: mr 14, 30 lwz 31, -12(27) mtctr 31 bctr .LnI: mr 31, 30 b .Lco }}} Apparently the fixup code is in pace (as '.LnI'), but 1. why is it needed at all? (there are two branches to '_co', from 'ce' and 'cl') 2. in 'cl' (%vI_nv => r31) and in 'ce' %vI_nv is not used but marked as live in, dying on exit 3. who calls 'ce'? appears to have block_ce_info -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Here is the CFG: {{{ ___________ / \ cc -> cl -> cn ===> ce -> co \ cj }}} Strangely on x86 with -fPIC this decomposes to 3 SCCs OTOH on PPC -fPIC only one. But this probably causes the trouble, as the 'ce' label is only invoked via a return, and needs the picBaseReg too (actually 'co' needs it). So this probably the bug. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------------+------------------------------------------- Reporter: heisenbug | Owner: heisenbug Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: Os: Unknown/Multiple | Architecture: powerpc Failure: Building GHC failed | Blockedby: Blocking: | Related: --------------------------------+------------------------------------------- Changes (by heisenbug): * owner: => heisenbug Comment: * [6:52pm] gabor: solution is this: https://github.com/ghc/ghc/blob/master/compiler/cmm/CmmPipeline.hs#L183 * [6:52pm] gabor: splitting has to happen on PPC/ELF too * [6:54pm] Igloo: Could you send a patch please, including another "The situation is the same" section for PPC/ELF (or altering the existing ong if the asm is identical) * [6:54pm] Igloo: And thanks for tracking this down! * [7:01pm] gabor: Igloo: this is my first hunch, will test. But maybe PPC/ELF has actually consistent PIC-reg, in which case we have to dig deeper. But for now I'll go this route and check stuff later * [7:02pm] gabor: with domain experts (e.g. the LLVM list) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------------+------------------------------------------- Reporter: heisenbug | Owner: heisenbug 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): Here is some background material about PPC/ELF, at first sight it appears analogous to x86/ELF: http://devpit.org/wiki/Debugging_PowerPC_ELF_Binaries#The_.got_section_on_po... -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------------+------------------------------------------- Reporter: heisenbug | Owner: heisenbug 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): Replying to [comment:4 heisenbug]: I made the same dump with Darwin/x86 (with splitting hacked out) {{{ ==================== Liveness annotations added ==================== stg_sel_0_upd_entry() // [R1] { [(cb, stg_sel_0_upd_info: const 0; const 23;), (ce, block_ce_info: const 0; const 32;)] # firstId = Just cb # liveVRegsOnEntry = Just [(cb, []), (ce, []), (cj, [(cc, %vI_cc)]), (cl, [(cc, %vI_cc), (nt, %vI_nt)]), (cn, [(cf, %vI_cf), (nt, %vI_nt)]), (co, [(cf, %vI_cf), (nt, %vI_nt)])] # liveSlotsOnEntry = fromList [] } [NONREC cb: call 1f 1: popl %vI_nt # born: %vI_nt movl %esi,%vI_cc # born: %vI_cc leal -12(%ebp),%vI_ns # born: %vI_ns cmpl 220(%ebx),%vI_ns # r_dying: %vI_ns jb _cj jmp _cl # r_dying: %vI_cc %vI_nt , NONREC ce: call 1f 1: popl %vI_nt # born: %vI_nt addl $12,%ebp movl %esi,%vI_cf # born: %vI_cf jmp _co # r_dying: %vI_cf %vI_nt , NONREC cj: movl %vI_cc,%esi # r_dying: %vI_cc jmp *-8(%ebx) , NONREC cl: movl Lstg_upd_frame_info$non_lazy_ptr-(1b)+0(%vI_nt),%vI_nu # born: %vI_nu movl %vI_nu,-8(%ebp) # r_dying: %vI_nu movl %vI_cc,-4(%ebp) movl 8(%vI_cc),%vI_cf # born: %vI_cf # r_dying: %vI_cc testl $3,%vI_cf jne _co jmp _cn # r_dying: %vI_cf %vI_nt , NONREC cn: movl %vI_nt,%vI_nw # born: %vI_nw # r_dying: %vI_nt addl $block_ce_info-(1b)+0,%vI_nw movl %vI_nw,-12(%ebp) # r_dying: %vI_nw movl %vI_cf,%esi addl $-12,%ebp jmp *(%vI_cf) # r_dying: %vI_cf , NONREC co: movl %vI_cf,%vI_ny # born: %vI_ny # r_dying: %vI_cf andl $-4,%vI_ny movl 4(%vI_ny),%esi # r_dying: %vI_ny addl $-8,%ebp jmp *Lstg_ap_0_fast$non_lazy_ptr-(1b)+0(%vI_nt) # r_dying: %vI_nt ] } }}} Notice how `liveVRegsOnEntry (ce, [])` is empty. I would expect the same thing for PPC too. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG
--------------------------------+-------------------------------------------
Reporter: heisenbug | Owner: heisenbug
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 ggreif@…):
commit 9e460664f3179c53f2f439238929b501691ddf24
{{{
Author: Gabor Greif

#7814: panic in PPC NCG --------------------------------+------------------------------------------- Reporter: heisenbug | Owner: heisenbug Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: Os: Unknown/Multiple | Architecture: powerpc Failure: Building GHC failed | Blockedby: Blocking: | Related: --------------------------------+------------------------------------------- Changes (by PHO): * cc: pho@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------------+------------------------------------------- Reporter: heisenbug | Owner: heisenbug 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): Replying to [comment:10 ggreif@…]: That patch fixes liveness: {{{ ==================== 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, []), (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 [] } ... }}} But now we get in trouble when certain object files get too large: {{{ $ "inplace/bin/ghc-stage1" -hisuf hi -osuf o -hcsuf hc -static -H64m -O0 -fasm -package-name time-1.4.0.2 -hide-all-packages -i -ilibraries/time/. -ilibraries/time/dist-install/build -ilibraries/time /dist-install/build/autogen -Ilibraries/time/dist-install/build -Ilibraries/time/dist-install/build/autogen -Ilibraries/time/include -optP-DLANGUAGE_Rank2Types -optP-DLANGUAGE_DeriveDataTypeable -optP- DLANGUAGE_StandaloneDeriving -optP-include -optPlibraries/time/dist- install/build/autogen/cabal_macros.h -package base-4.7.0.0 -package deepseq-1.3.0.2 -package old-locale-1.0.0.5 -Wall -XHaskell2010 -XRank2Types -XDeriveDataTypeable -XStandaloneDeriving -XCPP -O -fasm -no-user-package-db -rtsopts -odir libraries/time/dist-install/build -hidir libraries/time/dist-install/build -stubdir libraries/time/dist- install/build -dynamic-too -c libraries/time/./Data/Time/Format.hs -o libraries/time/dist-install/build/Data/Time/Format.o -dyno libraries/time /dist-install/build/Data/Time/Format.dyn_o /tmp/ghc3030_0/ghc3030_1.s: Assembler messages: /tmp/ghc3030_0/ghc3030_1.s:51471:0: Error: operand out of range (0x0000adf8 is not between 0xffff8000 and 0x00007fff) ... and many more like the above ... }}} The referenced label is `Lnw0w` {{{ .Lctem: bcl 20,31,1f 1: mflr 31 lwz 30, .Lnw0w-(1b)(31) }}} Maybe we can salvage the situation by placing its definition {{{ .text .align 2 .Lnw0w: .long .LCTOC1-(1b)+0 }}} further up? I.e., being more conservative with approximating label differences? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------+------------------------------------------------- Reporter: heisenbug | Owner: heisenbug Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Os: Unknown/Multiple Architecture: powerpc | Failure: Building GHC failed Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | --------------------------+------------------------------------------------- Changes (by igloo): * difficulty: => Unknown Old description:
I get panics in the NCG PPC register allocator while compiling these files:
rts_dist_HC rts/dist/build/StgStdThunks.dyn_o rts_dist_HC rts/dist/build/StgStdThunks.thr_dyn_o rts_dist_HC rts/dist/build/StgStdThunks.l_dyn_o rts_dist_HC rts/dist/build/StgStdThunks.thr_l_dyn_o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/Classes.o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/CString.o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/Debug.o
The panic message is like this: {{{ ghc-stage1: panic! (the 'impossible' happened) (GHC version 7.7.20130405 for powerpc-montavista-linux): allocateRegsAndSpill: Cannot read from uninitialized register %vI_nff
}}}
This makes the bootstapping of PPC cross compiler, ehm, delicate.
There is a comment in compiler/nativeGen/RegAlloc/Linear/Main.hs:756
Nothing | reading -> pprPanic "allocateRegsAndSpill: Cannot read from uninitialized register" (ppr r) -- NOTE: if the input to the NCG contains some -- unreachable blocks with junk code, this panic -- might be triggered. Make sure you only feed -- sensible code into the NCG. In CmmPipeline we -- call removeUnreachableBlocks at the end for this -- reason.
So we have a 'junk code' issue here.
Any hints how I can debug this?
New description: I get panics in the NCG PPC register allocator while compiling these files: {{{ rts_dist_HC rts/dist/build/StgStdThunks.dyn_o rts_dist_HC rts/dist/build/StgStdThunks.thr_dyn_o rts_dist_HC rts/dist/build/StgStdThunks.l_dyn_o rts_dist_HC rts/dist/build/StgStdThunks.thr_l_dyn_o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/Classes.o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/CString.o HC [stage 1] libraries/ghc-prim/dist-install/build/GHC/Debug.o }}} The panic message is like this: {{{ ghc-stage1: panic! (the 'impossible' happened) (GHC version 7.7.20130405 for powerpc-montavista-linux): allocateRegsAndSpill: Cannot read from uninitialized register %vI_nff }}} This makes the bootstapping of PPC cross compiler, ehm, delicate. There is a comment in compiler/nativeGen/RegAlloc/Linear/Main.hs:756 {{{ Nothing | reading -> pprPanic "allocateRegsAndSpill: Cannot read from uninitialized register" (ppr r) -- NOTE: if the input to the NCG contains some -- unreachable blocks with junk code, this panic -- might be triggered. Make sure you only feed -- sensible code into the NCG. In CmmPipeline we -- call removeUnreachableBlocks at the end for this -- reason. }}} So we have a 'junk code' issue here. Any hints how I can debug this? -- -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------+------------------------------------------------- Reporter: heisenbug | Owner: heisenbug Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Keywords: | Os: Unknown/Multiple Architecture: powerpc | Failure: Building GHC failed Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | --------------------------+------------------------------------------------- Changes (by igloo): * priority: normal => high * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------+------------------------------------------------- Reporter: heisenbug | Owner: heisenbug Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Keywords: | Os: Unknown/Multiple Architecture: powerpc | Failure: Building GHC failed Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | --------------------------+------------------------------------------------- Comment(by heisenbug): Replying to [comment:14 igloo]: The patch that I have committed seems to work, no panics any more. It remains to be verified, though, whether the compiled dynamic code works. I hope to have this done in the upcoming week. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7814: panic in PPC NCG --------------------------+------------------------------------------------- Reporter: heisenbug | Owner: heisenbug Type: bug | Status: new Priority: high | Milestone: 7.8.1 Component: Compiler | Version: 7.7 Keywords: | Os: Unknown/Multiple Architecture: powerpc | Failure: Building GHC failed Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | --------------------------+------------------------------------------------- Comment(by igloo): See also #7830 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7814#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC