Re: Weird behavior of the NonTermination exception

2012-05-04 Thread Bas van Dijk
On 4 May 2012 14:12, Simon Marlow  wrote:
> The forked thread is deadlocked, so the MVar is considered unreachable and
> the main thread is also unreachable.  Hence both threads get sent the
> exception.
>
> The RTS does this analysis using the GC, tracing the reachable objects
> starting from the roots.  It then send an exception to any threads which
> were not reachable, which in this case is both the main thread and the
> child, since neither is reachable.
>
> We (the user) knows that waking up the child thread will unblock the main
> thread, but the RTS doesn't know this, and it's not clear how it could find
> out easily (i.e. without multiple scans of the heap).

Thanks Simon, I learned something new today.

Cheers,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Weird behavior of the NonTermination exception

2012-05-04 Thread Simon Marlow

On 03/05/2012 17:14, Bas van Dijk wrote:

On 3 May 2012 17:31, Edward Z. Yang  wrote:

Excerpts from Bas van Dijk's message of Thu May 03 11:10:38 -0400 2012:

As can be seen, the putMVar is executed successfully. So why do I get
the message: "thread blocked indefinitely in an MVar operation"?


GHC will send BlockedIndefinitelyOnMVar to all threads involved
in the deadlock, so it's not unusual that this can interact with
error handlers to cause the system to become undeadlocked.


But why is the BlockedIndefinitelyOnMVar thrown in the first place?
According to the its documentation and your very enlightening article
it is thrown when:

"The thread is blocked on an MVar, but there are no other references
to the MVar so it can't ever continue."

The first condition holds for the main thread since it's executing
takeMVar. But the second condition doesn't hold since the forked
thread still has a reference to the MVar.


The forked thread is deadlocked, so the MVar is considered unreachable 
and the main thread is also unreachable.  Hence both threads get sent 
the exception.


The RTS does this analysis using the GC, tracing the reachable objects 
starting from the roots.  It then send an exception to any threads which 
were not reachable, which in this case is both the main thread and the 
child, since neither is reachable.


We (the user) knows that waking up the child thread will unblock the 
main thread, but the RTS doesn't know this, and it's not clear how it 
could find out easily (i.e. without multiple scans of the heap).


Cheers,
Simon





I just tried delaying the thread before the putMVar:

-
main :: IO ()
main = do
   mv<- newEmptyMVar
   _<- forkIO $ do
  catch action
(\e ->  putStrLn $ "I solved the Halting Problem: " ++
  show (e :: SomeException))
  putStrLn "Delaying for 2 seconds..."
  threadDelay 200
  putStrLn "putting MVar..."
  putMVar mv ()
  putStrLn "putted MVar"
   takeMVar mv
-

Now I get the following output:

loop: thread blocked indefinitely in an MVar operation
I solved the Halting Problem:<>
Delaying for 2 seconds...

Now it seems the thread is killed while delaying. But why is it
killed? It could be a BlockedIndefinitelyOnMVar that is thrown.
However I get the same output when I catch and print all exceptions in
the forked thread:

main :: IO ()
main = do
   mv<- newEmptyMVar
   _<- forkIO $
  handle (\e ->  putStrLn $ "Oh nooo:" ++
   show (e :: SomeException)) $ do
catch action
  (\e ->  putStrLn $ "I solved the Halting Problem: " ++
show (e :: SomeException))
putStrLn "Delaying for 2 seconds..."
threadDelay 200
putStrLn "putting MVar..."
putMVar mv ()
putStrLn "putted MVar"
   takeMVar mv

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Weird behavior of the NonTermination exception

2012-05-03 Thread Bas van Dijk
On 3 May 2012 18:14, Bas van Dijk  wrote:
> Now it seems the thread is killed while delaying. But why is it
> killed?

Oh I realise the forked thread is killed because the main thread
terminates because it received a BlockedIndefinitelyOnMVar exception
and then all daemonic threads are killed.

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Weird behavior of the NonTermination exception

