[GHC] #16286: Continuations are not labelled in the binaries even with -g3

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Any program would work as a reproducer, but here's what I'm using currently: {{{ {-# LANGUAGE StaticPointers #-} module Main where import Control.Concurrent import System.Mem nats :: [Int] nats = [0 .. ] main = do let z = nats !! 400 print z performGC threadDelay 1000000 print (nats !! 900) }}} If I do `printStack` every time the GC copies a stack I sometimes see stack frames like {{{ RET_SMALL (0x535568) }}} but in gdb or objdump output I can't find a symbol at that address, even when the program is built with `-g3`. When I print the location as `StgInfoTable*` I can see that it's a valid info table so `0x535578` should be labelled as `foo_info`. In the objdump output I see that the location is shown as this: {{{ 535563: 0f 1f 44 00 00 nopl 0x0(%rax,%rax,1) ... 535570: 1e (bad) 535571: 00 00 add %al,(%rax) 535573: 00 00 add %al,(%rax) 535575: 00 00 add %al,(%rax) 535577: 00 bb e9 e2 85 00 add %bh,0x85e2e9(%rbx) 53557d: 48 83 c5 08 add $0x8,%rbp }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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: | -------------------------------------+------------------------------------- Comment (by osa1): I think we also don't generate labels for some closures. For example, I currently see `lvl7_r1Al_closure` in dump-asm, but gdb can't find `r1Al_closure` or `lvl7_r1Al_closure`, and I also don't see them in `nm` output. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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: | -------------------------------------+------------------------------------- Comment (by osa1): I _think_ this is because those symbols are not marked as `.globl` because they're not supposed to be referenced by other object files. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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: | -------------------------------------+------------------------------------- Comment (by osa1): Maybe not. `r1Al_info` is defined like this {{{ .section .text .align 8 .align 8 .loc 1 16 18 .quad 0 .long 21 .long .Lu1NS_srt-(.Lr1Al_info)+0 .Lr1Al_info: ... }}} This is also not `.globl`, but I can see it in gdb. I think because of this {{{ .L.Lr1Al_info_die: .byte 2 .asciz "main" .asciz "r1Al_info" .byte 0 .quad .Lr1Al_info .quad .L.Lr1Al_info_end .byte 1 .byte 156 }}} So maybe we need something like this for `r1Al_closure` ? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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: | -------------------------------------+------------------------------------- Comment (by osa1): It seems like we only generate debug info for `CmmProc`s currently, ignoring `CmmData`. I don't know if this is because of a limitation of DWARF, or because no one needed this before. @bgamari, any ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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: | -------------------------------------+------------------------------------- Comment (by bgamari): I seem to recall that there was a relevant hack in Phab:D4713 which might compromise symbol generation of info tables. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16286: Continuations are not labelled in the binaries even with -g3 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: DWARF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => DWARF -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16286#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC