[Haskell-cafe] IO exception not being caught

Joel Reymont joelr1 at gmail.com
Wed Nov 16 08:27:28 EST 2005


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/







More information about the Haskell-Cafe mailing list