Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-12 Thread Michael Snoyman
When I implemented this stuff yesterday, I included `Deep` variants for
each function which used NFData. I'm debating whether I think the right
recommendation is to, by default, use the `async`/NFData versions of catch,
handle, and try, or to have them as separate functions.

I wrote up the blog post, both on the Yesod blog[1] and School of
Haskell[2]. The latter's a bit easier to use since it includes active code
snippets.

[1] http://www.yesodweb.com/blog/2013/07/catching-all-exceptions
[2]
https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions


On Fri, Jul 12, 2013 at 4:03 AM, John Lato jwl...@gmail.com wrote:

 I agree that how the exception was thrown is more interesting than the
 type.  I feel like there should be a way to express the necessary
 information via the type system, but I'm not convinced it's easy (or even
 possible).

 Another issue to be aware of is that exceptions can be thrown from pure
 code, so if you don't fully evaluate your return value an exception can be
 thrown later, outside the catch block.  In practice this usually means an
 NFData constraint, or some other constraint for which you can guarantee
 evaluation.

 In the past I've been pretty vocal about my opposition to exceptions.
  It's still my opinion that they do not make it easy to reason about
 exceptional conditions.  Regardless, as Haskell has them and uses them, I'd
 like to see improvements if possible.  So if anyone is exploring the design
 space, I'd be willing to participate.


 On Fri, Jul 12, 2013 at 12:57 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Jul 11, 2013 at 6:07 PM, Felipe Almeida Lessa 
 felipe.le...@gmail.com wrote:

 On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  The only
  approach that handles the situation correctly is John's separate thread
  approach (tryAll3).

 I think you meant tryAll2 here.  Got me confused for some time =).

 Cheers,

 --
 Felipe.


 Doh, yes, I did, thanks for the clarification.

 After playing around with this a bit, I was able to get an implementation
 of try, catch, and handle which work for any non-async exception, in monad
 transformers which are instances of MonadBaseControl (from monad-control).
 I'll try to write up my thoughts in something more coherent, likely a blog
 post.

 Michael



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread Michael Snoyman
On Thu, Jul 11, 2013 at 3:44 AM, John Lato jwl...@gmail.com wrote:

 Hi Michael,

 I don't think those are particularly niche cases, but I still think this
 is a bad approach to solving the problem.  My reply to Erik explicitly
 covers the worker thread case, and for running arbitrary user code (as in
 your top line) it's even simpler: just fork a new thread for the user code.
  You can use the async package or similar to wrap this, so it doesn't even
 add any LOCs.

 What I think is particularly niche is not being able to afford the cost of
 another fork, but I strongly doubt that's the case for Warp.

 The reason I think this is a bad design is twofold: first maintaining a
 list of exclusions like this (whether it's consolidated in a function or
 part of the exception instance) seems rather error-prone and increases the
 maintenance burden for very little benefit IMHO.

 Besides, it's still not correct.  What if you're running arbitrary user
 code that forks its own threads?  Then that code's main thread could get a
 BlockedIndefinitelyOnMVar exception that really shouldn't escape the user
 code, but with this approach it'll kill your worker thread anyway.  Or even
 malicious/brain-damaged code that does myThreadId = killThread?

 I like Ertugrul's suggestion though.  It wouldn't fix this issue, but it
 would add a lot more flexibility to exceptions.



I've spent some time thinking about this, and I'm beginning to think the
separate thread approach is in fact the right way to solve this. I think
there's really an important distinction to be made that we've all gotten
close to, but not specifically identified: the exception type itself isn't
really what we're interested, it's how that exception was thrown which is
interesting. I've put together an interesting demonstration[1].

The test I've created is that a worker thread is spawned. In the worker
thread, we run an action and wrap it in a tryAll function. Meanwhile, in
the main thread, we try to read a file and, when it fails, throw that
IOException to the worker thread. In this case, we want the worker thread
to halt execution immediately. With the naive try implementation (tryAll1)
this will clearly not happen, since the async exception will be caught as
if the subaction itself threw the exception. The more intelligent tryAll3
does the same thing, since it is viewing the thrown exception as
synchronous based on its type, when in reality it was thrown as an async
exception.[2] The only approach that handles the situation correctly is
John's separate thread approach (tryAll3). The reason is that it is
properly differentiating based on how the exception was thrown.

