[Haskell-cafe] waitForProcess: sytem call interrupted
Joel Reymont
joelr1 at gmail.com
Tue Nov 15 20:36:41 EST 2005
Folks,
My program frequently quites (I think) after this message:
waitForProcess: sytem call interrupted
I think it has to do with my killing the thread that calls connectTo,
after a certain timeout. Is there a way to catch this exception so
that the program does not crash?
My code looks like this:
connect :: HostName -> Int -> EngineState ()
connect host port =
do w <- get
let secs = timeout_seconds w
x <- liftIOTrap $ timeout secs $ connect_ host port
let h = case x of (Right x') -> x'
trace "Connection established"
...
timeout :: forall a.Show a => Int -> IO a -> IO (Either String a)
timeout secs fun =
do resultVar <- newEmptyMVar
threadId <- forkIO $
do result <- try fun
let x = case result of
Right a -> Right a
Left b -> Left (fromIOError b)
trace_ $ "timeout: " ++ show x
putMVar resultVar x
forkIO $ do threadDelay (secs * 1000000)
putMVar resultVar (Left "Timeout")
maybeResult <- takeMVar resultVar
case maybeResult
of (Right result) -> return (Right result)
(Left result) -> do killThread threadId
return (Left result)
and
fromIOError err = ioeGetErrorString err
liftIOTrap :: IO a -> EngineState a
liftIOTrap io =
do mx <- liftIO (do x <- io
return (return x)
`catchError`
(\e -> return (throwError
(fromIOError e))))
mx
Thanks, Joel
--
http://wagerlabs.com/
More information about the Haskell-Cafe
mailing list