Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-18 Thread Sterling Clover

On Oct 18, 2010, at 6:31 AM, Michael Snoyman wrote:

 Thank you for the offer, but I don't think I'm in a position to take
 over maintainership of another library. However, I think that my
 original suggestion of moving all of the exception-handling functions
 into the type class itself would solve the current issue; is there a
 reason not to do so? I'm still not sure what to do about ContT.

As I posted some time ago, the scheme community has long know that genuine 
unwind-protect (i.e. bracket) is impossible in the presence of call/CC. I 
suggest that the instance simply be removed from the catchIO libraries to avoid 
confusion, and that the reason for its omission be documented.

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


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-18 Thread Sterling Clover
On Mon, Oct 18, 2010 at 8:50 AM, Michael Snoyman mich...@snoyman.com wrote:

 The point here is that we want to treat these things very differently.
 Just take a look at the runHandler code in the Yesod.Handler module:
 runtime exceptions need to be wrapped up in an internal server error,
 whereas Left values from the ErrorT get cased on. I understand
 that all of this could be done with extensible exceptions, but that's
 really just taking something which is currently explicit and
 type-checkable and making it implicit. It really does seem to me to be
 a typical dynamic-versus-static issue.

I fail to see how this is a dynamic-static issue. You're already
forced to catch exceptions and wrap them in a MLeft, and then later
you force the MLeft and MRight values in to a uniform representation
which you then case on. Catching a special exception type for exit and
forcing it into the same ultimate union representation doesn't seem
conceptually any more difficult, and in fact removes the need to
reason about two types of exceptions throughout the rest of the code
base.

I've got a large project that is based on a transformer stack over IO,
and one of my ongoing regrets has been that I went with Either as well
as extensible exceptions -- there's never been a genuine payoff, and
there have been more than a few headaches.

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


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-17 Thread Antoine Latter
On Sun, Oct 17, 2010 at 1:04 PM, Arie Peterson ar...@xs4all.nl wrote:
 On Thu, 14 Oct 2010 12:01:59 +0200, Michael Snoyman
 mich...@snoyman.com wrote:
 [...] which I believe is a flawed
 design in the MonadCatchIO-transformers package. Here are my thoughts
 on this and what I think needs to be done to fix it.

 [...]

 Try running the code with each version of go uncommented. In the first
 two, sequel called gets printed. However, in the third, it does not.
 The reason is short-circuiting: if we remember from the definition of
 finally, there are two cases we account for. If an exception is
 called, catch addresses it. If not, we assume that the next line will
 be called. However, in the presence of short-circuiting monads like
 ErrorT, that line of code will never get called!

 Yes. That is the behaviour I would expect.

 There are two kinds of exceptional values in, for instance, 'ErrorT e
 IO a':
 • IO exceptions, in the underlying monad 'IO';
 • error values of type 'e', in the monad transformer 'ErrorT e'.
 The MonadCatchIO instance for ErrorT deals with the first kind only.
 Catching IO exceptions, and cleaning up after them, is what MonadCatchIO
 was invented for. I feel that I should not decide for all users how
 these two layers of exceptions should interact; keeping the MonadCatchIO
 instance oblivious to the underlying monad as much as possible seems
 like the safest/most general thing to do.

 Meanwhile, I can see why you would want 'finally' to also catch the
 ErrorT errors, in your example, and circumvent the short-circuiting.
 However, I'm not convinced that this is always the right (expected, most
 useful, ...) behaviour. Maybe I just need more convincing :-).


I think the big thing I would look for is that the second argument to
'finally' always run (barring calls to System.Exit or the universe
ending or whatever). Otherwise I wouldn't expect any other interaction
with the 'Left' half of ErrorT.

For example I wouldn't expect the 'error' half of 'try' to be run on
Left, but I would expect the cleanup tasks in 'bracket' to be
executed. Otherwise the function just isn't useful.

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


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-14 Thread Antoine Latter
On Thu, Oct 14, 2010 at 7:15 AM, Michael Snoyman mich...@snoyman.com wrote:
 By the way, here is how I would implement the ErrorT MonadCatchIO instance:

 instance (MonadCatchIO m, Error e) = MonadCatchIO (ErrorT e m) where
  m `catch` f   = mapErrorT (\m' - m' `catch` \e - runErrorT $ f e) m
  block         = mapErrorT block
  unblock       = mapErrorT unblock
  bracket before after thing = block $ do
    a - before
    unblock $ thing a `finally` after a
  bracket_ before after thing = block $ do
    _ - before
    unblock $ thing `finally` after
  finally thing after = mapErrorT (`finally` runErrorT after) thing

 By using finally inside of the definitions of bracket, bracket_ and
 finally, we can ensure that if there is any special monad underneath
 our ErrorT, the cleanup function will still run.

 Michael


