[GHC] #14725: memory leak: forkOS not releasing thread local `Task` struct upon end of thread
GHC
ghc-devs at haskell.org
Fri Jan 26 16:30:23 UTC 2018
#14725: memory leak: forkOS not releasing thread local `Task` struct upon end of
thread
-------------------------------------+-------------------------------------
Reporter: RobertZabel | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Runtime System | Version: 8.2.2
Resolution: | Keywords: forkOS memory
| leak
Operating System: POSIX | Architecture:
| Unknown/Multiple
Type of failure: Other | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by RobertZabel:
Old description:
> I came to notice a memory leak in the runtime system while letting warp
> use `forkOS` and conducting a load test.\\
> A minimal snippet to reproduce:
>
> {{{#!hs
> module Main where
> import Control.Concurrent
>
> main :: IO ()
> main = replicateM_ 10000000 $ forkOS $ return ()
> }}}
>
> This patch will clean up the thread local `Task` struct just before
> threads created by forkOS terminate.
>
> {{{
> diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c
> index c9adf4e..bd4e75d 100644
> --- a/rts/posix/OSThreads.c
> +++ b/rts/posix/OSThreads.c
> @@ -223,6 +223,7 @@ forkOS_createThreadWrapper ( void * entry )
> cap = rts_lock();
> rts_evalStableIO(&cap, (HsStablePtr) entry, NULL);
> rts_unlock(cap);
> + rts_done();
> return NULL;
> }
> }}}
>
> I think win32 platforms need an equivalent patch, but unfortunately I
> cannot verify that. \\
> Hence I'm only targeting posix here.
New description:
I came to notice a memory leak in the runtime system while letting warp
use `forkOS` and conducting a load test.\\
A minimal snippet to reproduce:
{{{#!hs
module Main where
import Control.Concurrent
import Control.Monad
main :: IO ()
main = replicateM_ 10000000 $ forkOS $ return ()
}}}
This patch will clean up the thread local `Task` struct just before
threads created by forkOS terminate.
{{{
diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c
index c9adf4e..bd4e75d 100644
--- a/rts/posix/OSThreads.c
+++ b/rts/posix/OSThreads.c
@@ -223,6 +223,7 @@ forkOS_createThreadWrapper ( void * entry )
cap = rts_lock();
rts_evalStableIO(&cap, (HsStablePtr) entry, NULL);
rts_unlock(cap);
+ rts_done();
return NULL;
}
}}}
I think win32 platforms need an equivalent patch, but unfortunately I
cannot verify that. \\
Hence I'm only targeting posix here.
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14725#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list