[Haskell-cafe] Re: Cleaning up threads

Ertugrul Soeylemez es at ertes.de
Mon Sep 13 03:03:11 EDT 2010


Mitar <mmitar at gmail.com> wrote:

> I run multiple threads where I would like that exception from any of
> them (and main) propagate to others but at the same time that they can
> gracefully cleanup after themselves (even if this means not exiting).
> I have this code to try, but cleanup functions (stop) are interrupted.
> How can I improve this code so that this not happen?

In general it's better to avoid using killThread.  There are much
cleaner ways to tell a thread to exit.  A very common piece of code
found in my applications is this:

  data StateCmd s
    = GetState (s -> IO ())
    | ModifyState (s -> s)
    | Quit (() -> IO ())
    | SetState s

  stateThread :: s -> IO (StateCmd s -> IO ())
  stateThread initialState = do
    cmdVar <- newEmptyMVar
    forkIO . runContT return . fmap fst . runStateT initialState .
      forever $ do
        cmd <- inBase $ takeMVar cmdVar
        case cmd of
          GetState c    -> get >>= inBase . c
          ModifyState f -> sets_ f
          Quit c        -> inBase (c ()) >> abort ()
          SetState x    -> set x
    return (putMVar cmdVar)

  askThread :: (c -> IO ()) -> ((r -> IO ()) -> c) -> IO r
  askThread sendCmd cmdName = do
    result <- newEmptyMVar
    sendCmd $ cmdName (putMVar result)
    takeMVar result

The 'stateThread' function gives a computation, which starts a thread to
maintain state of a certain type.  It returns a function to send
commands to this thread.  Those commands, which don't require an answer
like SetState and ModifyState, can be sent right away using this
command.  For those, which will give an answer like GetState and Quit,
exists a convenience function askThread.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/




More information about the Haskell-Cafe mailing list