A while back I wrote a small package built on MonadCatchIO to give the
equivalent of alloca and the like[1].

I haven't used it much because I couldn't convince myself that the
resources would eventually be freed in a monad with non-standard
control flow (such as the continuation based iteratee-0.4[2]).

Antoine

[1] 
http://hackage.haskell.org/packages/archive/MonadCatchIO-mtl-foreign/0.1/doc/html/Control-Monad-CatchIO-Foreign.html

[2] http://hackage.haskell.org/package/iteratee
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-14 Thread Michael Snoyman
On Thu, Oct 14, 2010 at 4:28 PM, Antoine Latter aslat...@gmail.com wrote:
 On Thu, Oct 14, 2010 at 7:15 AM, Michael Snoyman mich...@snoyman.com wrote:
 By the way, here is how I would implement the ErrorT MonadCatchIO instance:

 instance (MonadCatchIO m, Error e) = MonadCatchIO (ErrorT e m) where
  m `catch` f   = mapErrorT (\m' - m' `catch` \e - runErrorT $ f e) m
  block         = mapErrorT block
  unblock       = mapErrorT unblock
  bracket before after thing = block $ do
    a - before
    unblock $ thing a `finally` after a
  bracket_ before after thing = block $ do
    _ - before
    unblock $ thing `finally` after
  finally thing after = mapErrorT (`finally` runErrorT after) thing

 By using finally inside of the definitions of bracket, bracket_ and
 finally, we can ensure that if there is any special monad underneath
 our ErrorT, the cleanup function will still run.

 Michael


 A while back I wrote a small package built on MonadCatchIO to give the
 equivalent of alloca and the like[1].

 I haven't used it much because I couldn't convince myself that the
 resources would eventually be freed in a monad with non-standard
 control flow (such as the continuation based iteratee-0.4[2]).

I think proper exception control in monad transformer stacks is
something too important to simply give up on. It seems to me that the
MonadCatchIO family is broken, and that the maintainer isn't
interested in fixing it. Given that, perhaps we need to design a new
approach that works properly and is thoroughly tested, and perhaps
deprecate the MonadCatchIO family of packages so as not to leave a
stumbling block for people trying to do proper exception handling.

Did you have particular reasons why you thought the resources would
not be freed correctly Antoine? I'd love any insight you have on this.

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


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-14 Thread Antoine Latter
On Thu, Oct 14, 2010 at 10:20 AM, Michael Snoyman mich...@snoyman.com wrote:

 Did you have particular reasons why you thought the resources would
 not be freed correctly Antoine? I'd love any insight you have on this.


I didn't have a good reason at the time, but your email above
crystallized it for me - it's that that the MonadCatchIO package
doesn't provide the things I need as primitives. Here's my
implementation of allocaBytes:

 allocaBytes :: (MonadCatchIO m) = Int - (Ptr a - m b) - m b
 allocaBytes size = bracket (liftIO $ F.mallocBytes size) (liftIO . F.free)

As you've described above, if someone is using this in ErrorT (or even
MaybeT) I can't promise that F.free is ever run:

 bracket :: MonadCatchIO m = m a - (a - m b) - (a - m c) - m c
 bracket before after thing =
 block (do a - before
   r - unblock (thing a) `onException` after a
   _void $ after a
   return r)

Because the 'do' runs in 'ErrorT', then nothing promises that the line
_void $ after a is run.

