[Haskell-cafe] Exceptions
Ryan Ingram
ryani.spam at gmail.com
Thu Sep 18 00:54:13 EDT 2008
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 <marco-oweber at gmx.de> wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list