#3618: getStablePtr is called too early with dynamic libraries
-----------------------+----------------------------------------------------
Reporter: guest | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.12.1 RC1 | Severity: normal
Keywords: | Testcase:
Os: Linux | Architecture: x86_64 (amd64)
-----------------------+----------------------------------------------------
{{{
$ cat Hello.hs
module Main where
main = print "Hello world"
}}}
{{{
$ ghc -debug -dynamic --make Hello.hs && ./Hello +RTS -DS
Linking Hello ...
"Hello world"
Warning: Freeing non-allocated memory at 0x1ff87850
Warning: Freeing non-allocated memory at 0x1ff85820
Warning: Freeing non-allocated memory at 0x1ff85010
Warning: Freeing non-allocated memory at 0x1ff89860
Warning: Freeing non-allocated memory at 0x1ff8b860
Warning: 192 bytes at 0x1ff9b920 still allocated at shutdown
Warning: 2048 bytes at 0x1ff8ef50 still allocated at shutdown
Warning: 48 bytes at 0x1ff8eef0 still allocated at shutdown
Warning: 2048 bytes at 0x1ff8e6c0 still allocated at shutdown
Warning: 48 bytes at 0x1ff8e660 still allocated at shutdown
Warning: 2048 bytes at 0x1ff8de30 still allocated at shutdown
Warning: 48 bytes at 0x1ff8ddd0 still allocated at shutdown
Warning: 4100 bytes at 0x1ff8cca0 still allocated at shutdown
Warning: 16 bytes at 0x1ff8c980 still allocated at shutdown
Warning: 16 bytes at 0x1ff8c940 still allocated at shutdown
Warning: 4 bytes at 0x1ff8c880 still allocated at shutdown
Warning: 5 bytes at 0x1ff8c840 still allocated at shutdown
Warning: 8 bytes at 0x1ff8c800 still allocated at shutdown
Warning: 32 bytes at 0x1ff8c7b0 still allocated at shutdown
}}}
Note the freeing of non-allocated memory. This is because "base" contains
a foreign export of forkOS_entry. Foreign exports are desugared to uses of
__attribute__((constructor)) which call getStablePtr (in this case
initializing
stginit_export_base_ControlziConcurrent_zdfforkOSzuentryzua1bd). On our
system this initializer is being run when
libHSbase-4.2.0.0-ghc6.12.0.20091010.so gets loaded, which is before the
runtime is actually initialized.
This leads to a call to allocHashTable (from initStablePtrTable) which
allocates memory. This allocation is recorded in the allocs linked list
but when the runtime is initialized initAllocator gets called which
overwrites that entry. Hence when we come to free that hash table we free
a pointer which is not in the allocs list and get the warning.
I don't get this message with static linking on 6.10 - I can't check 6.12
because there is no static debug runtime for 6.12 RC1 by default. This
makes me suspect that this is a peculiarity of shared object
initialization, and the call to getStablePtr will happen more lazily with
static linking (probably on the first reference to a function in base),
such that it comes after RTS initialization is complete.
I observed this behaviour when trying to use -DS to isolate a segfault in
Haskell code in a very large program using -dynamic and Haskell shared
libraries. I'm not sure if this problem is actually causing my segfault,
but it certainly feels like it has the potential to do so, especially as I
tend to get my segfaults from Evac.c, which could be affected by the
stable ptr table.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3618>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs