
Folks, I have a problem catching my IO exception with the code below. The intent is to catch either the IO exception from connectTo (connection refused, etc.) or the timeout. type EngineState = ErrorT String (StateT World IO) 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 timeout secs fun = do resultVar <- newEmptyMVar threadId <- forkIO $ do result <- fun putMVar resultVar result forkIO $ do threadDelay (secs * 1000000) throwError $ userError "Timeout" maybeResult <- takeMVar resultVar killThread threadId return maybeResult connect_ :: HostName -> Int -> IO Handle connect_ h p = connectTo h $ PortNumber $ fromIntegral p connect :: HostName -> Int -> EngineState () connect host port = do w <- get let secs = timeout_seconds w h <- liftIOTrap $ timeout secs $ connect_ host port trace $ "Connection established, h: " ++ show h ... Thanks, Joel -- http://wagerlabs.com/

I fixed up my timeout function to look like this: timeout :: forall a.Show a => Int -> IO a -> IO a timeout secs fun = mdo mvar <- newEmptyMVar tid1 <- forkIO $ do result <- try fun putMVar mvar $ either (Left . show) (Right . id) result killThread tid2 tid2 <- forkIO $ do threadDelay (secs * 1000000) putMVar mvar (Left "timeout") killThread tid1 maybeResult <- takeMVar mvar case maybeResult of Right a -> return a Left b -> fail b But the IOError is still not being caught by liftIOTrap. Any clues? Thanks, Joel On Nov 16, 2005, at 1:27 PM, Joel Reymont wrote:
Folks,
I have a problem catching my IO exception with the code below. The intent is to catch either the IO exception from connectTo (connection refused, etc.) or the timeout.
type EngineState = ErrorT String (StateT World IO)
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

After almost two months with Haskell I'm starting to understand why its use is not as widespread as... well pick a favorite language of your own. My issue was that of indentation. Compare this working version: liftIOTrap io = do mx <- liftIO (do x <- io return (return x) `catchError` (\e -> do let x = fromIOError e trace_ $ "Caught " ++ x return $ throwError x )) mx With the one below On Nov 16, 2005, at 2:27 PM, Joel Reymont wrote:
liftIOTrap io = do mx <- liftIO (do x <- io return (return x) `catchError` (\e -> return (throwError (fromIOError e)))) mx

Hello Joel, Wednesday, November 16, 2005, 6:37:25 PM, you wrote: JR> After almost two months with Haskell I'm starting to understand why JR> its use is not as widespread as... well pick a favorite language of JR> your own. My issue was that of indentation. just enclose potentially problematic "do ..." in parentheses: JR> liftIOTrap io = JR> do mx <- liftIO (do x <- io JR> return (return x) can be written as do mx <- liftIO ((do x <- io return (return x)) and after that you can put `catchError` to any position in the line -- Best regards, Bulat mailto:bulatz@HotPOP.com
participants (2)
-
Bulat Ziganshin
-
Joel Reymont