I'm going to play around with this a bit more; in particular, I want to see
how this works with monad transformer stacks. But I at least feel like I
have a slightly better conceptual grasp on what's going on here. Thanks for
pointing this out John.

Michael

[1] https://gist.github.com/snoyberg/5975592
[2] You could also do the reverse: thrown an async exception synchronously,
and similarly get misleading results.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread Felipe Almeida Lessa
On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com wrote:
 The only
 approach that handles the situation correctly is John's separate thread
 approach (tryAll3).

I think you meant tryAll2 here.  Got me confused for some time =).

Cheers,

--
Felipe.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread Michael Snoyman
On Thu, Jul 11, 2013 at 6:07 PM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  The only
  approach that handles the situation correctly is John's separate thread
  approach (tryAll3).

 I think you meant tryAll2 here.  Got me confused for some time =).

 Cheers,

 --
 Felipe.


Doh, yes, I did, thanks for the clarification.

After playing around with this a bit, I was able to get an implementation
of try, catch, and handle which work for any non-async exception, in monad
transformers which are instances of MonadBaseControl (from monad-control).
I'll try to write up my thoughts in something more coherent, likely a blog
post.

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-11 Thread John Lato
I agree that how the exception was thrown is more interesting than the
type.  I feel like there should be a way to express the necessary
information via the type system, but I'm not convinced it's easy (or even
possible).

Another issue to be aware of is that exceptions can be thrown from pure
code, so if you don't fully evaluate your return value an exception can be
thrown later, outside the catch block.  In practice this usually means an
NFData constraint, or some other constraint for which you can guarantee
evaluation.

In the past I've been pretty vocal about my opposition to exceptions.  It's
still my opinion that they do not make it easy to reason about exceptional
conditions.  Regardless, as Haskell has them and uses them, I'd like to see
improvements if possible.  So if anyone is exploring the design space, I'd
be willing to participate.


On Fri, Jul 12, 2013 at 12:57 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Jul 11, 2013 at 6:07 PM, Felipe Almeida Lessa 
 felipe.le...@gmail.com wrote:

 On Thu, Jul 11, 2013 at 10:56 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  The only
  approach that handles the situation correctly is John's separate thread
  approach (tryAll3).

 I think you meant tryAll2 here.  Got me confused for some time =).

 Cheers,

 --
 Felipe.


 Doh, yes, I did, thanks for the clarification.

 After playing around with this a bit, I was able to get an implementation
 of try, catch, and handle which work for any non-async exception, in monad
 transformers which are instances of MonadBaseControl (from monad-control).
 I'll try to write up my thoughts in something more coherent, likely a blog
 post.

 Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Ertugrul Söylemez
Michael Snoyman mich...@snoyman.com wrote:

 shouldBeCaught :: SomeException - Bool

 One first stab at such a function would be to return `False` for
 AsyncException and Timeout, and `True` for everything else, but I'm
 not convinced that this is sufficient. Are there any thoughts on the
 right approach to take here?

I think there is no one right approach.  However, if you add such a
function to the exception library, it really belongs into the Exception
type class with the following type:

shouldBeCaught :: (Exception e) = e - Bool

However, a better approach is to have exception tags.  In most cases you
don't want to catch killThread's or timeout's exception, but you do want
to catch all error exceptions:

data Tag = Error | Abort | TryAgain | {- ... -} | Other String
deriving (Data, Eq, Ord, Read, Show, Typeable)

instance IsString Tag where
fromString t = Other t

This could then manifest in the following two functions in the Exception
type class:

hasTag :: (Exception e) = Tag - e - Bool
tagsOf :: (Exception e) = e - [Tag]

Then exception catchers (functions that risk swallowing important
exceptions) could filter by type and tag.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread John Lato
I think 'shouldBeCaught' is more often than not the wrong thing.  A
whitelist of exceptions you're prepared to handle makes much more sense
than excluding certain operations.  Some common whitelists, e.g. filesystem
exceptions or network exceptions, might be useful to have.

I like Ertugrul's suggestion a lot, however it seems a bit more invasive.
 If we want to do that work, we could also restructure the wired-in
exceptions so they're more hierarchical.  There are some top-level
exceptions we can get by type, such as ArithException, but sadly many
interesting and useful exceptions are lumped together under IOException.