If there are one or two primitives we can add to MonadCatchIO to make
it so bracket and finally can be implemented safely I'm all for it.
Maybe the simple thing is to just lift them all into the class, but
I'm hoping there is a better way to describe what we want.

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


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-14 Thread Michael Snoyman
On Thu, Oct 14, 2010 at 8:10 PM, Antoine Latter aslat...@gmail.com wrote:
 On Thu, Oct 14, 2010 at 10:20 AM, Michael Snoyman mich...@snoyman.com wrote:

 Did you have particular reasons why you thought the resources would
 not be freed correctly Antoine? I'd love any insight you have on this.


 I didn't have a good reason at the time, but your email above
 crystallized it for me - it's that that the MonadCatchIO package
 doesn't provide the things I need as primitives. Here's my
 implementation of allocaBytes:

 allocaBytes :: (MonadCatchIO m) = Int - (Ptr a - m b) - m b
 allocaBytes size = bracket (liftIO $ F.mallocBytes size) (liftIO . F.free)

 As you've described above, if someone is using this in ErrorT (or even
 MaybeT) I can't promise that F.free is ever run:

 bracket :: MonadCatchIO m = m a - (a - m b) - (a - m c) - m c
 bracket before after thing =
     block (do a - before
               r - unblock (thing a) `onException` after a
               _void $ after a
               return r)

 Because the 'do' runs in 'ErrorT', then nothing promises that the line
 _void $ after a is run.

 If there are one or two primitives we can add to MonadCatchIO to make
 it so bracket and finally can be implemented safely I'm all for it.
 Maybe the simple thing is to just lift them all into the class, but
 I'm hoping there is a better way to describe what we want.

I thought a bit about this, and I believe the only extra primitive we
need is one of bracket, bracket_ or finally. I also noticed the
exception-transformers package[1], which seems to be a good
replacement for MonadCatchIO. I contacted the author about adding a
MonadBracket typeclass, and he said he'll try to get to it. I'm
planning on making that my replacement for MonadCatchIO (assuming it
turns out correctly), and if so I'd recommend others do the same.

Michael

[1] http://hackage.haskell.org/package/exception-transformers-0.2
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-14 Thread Antoine Latter
On Thu, Oct 14, 2010 at 1:28 PM, Michael Snoyman mich...@snoyman.com wrote:

 I thought a bit about this, and I believe the only extra primitive we
 need is one of bracket, bracket_ or finally. I also noticed the
 exception-transformers package[1], which seems to be a good
 replacement for MonadCatchIO. I contacted the author about adding a
 MonadBracket typeclass, and he said he'll try to get to it. I'm
 planning on making that my replacement for MonadCatchIO (assuming it
 turns out correctly), and if so I'd recommend others do the same.


Ah!

I didn't notice at first that the Exception type class was simply
re-exported from base. At first glance, that package looked like
entirely too much for what I wanted.


 [1] http://hackage.haskell.org/package/exception-transformers-0.2


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


Re: [Haskell-cafe] Re: MonadCatchIO, finally and the error monad

2010-10-14 Thread Michael Snoyman
On Thu, Oct 14, 2010 at 11:13 PM, Antoine Latter aslat...@gmail.com wrote:
 On Thu, Oct 14, 2010 at 1:28 PM, Michael Snoyman mich...@snoyman.com wrote:

 I thought a bit about this, and I believe the only extra primitive we
 need is one of bracket, bracket_ or finally. I also noticed the
 exception-transformers package[1], which seems to be a good
 replacement for MonadCatchIO. I contacted the author about adding a
 MonadBracket typeclass, and he said he'll try to get to it. I'm
 planning on making that my replacement for MonadCatchIO (assuming it
 turns out correctly), and if so I'd recommend others do the same.


 Ah!

 I didn't notice at first that the Exception type class was simply
 re-exported from base. At first glance, that package looked like
 entirely too much for what I wanted.

For a while now I've had the idea of inverting monads: flipping them
inside out so that we can automatically apply any of the special
IO-specific functions to them. I always got caught when implementing
Reader and State, but last night I had a break-through and finally got
it to work. For the moment, the code is up in my neither repo on
github[1], and it has a fairly complete test suite[2].

It's a pretty complicated implementation, since it needs to be generic
enough to address a wide variety of monads, but I'm fairly certain
that the theoretical foundations are sound. I intend to write a full
blog post to explain the idea. With this, I have been able to
implement catch, finally, bracket, alloca, allocaBytes and
withForeignPtr simply by calling the standard IO-specific functions.

I'm excited about this approach: I think it has the possibility to
liberate us from a lot of tedious, error-prone code.

Michael

[1] http://github.com/snoyberg/neither/blob/master/Control/Monad/Invert.hs
[2] http://github.com/snoyberg/neither/blob/master/runtests.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe