[Haskell-cafe] Re: IO exception not being caught

Joel Reymont joelr1 at gmail.com
Wed Nov 16 09:27:38 EST 2005


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
>

--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list