On Wed, Jul 10, 2013 at 4:29 PM, Ertugrul Söylemez e...@ertes.de wrote:

 Michael Snoyman mich...@snoyman.com wrote:

  shouldBeCaught :: SomeException - Bool
 
  One first stab at such a function would be to return `False` for
  AsyncException and Timeout, and `True` for everything else, but I'm
  not convinced that this is sufficient. Are there any thoughts on the
  right approach to take here?

 I think there is no one right approach.  However, if you add such a
 function to the exception library, it really belongs into the Exception
 type class with the following type:

 shouldBeCaught :: (Exception e) = e - Bool

 However, a better approach is to have exception tags.  In most cases you
 don't want to catch killThread's or timeout's exception, but you do want
 to catch all error exceptions:

 data Tag = Error | Abort | TryAgain | {- ... -} | Other String
 deriving (Data, Eq, Ord, Read, Show, Typeable)

 instance IsString Tag where
 fromString t = Other t

 This could then manifest in the following two functions in the Exception
 type class:

 hasTag :: (Exception e) = Tag - e - Bool
 tagsOf :: (Exception e) = e - [Tag]

 Then exception catchers (functions that risk swallowing important
 exceptions) could filter by type and tag.


 Greets,
 Ertugrul

 --
 Not to be or to be and (not to be or to be and (not to be or to be and
 (not to be or to be and ... that is the list monad.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Erik Hesselink
Hi Michael,

We do this as well. In addition to AsyncException, we ignore
BlockedIndefinitelyOnSTM, BlockedIndefinitelyOnMVar and Deadlock. I'm
not sure you can ignore Timeout, since the type is not exported from
System.Timeout. I'm not sure how to classify these, though. They are
in some sense non-recoverable: restarting whatever the thread was
doing is not the right thing to do.

Erik

On Wed, Jul 10, 2013 at 8:28 AM, Michael Snoyman mich...@snoyman.com wrote:
 There's a pattern that arises fairly often: catching every exception thrown
 by code. The naive approach is to do something like:

 result - try someCode
 case result of
 Left (e :: SomeException) - putStrLn $ It failed:  ++ show e
 Right realValue - useRealValue

 This seems perfectly valid, except that it catches a number of exceptions
 which seemingly should not be caught. In particular, it catches the async
 exceptions used by both killThread and timeout.

 I think it's fair to say that there's not going to be a single function that
 solves all cases correctly, but it is a common enough situation that people
 need to write code that resumes work in the case of an exception that I
 think we need to either have some guidelines for the right approach here, or
 perhaps even a utility function along the lines of:

 shouldBeCaught :: SomeException - Bool

 One first stab at such a function would be to return `False` for
 AsyncException and Timeout, and `True` for everything else, but I'm not
 convinced that this is sufficient. Are there any thoughts on the right
 approach to take here?

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Erik Hesselink
On Wed, Jul 10, 2013 at 10:39 AM, John Lato jwl...@gmail.com wrote:
 I think 'shouldBeCaught' is more often than not the wrong thing.  A
 whitelist of exceptions you're prepared to handle makes much more sense than
 excluding certain operations.  Some common whitelists, e.g. filesystem
 exceptions or network exceptions, might be useful to have.

You'd think that, but there are common use cases. For example, if you
have a queue of work items, and a thread (or threads) processing them,
it is useful to catch all exceptions of these threads. You can then
log the exception, remove the item from the queue and put it in some
error bucket, and continue on to the next item. The same goes for e.g.
socket listening threads etc.

The thing here is that you are *not* actually handling the specific
exception, but instead failing gracefully. But you still want to be
able to kill the worker threads, and you don't want to handle
exceptions that you cannot recover from even by moving on to the next
work item.

Erik

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Alberto G. Corona
Don´t tried it and probably it does not even compile, but a possibility
could be along these lines:


catchExcept excepts handle e= do
   if not . null $ filter ( \(SomeException e') - typeOf e= typeOf e')
excepts
then throw e
else handle e

use:

u= undefined

excluded=  [SomeException (u :: AsyncException), SomeException (u
::ArithException)]

sample= expr `catchExcept` excluded $ do




2013/7/10 Erik Hesselink hessel...@gmail.com

 Hi Michael,

 We do this as well. In addition to AsyncException, we ignore
 BlockedIndefinitelyOnSTM, BlockedIndefinitelyOnMVar and Deadlock. I'm
 not sure you can ignore Timeout, since the type is not exported from
 System.Timeout. I'm not sure how to classify these, though. They are
 in some sense non-recoverable: restarting whatever the thread was
 doing is not the right thing to do.

 Erik

 On Wed, Jul 10, 2013 at 8:28 AM, Michael Snoyman mich...@snoyman.com
 wrote:
  There's a pattern that arises fairly often: catching every exception
 thrown
  by code. The naive approach is to do something like:
 
  result - try someCode
  case result of
  Left (e :: SomeException) - putStrLn $ It failed:  ++ show e
  Right realValue - useRealValue
 
  This seems perfectly valid, except that it catches a number of exceptions
  which seemingly should not be caught. In particular, it catches the async
  exceptions used by both killThread and timeout.
 
  I think it's fair to say that there's not going to be a single function
 that
  solves all cases correctly, but it is a common enough situation that
 people
  need to write code that resumes work in the case of an exception that I
  think we need to either have some guidelines for the right approach
 here, or
  perhaps even a utility function along the lines of:
 
  shouldBeCaught :: SomeException - Bool
 
  One first stab at such a function would be to return `False` for
  AsyncException and Timeout, and `True` for everything else, but I'm not
  convinced that this is sufficient. Are there any thoughts on the right
  approach to take here?
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Alberto.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread John Lato
On Wed, Jul 10, 2013 at 5:02 PM, Erik Hesselink hessel...@gmail.com wrote:

 On Wed, Jul 10, 2013 at 10:39 AM, John Lato jwl...@gmail.com wrote:
  I think 'shouldBeCaught' is more often than not the wrong thing.  A
  whitelist of exceptions you're prepared to handle makes much more sense
 than
  excluding certain operations.  Some common whitelists, e.g. filesystem
  exceptions or network exceptions, might be useful to have.

 You'd think that, but there are common use cases. For example, if you
 have a queue of work items, and a thread (or threads) processing them,
 it is useful to catch all exceptions of these threads. You can then
 log the exception, remove the item from the queue and put it in some
 error bucket, and continue on to the next item. The same goes for e.g.
 socket listening threads etc.

 The thing here is that you are *not* actually handling the specific
 exception, but instead failing gracefully. But you still want to be
 able to kill the worker threads, and you don't want to handle
 exceptions that you cannot recover from even by moving on to the next
 work item.


I think that's a particularly niche use case.  We have some similar code,
and our approach is to have the thread re-throw (or terminate) after
logging the exception.  There's a separate thread that monitors the thread
pool, and when threads die new ones are spawned to take their place (unless
the thread pool is shutting down, of course).  Spawning a new thread only
happens on an exception and it's cheap anyway, so there's no performance
issue.

As Haskell currently stands trying to sort out thread-control and
fatal-for-real exceptions from other exceptions seems rather fiddly,
unreliable, and prone to change between versions, so I think it's best
avoided.  If there were a standard library function to do it I might use
it, but I wouldn't want to maintain it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Michael Snoyman
On Wed, Jul 10, 2013 at 1:01 PM, John Lato jwl...@gmail.com wrote:

 On Wed, Jul 10, 2013 at 5:02 PM, Erik Hesselink hessel...@gmail.comwrote:

 On Wed, Jul 10, 2013 at 10:39 AM, John Lato jwl...@gmail.com wrote:
  I think 'shouldBeCaught' is more often than not the wrong thing.  A
  whitelist of exceptions you're prepared to handle makes much more sense
 than
  excluding certain operations.  Some common whitelists, e.g. filesystem
  exceptions or network exceptions, might be useful to have.

 You'd think that, but there are common use cases. For example, if you
 have a queue of work items, and a thread (or threads) processing them,
 it is useful to catch all exceptions of these threads. You can then
 log the exception, remove the item from the queue and put it in some
 error bucket, and continue on to the next item. The same goes for e.g.
 socket listening threads etc.

 The thing here is that you are *not* actually handling the specific
 exception, but instead failing gracefully. But you still want to be
 able to kill the worker threads, and you don't want to handle
 exceptions that you cannot recover from even by moving on to the next
 work item.


 I think that's a particularly niche use case.  We have some similar code,
 and our approach is to have the thread re-throw (or terminate) after
 logging the exception.  There's a separate thread that monitors the thread
 pool, and when threads die new ones are spawned to take their place (unless
 the thread pool is shutting down, of course).  Spawning a new thread only
 happens on an exception and it's cheap anyway, so there's no performance
 issue.

 As Haskell currently stands trying to sort out thread-control and
 fatal-for-real exceptions from other exceptions seems rather fiddly,
 unreliable, and prone to change between versions, so I think it's best
 avoided.  If there were a standard library function to do it I might use
 it, but I wouldn't want to maintain it.


Maybe I'm just always working on niche cases then, because I run into this
problem fairly regularly. Almost any time you want to write a library that
will run code it doesn't entirely trust, this situation arises. Examples
include:

   - Writing a web server (like Warp) which can run arbitrary user code.
   Warp must fail gracefully if the user code throws an exception, without
   bringing down the entire server thread.
   - Writing some kind of batch processing job which uses any library which
   may throw an exception. A white list approach would not be sufficient here,
   since we want to be certain that any custom exception types have been
   caught.
   - A system which uses worker threads to do much of its work. You want to
   make certain the worker threads don't unexpectedly die because some
   exception was thrown that you were not aware could be thrown. I use this
   technique extensively in Keter, and in fact some work I'm doing on that
   code base now is what triggered this email.

I think that, overall, Ertugrul's suggestion is probably the right one: we
should be including richer information in the `Exception` typeclass so that
there's no guessing involved, and any custom exception types can explicitly
state what their recovery preference is. In the meanwhile, I think we could
get pretty far by hard-coding some rules about standard exception types,
and making an assumption about all custom exception types (e.g., they *
should* be caught by a catch all exceptions call).

If we combine these two ideas, we could have a new package on Hackage which
defines the right set of tags and provides a `tagsOf` function which works
on any instance of Exception, which uses the assumptions I mentioned in the
previous paragraph. If it's then decided that this is generally useful
enough to be included in the Exception typeclass, we have a straightforward
migration path:

   1. Add the new method to the Exception typeclass, with a default
   implementation that conforms with our assumptions.
   2. For any of the special standard exception types (e.g.,
   AsyncException), override that default implementation.
   3. Modify the external package to simply re-export the new method when
   using newer versions of base, using conditional compilation.
   4. Any code written against that external package would work with both
   current and future versions of base.
   5. The only incompatibility would be if someone writes code which
   overrides the typeclass method; that code would only work with newer bases,
   not current ones.

Any thoughts on this? I'm not sure exactly what would be the right method
to add to the Exception typeclass, but if we can come to consensus on that
and there are no major objections to my separate package proposal, I think
this would be something moving forward on, including a library proposal.

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread kudah
I think that new SomeAsyncException type in base is supposed to make
it possible to ignore all asynchronous exceptions.
https://github.com/ghc/packages-base/blob/master/GHC/IO/Exception.hs#L113

On Wed, 10 Jul 2013 09:28:12 +0300 Michael Snoyman
mich...@snoyman.com wrote:

 There's a pattern that arises fairly often: catching every exception
 thrown by code. The naive approach is to do something like:
 
 result - try someCode
 case result of
 Left (e :: SomeException) - putStrLn $ It failed:  ++ show
 e Right realValue - useRealValue
 
 This seems perfectly valid, except that it catches a number of
 exceptions which seemingly should *not* be caught. In particular, it
 catches the async exceptions used by both killThread and timeout.
 
 I think it's fair to say that there's not going to be a single
 function that solves all cases correctly, but it is a common enough
 situation that people need to write code that resumes work in the
 case of an exception that I think we need to either have some
 guidelines for the right approach here, or perhaps even a utility
 function along the lines of:
 
 shouldBeCaught :: SomeException - Bool
 
 One first stab at such a function would be to return `False` for
 AsyncException and Timeout, and `True` for everything else, but I'm
 not convinced that this is sufficient. Are there any thoughts on the
 right approach to take here?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread Ertugrul Söylemez
Michael Snoyman mich...@snoyman.com wrote:

 Any thoughts on this? I'm not sure exactly what would be the right
 method to add to the Exception typeclass, but if we can come to
 consensus on that and there are no major objections to my separate
 package proposal, I think this would be something moving forward on,
 including a library proposal.

Just a minor note:  Add both `hasTag` and `tagsOf` to the type class,
because `hasTag` may use something much more efficient than `elem` like
pattern matching or `Data.Set.member`.  I'm not even sure we really need
`tagsOf`.


Greets,
Ertugrul

-- 
Key-ID: E5DD8D11 Ertugrul Soeylemez e...@ertes.de
FPrint: BD28 3E3F BE63 BADD 4157  9134 D56A 37FA E5DD 8D11
Keysrv: hkp://subkeys.pgp.net/


signature.asc
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correct way to catch all exceptions

2013-07-10 Thread John Lato
Hi Michael,

I don't think those are particularly niche cases, but I still think this is
a bad approach to solving the problem.  My reply to Erik explicitly covers
the worker thread case, and for running arbitrary user code (as in your top
line) it's even simpler: just fork a new thread for the user code.  You can
use the async package or similar to wrap this, so it doesn't even add any
LOCs.

What I think is particularly niche is not being able to afford the cost of
another fork, but I strongly doubt that's the case for Warp.

The reason I think this is a bad design is twofold: first maintaining a
list of exclusions like this (whether it's consolidated in a function or
part of the exception instance) seems rather error-prone and increases the
maintenance burden for very little benefit IMHO.

Besides, it's still not correct.  What if you're running arbitrary user
code that forks its own threads?  Then that code's main thread could get a
BlockedIndefinitelyOnMVar exception that really shouldn't escape the user
code, but with this approach it'll kill your worker thread anyway.  Or even
malicious/brain-damaged code that does myThreadId = killThread?

I like Ertugrul's suggestion though.  It wouldn't fix this issue, but it
would add a lot more flexibility to exceptions.


On Wed, Jul 10, 2013 at 6:44 PM, Michael Snoyman mich...@snoyman.comwrote:




 On Wed, Jul 10, 2013 at 1:01 PM, John Lato jwl...@gmail.com wrote:

 On Wed, Jul 10, 2013 at 5:02 PM, Erik Hesselink hessel...@gmail.comwrote:

 On Wed, Jul 10, 2013 at 10:39 AM, John Lato jwl...@gmail.com wrote:
  I think 'shouldBeCaught' is more often than not the wrong thing.  A
  whitelist of exceptions you're prepared to handle makes much more
 sense than
  excluding certain operations.  Some common whitelists, e.g. filesystem
  exceptions or network exceptions, might be useful to have.

 You'd think that, but there are common use cases. For example, if you
 have a queue of work items, and a thread (or threads) processing them,
 it is useful to catch all exceptions of these threads. You can then
 log the exception, remove the item from the queue and put it in some
 error bucket, and continue on to the next item. The same goes for e.g.
 socket listening threads etc.

 The thing here is that you are *not* actually handling the specific
 exception, but instead failing gracefully. But you still want to be
 able to kill the worker threads, and you don't want to handle
 exceptions that you cannot recover from even by moving on to the next
 work item.


 I think that's a particularly niche use case.  We have some similar code,
 and our approach is to have the thread re-throw (or terminate) after
 logging the exception.  There's a separate thread that monitors the thread
 pool, and when threads die new ones are spawned to take their place (unless
 the thread pool is shutting down, of course).  Spawning a new thread only
 happens on an exception and it's cheap anyway, so there's no performance
 issue.

 As Haskell currently stands trying to sort out thread-control and
 fatal-for-real exceptions from other exceptions seems rather fiddly,
 unreliable, and prone to change between versions, so I think it's best
 avoided.  If there were a standard library function to do it I might use
 it, but I wouldn't want to maintain it.


 Maybe I'm just always working on niche cases then, because I run into this
 problem fairly regularly. Almost any time you want to write a library that
 will run code it doesn't entirely trust, this situation arises. Examples
 include:

- Writing a web server (like Warp) which can run arbitrary user code.
Warp must fail gracefully if the user code throws an exception, without
bringing down the entire server thread.
- Writing some kind of batch processing job which uses any library
which may throw an exception. A white list approach would not be sufficient
here, since we want to be certain that any custom exception types have been
caught.
- A system which uses worker threads to do much of its work. You want
to make certain the worker threads don't unexpectedly die because some
exception was thrown that you were not aware could be thrown. I use this
technique extensively in Keter, and in fact some work I'm doing on that
code base now is what triggered this email.

 I think that, overall, Ertugrul's suggestion is probably the right one: we
 should be including richer information in the `Exception` typeclass so that
 there's no guessing involved, and any custom exception types can explicitly
 state what their recovery preference is. In the meanwhile, I think we could
 get pretty far by hard-coding some rules about standard exception types,
 and making an assumption about all custom exception types (e.g., they *
 should* be caught by a catch all exceptions call).

 If we combine these two ideas, we could have a new package on Hackage
 which defines the right set of tags and provides a `tagsOf` function