2012-05-03 Thread Bas van Dijk
On 3 May 2012 17:31, Edward Z. Yang  wrote:
> Excerpts from Bas van Dijk's message of Thu May 03 11:10:38 -0400 2012:
>> As can be seen, the putMVar is executed successfully. So why do I get
>> the message: "thread blocked indefinitely in an MVar operation"?
>
> GHC will send BlockedIndefinitelyOnMVar to all threads involved
> in the deadlock, so it's not unusual that this can interact with
> error handlers to cause the system to become undeadlocked.

But why is the BlockedIndefinitelyOnMVar thrown in the first place?
According to the its documentation and your very enlightening article
it is thrown when:

"The thread is blocked on an MVar, but there are no other references
to the MVar so it can't ever continue."

The first condition holds for the main thread since it's executing
takeMVar. But the second condition doesn't hold since the forked
thread still has a reference to the MVar.

I just tried delaying the thread before the putMVar:

-
main :: IO ()
main = do
  mv <- newEmptyMVar
  _ <- forkIO $ do
 catch action
   (\e -> putStrLn $ "I solved the Halting Problem: " ++
 show (e :: SomeException))
 putStrLn "Delaying for 2 seconds..."
 threadDelay 200
 putStrLn "putting MVar..."
 putMVar mv ()
 putStrLn "putted MVar"
  takeMVar mv
-

Now I get the following output:

loop: thread blocked indefinitely in an MVar operation
I solved the Halting Problem: <>
Delaying for 2 seconds...

Now it seems the thread is killed while delaying. But why is it
killed? It could be a BlockedIndefinitelyOnMVar that is thrown.
However I get the same output when I catch and print all exceptions in
the forked thread:

main :: IO ()
main = do
  mv <- newEmptyMVar
  _ <- forkIO $
 handle (\e -> putStrLn $ "Oh nooo:" ++
  show (e :: SomeException)) $ do
   catch action
 (\e -> putStrLn $ "I solved the Halting Problem: " ++
   show (e :: SomeException))
   putStrLn "Delaying for 2 seconds..."
   threadDelay 200
   putStrLn "putting MVar..."
   putMVar mv ()
   putStrLn "putted MVar"
  takeMVar mv

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Weird behavior of the NonTermination exception

2012-05-03 Thread Edward Z. Yang
Excerpts from Bas van Dijk's message of Thu May 03 11:10:38 -0400 2012:
> As can be seen, the putMVar is executed successfully. So why do I get
> the message: "thread blocked indefinitely in an MVar operation"?

GHC will send BlockedIndefinitelyOnMVar to all threads involved
in the deadlock, so it's not unusual that this can interact with
error handlers to cause the system to become undeadlocked.

http://blog.ezyang.com/2011/07/blockedindefinitelyonmvar/

However, I must admit I am a bit confused as for the timing of
the thrown exceptions.

Edward

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Weird behavior of the NonTermination exception

2012-05-03 Thread Bas van Dijk
Hello,

Before I turn the following into a ticket I want to ask if I miss
something obvious:

When I run the following program:

-
import Prelude hiding (catch)
import Control.Exception
import Control.Concurrent

main :: IO ()
main = do
  mv <- newEmptyMVar
  _ <- forkIO $ do
 catch action
   (\e -> putStrLn $ "I solved the Halting Problem: " ++
 show (e :: SomeException))
 putStrLn "putting MVar..."
 putMVar mv ()
 putStrLn "putted MVar"
  takeMVar mv

action :: IO ()
action = let x = x in x
-

I get the output:

$ ghc --make Loop.hs -o loop -O2 -fforce-recomp && ./loop
[1 of 1] Compiling Main ( Loop.hs, Loop.o )
Linking loop ...
loop: thread blocked indefinitely in an MVar operation
I solved the Halting Problem: <>
putting MVar...
putted MVar

As can be seen, the putMVar is executed successfully. So why do I get
the message: "thread blocked indefinitely in an MVar operation"?

Note that if I change the action to a normal error the message disappears.

I discovered this bug when hunting for another one. I have a Haskell
web-server where one of the request handlers contained a loop. All
exceptions thrown by handlers are caught and logged. When executing
the looping handler I noticed ~0% CPU usage so I assumed that the
handler wasn't actually looping because a NonTermination exception was
thrown. However for some reason the NonTermination exception was not
caught and logged. I haven't yet isolated this bug into a small
test-case but when trying that I discovered the above.

Regards,

Bas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users