[Haskell-cafe] GHC.Conc.threadStatus - documentation of ThreadDied :: ThreadStatus

Will Yager will.yager at gmail.com
Wed Mar 9 15:39:09 UTC 2022


The idiom I use for non-terminating processes with async looks like this (snippet from the end of a main function):


  outputter <- async $
    logged $
      forever $ do
        (topic, msg) <- liftIO $ readChan outputChan
        liftIO $ MC.publish client topic msg False
  automation <- async $ logged $ liftIO $ MC.waitForClient client
  calendarChecker <- async $ logged $ handleCalendarEvents (liftIO . calendar)
  (_, err :: String) <-
    liftIO $
      waitAny
        [ "logger1 died" <$ logger1,
          "logger2 died" <$ logger2,
          "reporter died" <$ reporter,
          "client died" <$ automation,
          "outputter died" <$ outputter,
          "calendar died" <$ calendarChecker
        ]
  print err

Typically these things like `automation` will return `IO void`, but they can return whatever you like. 


    

> On Mar 9, 2022, at 08:10, Olaf Klinke <olf at aatal-apotheke.de> wrote:
> 
> On Mon, 2022-03-07 at 19:59 +0000, coot at coot.me wrote:
>> Hi Olaf,
>> 
>> `forkIO` is rather a low level.  It's more common to use async package (https://hackage.haskell.org/package/async).  Async has `waitCatch` which allows you to wait for a thread to finish and get access to either an exception which killed the thread or the result of the thread handler.
>> 
>> Best regards,
>> Marcin Szamotulski
>> 
>> Sent with ProtonMail secure email.
> 
> Thanks for pointing this out, Marcin. 
> Async seems to offer much better abstractions than what GHC.Conc
> provides for  ThreadId. 
> I have the impression, though, that Async was written for threads that
> are supposed to do their work and eventually terminate. 
> In my application, a webserver forks several perpetually running
> threads and offers supervision to the user. Therefore withAsync is not
> perfectly suited, as we do not know upfront when and what we're going
> to do with the Async handle. I resorted to the following pattern. 
> 
> import Control.Concurrent.Async
> import Control.Concurrent
> import Control.Exception (SomeException)
> 
> type MyThread = (IO (),MVar (Async ()))
> 
> startThread :: MyThread -> IO ()
> startThread (action,var) = withAsync action (putMVar var)
> 
> pauseThread :: MyThread -> IO ()
> pauseThread (_,var) = do
>    a <- takeMVar var
>    cancel a
> 
> data MyThreadStatus = Paused | Running | Died SomeException
> threadStatus :: MyThread -> IO MyThreadStatus
> threadStatus (_,var) = do
>    running <- tryReadMVar var
>    case running of
>        Nothing -> return Paused
>        Just a -> do
>            finished <- poll a
>            case finished of
>                Nothing         -> return Running
>                Just (Right _)  -> return Paused
>                Just (Left why) -> return (Died why)
> 
> -- Olaf
> 
>> 
>> ------- Original Message -------
>> 
>>> On Monday, March 7th, 2022 at 10:56, Olaf Klinke <olf at aatal-apotheke.de> wrote:
>>> 
>>> Dear Cafe,
>>> 
>>> I had expected to see ThreadDied in the small example below.
>>> 
>>> But when I compile with
>>> 
>>> ghc --make -threaded -with-rtsopts=-N2
>>> 
>>> The output is:
>>> 
>>> threadStatus: user error (child thread is crashing!)
>>> 
>>> The status of my child is:
>>> 
>>> ThreadFinished
>>> 
>>> The output is not really a lie. But how do I determine whether a child
>>> 
>>> thread has exited normally or not? Wouldn't you say a call to fail (or
>>> 
>>> any other throwIO) should count as ThreadDied?
>>> 
>>> The documentation of GHC.Conc.forkIO says:
>>> 
>>> "... passes all other exceptions to the uncaught exception handler."
>>> 
>>> and the documentation for GHC.Conc.ThreadStatus says:
>>> 
>>> ThreadDied -- the thread received an uncaught exception
>>> 
>>> One can provoke ThreadDied by using throwTo from the parent thread. So
>>> 
>>> the emphasis in the documentation of ThreadDied should be on the word
>>> 
>>> "received".
>>> 
>>> This is a case of misleading documentation, in my humble opinion.
>>> 
>>> The constructor should not be named ThreadDied because that suggests
>>> 
>>> inclusion of internal reasons.
>>> 
>>> Olaf
>>> 
>>> -- begin threadStatus.hs
>>> 
>>> import Control.Concurrent
>>> 
>>> import GHC.Conc
>>> 
>>> main = mainThread
>>> 
>>> childThread :: IO ()
>>> 
>>> childThread = fail "child thread is crashing!"
>>> 
>>> mainThread :: IO ()
>>> 
>>> mainThread = do
>>> 
>>> child <- forkIO childThread
>>> 
>>> threadDelay 5000
>>> 
>>> status <- threadStatus child
>>> 
>>> putStr "The status of my child is: "
>>> 
>>> print status
>>> 
>>> -- end threadStatus.hs
>>> 
>>> _______________________________________________
>>> 
>>> Haskell-Cafe mailing list
>>> 
>>> To (un)subscribe, modify options or view archives go to:
>>> 
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>> 
>>> Only members subscribed via the mailman list are allowed to post.
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20220309/745079fc/attachment.html>


More information about the Haskell-Cafe mailing list