[Haskell-cafe] Threads and hGetLine
Johannes Waldmann
waldmann at imn.htwk-leipzig.de
Wed May 2 20:45:44 CEST 2012
> There are two threads, one which is waits on input via
> hGetLine
> and another, which should terminate this thread or close this handle.
like this? The trick is to fork the blocking call (hGetLine)
and wait on an MVar. That way, the kill signal can be handled:
{-# language PatternSignatures #-}
import Control.Concurrent
import Control.Concurrent.MVar
import Control.Exception
import System.IO
main = do
pid <- forkIO $ do
s <- wawiter
putStrLn s
threadDelay $ 5 * 10^6
killThread pid
waiter = do
v <- newEmptyMVar
forkIO $ do s <- hGetLine stdin ; putMVar v s
readMVar v `Control.Exception.catch`
\ (e :: AsyncException ) -> return "killed"
PS: and I refuse to use the "ScopedTypeVariables" pragma
since obviously there are no type variables.
More information about the Haskell-Cafe
mailing list