
#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