What happens to child threads when their parent dies in GHC Haskell?

后端 未结 3 1931
被撕碎了的回忆
被撕碎了的回忆 2021-02-14 02:55

The documentation for forkIO says

GHC note: the new thread inherits the masked state of the parent (see mask).

The newly created thread has an exce         


        
相关标签:
3条回答
  • 2021-02-14 03:32

    This is an answer inspired by Zeta's. It uses a free monad transformer to avoid explicit nesting of computations, and the withAsync function from the async package instead of forkRunDie.

    module Main  where
    
    import Control.Monad
    import Control.Monad.Trans
    import Control.Monad.Trans.Free (FreeT,liftF,iterT)
    import Control.Concurrent
    import Control.Concurrent.Async (withAsync)
    import Control.Exception
    
    type DaemonIO = FreeT ((,) (IO ())) IO
    
    launch :: IO () -> DaemonIO ()
    launch a = liftF (a,()) 
    
    runDaemonIO :: DaemonIO a -> IO a
    runDaemonIO = iterT $ \(action,rest) -> withAsync action $ \_ -> rest
    
    main :: IO ()
    main = do
        let delaySeconds n = threadDelay $ n * (10^6)
        runDaemonIO $ do
            launch $ (forever $ delaySeconds 1 >> print "Pseudo child 1") 
                     `finally` putStrLn "killed 1!"
            launch $ (forever $ delaySeconds 1 >> print "Pseudo child 2") 
                     `finally` putStrLn "killed 2!"
            liftIO $ delaySeconds 10
            liftIO $ putStrLn "done!!!"
    
    0 讨论(0)
  • 2021-02-14 03:39

    In a standalone GHC program, only the main thread is required to terminate in order for the process to terminate. Thus all other forked threads will simply terminate at the same time as the main thread (the terminology for this kind of behaviour is "daemonic threads").

    https://hackage.haskell.org/package/base-4.7.0.0/docs/Control-Concurrent.html#g:12

    0 讨论(0)
  • 2021-02-14 03:43

    What exactly happens when the parent thread dies?

    Nothing. That's actually also true for POSIX threads. Threads don't share the parent-child relationship you might know from fork in C or similar languages. There is, however, one main thread, and its termination will usually lead to the termination of the whole program:

    Note that the thread in which main() was originally invoked differs from this. When it returns from main(), the effect is as if there was an implicit call to exit() using the return value of main() as the exit status.

    Does the child get any exception raised? Or is there any way at all to see from the child's perspective that the parent died? Is there anything else that happens except that the parent thread just stops running?

    No. No. And no. For the same reason as with usual OS threads. You can try this pretty easily:

    import Control.Concurrent (forkIO, threadDelay)
    
    delaySeconds n = threadDelay $ n * (10^6)
    
    main = do
      forkIO $ do
        forkIO $ delaySeconds 1 >> print "Pseudo child 1"
        forkIO $ delaySeconds 1 >> print "Pseudo child 2"
        print "Pseudo parent says goodbye"
      delaySeconds 10
      print "Exiting main"
    

    The "parent" will say goodbye, and the "children" will print a second later. Remember, there is no actual parent in thread programming. There are only siblings. One of them is a little bit special, yes, but that is just how it's been specified.

    Is it necessary to restructure the program and propagate the child's ThreadId up to the parent and explicitly kill it?

    At least a little bit, since forkIO doesn't provide this. Also, if there was a forkIOKillAutomatically, what type should it have? And why?

    Or is there any other workaround for this?

    Well, you could provide the rest of your parent as another action, and therefore use a helper:

    forkRunDie :: IO () -> IO () -> IO ()
    forkRunDie p s = forkIO p >>= \tid -> s >> killThread tid
    

    The above example would then become

    main = do
      forkIO $ do
        forkRunDie (delaySeconds 1 >> print "Pseudo child 1") $ do
          forkRunDie (delaySeconds 1 >> print "Pseudo child 2") $ do
            print "Pseudo parent says goodbye"
      delaySeconds 10
      print "Exiting main"
    

    In this case the only output will be

    "Pseudo parent says goodbye"
    "Exiting main"
    

    See also:

    • Smarter termination for thread racing by Conal Elliott (provides a very similar function to forkRunDie with finally).
    0 讨论(0)
提交回复
热议问题