
Hello, I think it'd be nice if the compiler could warn me if there are any exceptions which I'm not catching, similar to checked exceptions in Java. Does anyone know of a possibility to do that in Haskell? Adrian

I don't really think this is possible: consider asynchronous
exceptions and throwTo.
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception...
Since it can throw just *any* exception into thread. And this thread
might not be aware that anyone can throw him anything. Therefore it is
not possible to catch it while compiling it's code.
But Maybe I'm Just wrong.
Christopher Skrzętnicki
2008/7/27 Adrian Neumann
Hello,
I think it'd be nice if the compiler could warn me if there are any exceptions which I'm not catching, similar to checked exceptions in Java. Does anyone know of a possibility to do that in Haskell?
Adrian
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

aneumann:
Hello,
I think it'd be nice if the compiler could warn me if there are any exceptions which I'm not catching, similar to checked exceptions in Java. Does anyone know of a possibility to do that in Haskell?
Adrian
You could provide exception-safe wrappers for the functions you use, that catch any exception and flatten it to an Either type (or something similar). Then GHC's usual coverage checking will enforce the handling. import qualified System.IO import Control.Exception maybeReadFile :: FilePath -> IO (Maybe String) maybeReadFile f = handle (\_ -> return Nothing) (Just `fmap` System.IO.readFile f) {- *A> maybeReadFile "/tmp/DOESNOTEXIST" Nothing -} main = do mf <- maybeReadFile "DOESNOTEXIST" case mf of Nothing -> return () Just s -> print s The ability to control exceptions seems like something we should have more solutions for. -- Don

On Sun, 27 Jul 2008, Adrian Neumann wrote:
Hello,
I think it'd be nice if the compiler could warn me if there are any exceptions which I'm not catching, similar to checked exceptions in Java. Does anyone know of a possibility to do that in Haskell?
Please refer to the long "extensible extension" thread: http://www.haskell.org/pipermail/libraries/2008-July/010095.html In my posts I sketched possibilities to do that.

On Sun, Jul 27, 2008 at 07:23:14PM +0200, Adrian Neumann wrote:
Hello,
I think it'd be nice if the compiler could warn me if there are any exceptions which I'm not catching, similar to checked exceptions in Java. Does anyone know of a possibility to do that in Haskell?
He, I have found a use case for your request: from network inet_addr :: String -> IO HostAddress inet_addr ipstr = do withCString ipstr $ \str -> do had <- c_inet_addr str if had == -1 then ioError (userError ("inet_addr: Malformed address: " ++ ipstr)) else return had -- network byte order from HAppS-Server: host <- Exception.catch (inet_addr uri) -- handles ascii IP numbers (\_ -> getHostByName uri >>= \host -> case hostAddresses host of [] -> return (error "no addresses in host entry") (h:_) -> return h) Very bad because this catches Exceptions thrown by trowTo as well, doesn't it? On the other hand just catching the UserError can be useless if the maintainers decide to throw a custom Exception in the future (which can and should be done in the future when extensible exceptions are standard?) In this case I would miss this update and miss to update the code. If we could only catch exceptions. Using Either would be another choice here. But it would lead to much more code. Anyway It think using Either is better because it can't lead to code as shown above. Another nice use case for Exceptions are timouts as implemented by HAppS as well. However I must conclude that a function call including the code above can just absorb my exception and rethrow another one (or in a worse case continue?) So maybe I have to change the TimOut code to do a forever (throwTo threadId TimOutException) to make sure it quits as fast as possible? This could lead to different trouble. So I think using Either is the best option although there is some more code to write. Marc Weber

Better is this:
data MalformedAddressException = MalformedAddressException String
deriving (Show, Typeable)
throwDynIO x = throwIO (DynException $ toDyn x)
-- in inet_error
... throwDynIO (MalformedAddressException "blah blah") ...
-- in HAppS-Server
... Exception.catchDyn (inet_addr uri) (\(MalformedAddressException s) -> ...)
-- ryan
On Wed, Sep 17, 2008 at 5:51 PM, Marc Weber
On Sun, Jul 27, 2008 at 07:23:14PM +0200, Adrian Neumann wrote:
Hello,
I think it'd be nice if the compiler could warn me if there are any exceptions which I'm not catching, similar to checked exceptions in Java. Does anyone know of a possibility to do that in Haskell?
He, I have found a use case for your request: from network
inet_addr :: String -> IO HostAddress inet_addr ipstr = do withCString ipstr $ \str -> do had <- c_inet_addr str if had == -1 then ioError (userError ("inet_addr: Malformed address: " ++ ipstr)) else return had -- network byte order
from HAppS-Server:
host <- Exception.catch (inet_addr uri) -- handles ascii IP numbers (\_ -> getHostByName uri >>= \host -> case hostAddresses host of [] -> return (error "no addresses in host entry") (h:_) -> return h)
Very bad because this catches Exceptions thrown by trowTo as well, doesn't it?
On the other hand just catching the UserError can be useless if the maintainers decide to throw a custom Exception in the future (which can and should be done in the future when extensible exceptions are standard?)
In this case I would miss this update and miss to update the code. If we could only catch exceptions. Using Either would be another choice here. But it would lead to much more code.
Anyway It think using Either is better because it can't lead to code as shown above.
Another nice use case for Exceptions are timouts as implemented by HAppS as well. However I must conclude that a function call including the code above can just absorb my exception and rethrow another one (or in a worse case continue?) So maybe I have to change the TimOut code to do a forever (throwTo threadId TimOutException) to make sure it quits as fast as possible? This could lead to different trouble.
So I think using Either is the best option although there is some more code to write.
Marc Weber _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Better is this:
data MalformedAddressException = MalformedAddressException String deriving (Show, Typeable)
throwDynIO x = throwIO (DynException $ toDyn x) You are right. Anyway the DynException will not be needed in the future because you can
On Wed, Sep 17, 2008 at 09:54:13PM -0700, Ryan Ingram wrote: throw arbitrary types directly.. But if you change the code the type checker won't fail, you'll keep catching the old user error while the new dyn type is beeing thrown. That's the mess. The only thing to do is whenever you start using inet_addr implement an HUnit test to ensure it still throws a user exception.. That's the only reliable way to get notified if the behaviour changes.. But the strength of haskell is that we don't have to write tests for everything because the type checker will do most work for us.. Another solution would be telling the compiler that the exception beeing caught must be thrown within this thread... But that's not possible with the new SomeException either. So my result is that Exceptions should not be used here (?) or there should be an alternative function.. Is that feasable to have to functions so that you can choose? inet_addr_ThrowEx ? inet_addr_Maybe ? Java would have recignized if the exception type changes from user error to dyn type. Haskell can't :-( Marc Weber
participants (6)
-
Adrian Neumann
-
Don Stewart
-
Henning Thielemann
-
Krzysztof Skrzętnicki
-
Marc Weber
-
Ryan Ingram