[GHC] #8834: 64-bit windows cabal.exe segfaults in GC

GHC ghc-devs at haskell.org
Mon Mar 31 07:01:57 UTC 2014


#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
        Reporter:  awson          |            Owner:
            Type:  bug            |           Status:  new
        Priority:  highest        |        Milestone:  7.8.1
       Component:  Compiler       |          Version:  7.8.1-rc2
      Resolution:                 |         Keywords:
Operating System:  Windows        |     Architecture:  x86_64 (amd64)
 Type of failure:  Runtime crash  |       Difficulty:  Unknown
       Test Case:                 |       Blocked By:
        Blocking:                 |  Related Tickets:
----------------------------------+----------------------------------

Comment (by thoughtpolice):

 Okay, I spent some time boiling some things down, and I've at least
 determined the approximate location of the segfault in the code during
 compilation, which is `stmtToInstrs` in
 `compiler/nativeGen/X86/CodeGen.hs`. Here's just a quick dump (to not
 loose findings) and I'll keep looking around.

 The fault is when compiling `System.Time` in profiling. Run under gdb:

 {{{
 $ gdb --args "inplace/bin/ghc-stage2.exe" -v3 -hisuf p_hi -osuf  p_o
 -hcsuf p_hc -static -prof  -H32m -O    -package-name old-time-1.i
 -ilibraries/old-time/. -ilibraries/old-time/dist-install/build -ilibraries
 /old-time/dist-install/build/autogen -Ilibraries/old-timearies/old-time
 /dist-install/build/autogen -Ilibraries/old-time/include    -optP-include
 -optPlibraries/old-time/dist-install/build/auage base-4.7.0.0 -package
 old-locale-1.0.0.6 -Wall -XHaskell2010 -O2  -no-user-package-db -rtsopts
 -odir libraries/old-time/distaries/old-time/dist-install/build -stubdir
 libraries/old-time/dist-install/build   -c libraries/old-time/dist-
 install/build/System/Tie/dist-install/build/System/Time.p_o +RTS -DS
 GNU gdb (GDB) 7.6.1
 Copyright (C) 2013 Free Software Foundation, Inc.
 License GPLv3+: GNU GPL version 3 or later
 <http://gnu.org/licenses/gpl.html>
 This is free software: you are free to change and redistribute it.
 There is NO WARRANTY, to the extent permitted by law.  Type "show copying"
 and "show warranty" for details.
 This GDB was configured as "i686-pc-msys".
 For bug reporting instructions, please see:
 <http://www.gnu.org/software/gdb/bugs/>...
 Traceback (most recent call last):
   File "<string>", line 3, in <module>
 ImportError: No module named libstdcxx.v6.printers
 /etc/gdbinit:6: Error in sourced command file:
 Error while executing Python code.
 Reading symbols from /home/Administrator/ghc/inplace/bin/ghc-
 stage2.exe...done.
 warning: File "/home/Administrator/ghc/.gdbinit" auto-loading has been
 declined by your `auto-load safe-path' set to "$debugdir:$datadir/auto-
 load".
 To enable execution of this file add
         add-auto-load-safe-path /home/Administrator/ghc/.gdbinit
 line to your configuration file "/home/Administrator/.gdbinit".
 To completely disable this security protection add
         set auto-load safe-path /
 line to your configuration file "/home/Administrator/.gdbinit".
 For more information about this security protection see the
 "Auto-loading safe path" section in the GDB manual.  E.g., run from the
 shell:
         info "(gdb)Auto-loading safe path"
 (gdb) load .gdbinit
 You can't do that when your target is `exec'
 (gdb) source .gdbinit
 (gdb) r
 Starting program: /home/Administrator/ghc/inplace/bin/ghc-stage2.exe -v3
 -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -package-name
 old-time-1.1.0.2 -hide-all-packages -i -ilibraries/old-time/. -ilibraries
 /old-time/dist-install/build -ilibraries/old-time/dist-
 install/build/autogen -Ilibraries/old-time/dist-install/build -Ilibraries
 /old-time/dist-install/build/autogen -Ilibraries/old-time/include -optP-
 include -optPlibraries/old-time/dist-install/build/autogen/cabal_macros.h
 -package base-4.7.0.0 -package old-locale-1.0.0.6 -Wall -XHaskell2010 -O2
 -no-user-package-db -rtsopts -odir libraries/old-time/dist-install/build
 -hidir libraries/old-time/dist-install/build -stubdir libraries/old-time
 /dist-install/build -c libraries/old-time/dist-
 install/build/System/Time.hs -o libraries/old-time/dist-
 install/build/System/Time.p_o +RTS -DS
 [New Thread 1136.0xcc8]
          cc8: cap 0: initialised
 [New Thread 1136.0x15e8]
 [New Thread 1136.0x1658]
 [New Thread 1136.0x11b8]
 [New Thread 1136.0x11e8]
 [New Thread 1136.0x1718]
 Glasgow Haskell Compiler, Version 7.9.20140329, stage 2 booted by GHC
 version 7.6.3
 Using binary package database:
 C:\Users\Administrator\Desktop\msys32\home\Administrator\ghc\inplace\lib\package.conf.d\package.cache
 wired-in package ghc-prim mapped to ghc-prim-0.3.1.0-inplace
 wired-in package integer-gmp mapped to integer-gmp-0.5.1.0-inplace
 wired-in package base mapped to base-4.7.0.0-inplace
 wired-in package rts mapped to builtin_rts
 wired-in package template-haskell mapped to template-
 haskell-2.10.0.0-inplace
 wired-in package dph-seq not found.
 wired-in package dph-par not found.
 Hsc static flags:
 *** Checking old interface for old-time-1.1.0.2:System.Time:
 *** Parser:
 *** Renamer/typechecker:
 *** Desugar:
 Result size of Desugar (after optimization)
   = {terms: 5,701, types: 3,843, coercions: 29}
 ...
 *** Tidy Core:
 Result size of Tidy Core
   = {terms: 15,413, types: 10,079, coercions: 582}
 Created temporary directory:
 C:\Users\Administrator\Desktop\msys32\tmp\ghc1136_0
 *** CorePrep:
 Result size of CorePrep
   = {terms: 18,936, types: 12,028, coercions: 582}
 *** Stg2Stg:
 *** CodeOutput:
 *** New CodeGen:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:
 *** CPSZ:

 Program received signal SIGSEGV, Segmentation fault.
 0x02137032 in c1hhA_info ()
 (gdb) bt
 #0  0x02137032 in c1hhA_info ()
 Cannot access memory at address 0x28a874
 (gdb) disassemble
 Dump of assembler code for function c1hhA_info:
    0x02137024 <+0>:     sub    $0x3510,%esp
    0x0213702a <+6>:     mov    0x8(%ebp),%eax
    0x0213702d <+9>:     mov    0x4(%ebp),%ecx
    0x02137030 <+12>:    mov    %esi,%edx
 => 0x02137032 <+14>:    mov    %eax,0x184(%esp)
    0x02137039 <+21>:    mov    -0x1(%edx),%eax
    0x0213703c <+24>:    movzwl -0x2(%eax),%eax
    0x02137040 <+28>:    cmp    $0x1e,%eax
    0x02137043 <+31>:    ja     0x214916f <c1hrv_info+1119>
    0x02137049 <+37>:    mov    %eax,0x190(%esp)
    0x02137050 <+44>:    mov    0x1c(%ebp),%eax
    0x02137053 <+47>:    mov    %eax,0xa0(%esp)
    0x0213705a <+54>:    mov    0x190(%esp),%eax
    0x02137061 <+61>:    jmp    *0x2b86708(,%eax,4)
    0x02137068 <+68>:    inc    %edx
    0x02137069 <+69>:    add    %al,(%eax)
    0x0213706b <+71>:    add    %ah,(%eax)
    0x0213706d <+73>:    add    %al,(%eax)
    0x0213706f <+75>:    add    %al,0x3510ec(%ecx)
 End of assembler dump.
 (gdb)
 (gdb) info registers
 eax            0x6b3b05d        112439389
 ecx            0x6b49524        112497956
 edx            0x67a40a9        108675241
 ebx            0x2bc3470        45888624
 esp            0x28a874 0x28a874
 ebp            0x4697cc8        0x4697cc8
 esi            0x67a40a9        108675241
 edi            0x6b4ac20        112503840
 eip            0x2137032        0x2137032 <c1hhA_info+14>
 eflags         0x10202  [ IF RF ]
 cs             0x23     35
 ss             0x2b     43
 ds             0x2b     43
 es             0x2b     43
 fs             0x53     83
 gs             0x2b     43
 (gdb) p8 $ebp
 0x4697ce4:      0x6b488d9
 0x4697ce0:      0x6b4ac18
 0x4697cdc:      0x6300ef1e
 0x4697cd8:      0x6b4954d
 0x4697cd4:      0x67a40a9
 0x4697cd0:      0x6b3b05d
 0x4697ccc:      0x6b49524
 0x4697cc8:      0x2137024 <c1hhA_info>
 (gdb) pinfo &c1hhA_info
 $1 = {layout = {payload = {ptrs = 903, nptrs = 0}, bitmap = 903,
 large_bitmap_offset = 903, selector_offset = 903}, type = 32,
   srt_bitmap = 7, code = 0x2137024 <c1hhA_info> "\201\354\020\065"}
 (gdb) prinfo &c1hhA_info
 $2 = {srt_offset = 8706840, i = {layout = {payload = {ptrs = 903, nptrs =
 0}, bitmap = 903, large_bitmap_offset = 903,
       selector_offset = 903}, type = 32, srt_bitmap = 7, code = 0x2137024
 <c1hhA_info> "\201\354\020\065"}}

 }}}

 The fault is in `c1hhA_info`. Finding that symbol:

 {{{
 $ find compiler/stage2 -type f | xargs grep c1hhA_info
 Binary file compiler/stage2/build/libHSghc-7.9.20140329.a matches
 Binary file compiler/stage2/build/X86/CodeGen.o matches
 }}}

 It's in `./nativeGen/X86/CodeGen.hs` - check the `-ddump-opt-cmm` out to
 get corresponding optimized code, finding the closure for the info table:

 {{{
 ==================== Optimised Cmm ====================
 a292_rFAj_entry() //  []
         { [(c18OH,
             block_c18OH_info:
                 const u1hJf_srtd-block_c18OH_info;
                 const 1;
                 const 4294901792;),
            (c18OQ,
             block_c18OQ_info:
                 const u1hJg_srtd-block_c18OQ_info;
                 const 3;
                 const 4294901792;),
 ...
 ...
 ...
            (c1hhA,
             block_c1hhA_info:
                 const SUys_srt-block_c1hhA_info+2332;
                 const 903;
                 const 458784;),
 ...
 ...
 ...
       c1hyQ:
           I32[Hp - 8] = $w$j_sSgL_info;
           I32[Hp - 4] = I32[Sp + 24];
           I32[Hp] = I32[Sp + 20];
           I32[Sp] = block_c1hhA_info;
           R1 = P32[Sp + 12];
           P32[Sp + 24] = Hp - 8;
           if (R1 & 3 != 0) goto c1hhA; else goto c1hhB;
       c1hhB:
           call (I32[R1])(R1) returns to c1hhA, args: 4, res: 4, upd: 4;
       c1hhA:
           _sSgE::P32 = P32[Sp + 8];
           _sSgI::P32 = P32[Sp + 4];
           _sSmu::P32 = R1;
           _c1hub::I32 = %MO_UU_Conv_W16_W32(I16[I32[_sSmu::P32 - 1] - 2]);
           if (_c1hub::I32 > 30) goto c1hug; else goto c1hue;
 ...
 ...
 }}}

 We can see this matches pretty closely with the assembly generated around
 the offending code (`-ddump-asm`):

 {{{
 _c1hyQ:
         movl $$w$j_sSgL_info,-8(%edi)
         movl 24(%ebp),%eax
         movl %eax,-4(%edi)
         movl 20(%ebp),%eax
         movl %eax,(%edi)
         movl $block_c1hhA_info,(%ebp)
         movl 12(%ebp),%esi
         leal -8(%edi),%eax
         movl %eax,24(%ebp)
         testl $3,%esi
         jne _n1kED
 ...
 .text
         .align 4,0x90
         .long   SUys_srt-(block_c1hhA_info)+2332
         .long   903
         .long   458784
 block_c1hhA_info:
 _c1hhA:
         subl $13584,%esp
 _n1kED:
         movl 8(%ebp),%eax
         movl 4(%ebp),%ecx
         movl %esi,%edx
         movl %eax,388(%esp)
         movl -1(%edx),%eax
         movzwl -2(%eax),%eax
         cmpl $30,%eax
         ja _c1hug
 }}}

 Next, looking at the STG output, `a292_rFAj` looks like:

 {{{
 a292_rFAj
   :: forall e_a94q x_a94r.
      CmmNode.CmmNode e_a94q x_a94r
      -> NCGMonad.NatM_State
      -> (X86.CodeGen.InstrBlock, NCGMonad.NatM_State)
 ...
 }}}

 If you search for calls to this, there is one call to it from `a290_rFAh`,
 which looks like:

 {{{
 a290_rFAh
   :: CmmMachOp.CallishMachOp
      -> Data.Maybe.Maybe CmmNode.CmmFormal
      -> [CmmNode.CmmActual]
      -> NCGMonad.NatM_State
      -> (X86.CodeGen.InstrBlock, NCGMonad.NatM_State)
 ...
                 let {
                   sat_sMWp [Occ=Once]
                     :: CmmNode.CmmNode Compiler.Hoopl.Block.O
 Compiler.Hoopl.Block.O
                   [LclId, Str=DmdType] =
                       NO_CCS CmmNode.CmmUnsafeForeignCall!
 [GHC.Prim.coercionToken#
 GHC.Prim.coercionToken#
                                                             sat_sMWb
                                                             sat_sMWd
                                                             sat_sMWo];
                 } in  a292_rFAj sat_sMWp st'_sMWa;
 }}}

 The only thing that has a type of `CallishMachOp -> ...` is
 `outOfLineCmmOp`, which does indeed call `stmtToInstrs
 (CmmUnsafeForeignCall ...)` like in the above snippet. The type of
 `stmtToInstrs` also matches the (desugared) type of `a292_rFAj`. So this
 is certainly where the fault is occurring.

 Unfortunately `stmtToInstrs` becomes incredibly large it seems, so pinning
 it down further is proving challening.

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


More information about the ghc-tickets mailing list