Re: throwTo block statements considered harmful

2006-12-08 Thread Cat Dancer

The key problem is, at least in the presence of block/unblock, that
Exceptions are never reliably delivered.


Never?  Even in a function which is in a blocking state?


The implementation of asynchronous signals, as described by the paper
Asynchronous exceptions in Haskell
Simon Marlow, Simon Peyton Jones, Andy Moran and John Reppy, PLDI'01.
is fatally inconsistent with the implementation in GHC 6.4 and GHC 6.6 today.


Is it a goal of the GHC developers to offer an implementation of
asynchronous signals which has the features and benefits described in
the original paper?

If the answer is no, then there are a couple points...

A: That the current implementation works differently than the original
paper is important to know, and the library documentation should be
updated to clearly describe what the implementation does and does not
do.

B: Since you are programming in a language which doesn't offer the
semantics of the original paper, and you can implement your algorithm
using an event queue... you can go ahead an implement your algorithm
with an event queue.

The situation doesn't rise to the level of fatal :-) until you have
an algorithm which you're not able to implement with the facilities
provided by GHC.

For example, if the implementation did not reliably deliver an
asynchronous exception when a function was blocking, then that
probably would be a *fatal* flaw, because then there'd be no way to
break out of a blocking function.

Otherwise, we're talking about convenience.  You'd like asynchronous
signals in GHC to offer the features and benefits described in the
original paper, and that's  a reasonable request to ask for, but it
doesn't rise to the level of a fatal flaw.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Re: How to combine Error and IO monads?

2006-12-08 Thread Cat Dancer

On 12/7/06, J. Garrett Morris [EMAIL PROTECTED] wrote:


foo :: ErrorT String IO Int

Since ErrorT String IO Int is not the same as IO, you can't use IO
operations directly.  In this case, you want:

 a - lift getLine

You want:

 r - runErrorT foo



Wow!  I found your help terrific!  Thank you!   Can I give you some money?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Network accept loop with graceful shutdown implementation

2006-12-07 Thread Cat Dancer

On 12/7/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:

Could you add info about where to get your code (or the code) itself to the wiki
 at http://haskell.org/haskellwiki/Concurrency_demos/Graceful_exit ?


OK, I did.


unblock yield is the right code for a safepoint


Be careful.  You are relying on the runtime to wake up the throwing
thread, to let it run long enough to raise the asynchronous exception,
and to have that complete before the thread doing the unblock yield
is resumed.

While a particular Haskell implementation might do all that on a
single processor system, it's hard to see how such a guarantee could
ever be offered on a multiprocessor system.  These days it's common to
buy a computer with a dual core cpu, before long we'll be getting
cpu's with ten cores... and in a few years we'll be seeing hundred
core cpu's.  yield is meaningless on a multiprocessor system.

I'd suggest that if you're using a concurrent language and you find
that the only way you can implement an algorithm is by using yield,
either A) you're wrong and there is a way to implement it without
yield, or B) your concurrent language is deficient and should be
fixed!  :-)
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] How to combine Error and IO monads?

2006-12-07 Thread Cat Dancer

I've read Jeff Newbern's tutorial on monad transformers
(http://www.nomaware.com/monads/html/index.html), but I don't grok it
yet and I can't tell how to get started with this particular
requirement, or even if I need monad transformers for this.

I have a program that performs a series of IO operations, each which
can result in an error or a value.  If a step returns a value I
usually want to pass that value on to the next step, if I get an error
I want to do some error handling but usually want to skip the
remaining steps.

Thus I have a lot of functions with return types like IO (Either
String x), where x might be (), Integer, or some other useful value
type, and a lot of case statements like

 a :: Integer - IO (Either String String)
   (a :: Either String Integer) - some_io_action_returning_integer_or_error
   case a of
 -- got to get from (Either String Integer) to (Either String String)
 Left message - return $ Left message
 -- continue on
 Right i - do_more i

If I was using just Either I know how to get rid of the case statements:

 import Control.Monad.Error

 p :: Integer - Either String Integer
 q :: Integer - Either String String

 r :: Either String String
 r = do
   a - p 3
   b - q a
   return b

which of course is much nicer.  But how do I combine the Error and IO
monads so that r could have the type IO (Either String String)?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to combine Error and IO monads?

2006-12-07 Thread Cat Dancer

And you just rediscovered monad transformers.


Can I use an existing monad transformer like ErrorT for this application?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to combine Error and IO monads?

2006-12-07 Thread Cat Dancer

On 12/7/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Cat Dancer wrote:
 I have a program that performs a series of IO operations, each which
 can result in an error or a value.  If a step returns a value I
 usually want to pass that value on to the next step, if I get an error
 I want to do some error handling but usually want to skip the
 remaining steps.

 Thus I have a lot of functions with return types like IO (Either
 String x), where x might be (), Integer, or some other useful value
 type, and a lot of case statements like

You are on the right track. The point is that (IO (Either String a)) is
a Monad, too. This allows you to write the ever repeating case
statements once and forall:

   newtype ErrorIO a = ErrorIO (IO (Either String a))

   instance Monad ErrorIO where
   return x = return (Right x)
   f = g  = do
   ex - f
   case ex of
   e@(Left _) - return e
   Right x- g x

It happens that you can parametrize this on IO:

   newtype ErrorT m a = ErrorT (m (Either String a))
   typeErrorIO a  = ErrorT IO a

   instance Monad m = Monad (ErrorT m) where ... -- same as above

And you just rediscovered monad transformers.


I think I need to explain how thoroughly clueless I am :)

I'm sure from a single example I could understand what was going on
and elaborate from there.

Let's say I want to get a line from the user, and either return an
integer or an error string using ErrorT.

 import Control.Monad.Error
 import Control.Monad.Trans

 foo :: ??
 foo = do  -- something like this?
   a - getLine
   if length a == 1
 then return 123
 else throwError not a single character

 main = do
   r - ?? foo ??
   print r -- prints Left not a single character or Right 123 ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


'accept' behavior with an asynchronous exception inside of a 'block'

2006-12-06 Thread Cat Dancer

Chris Kuklewicz suggested I direct this question to the developers ^_^

If I use a network accept inside a block:

 block (
...
(clientSocket, sockAddr) - accept serverSocket
...
)

and the 'accept' unblocks a pending asynchronous exception and the
exception gets thrown, does this mean that the 'accept' won't have
accepted a network connection?

Certainly this seems like desirable behavior, since if the 'accept'
call might accept a network connection and *then* raise the
asynchronous exception, the reference to the accepted connection would
be lost.  However I couldn't tell from the library documentation
whether this was intended to be a guarantee of the 'accept' function
or not.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell] Network accept loop with graceful shutdown implementation

2006-12-06 Thread Cat Dancer

I have a prospective implementation of a network accept loop with
graceful shutdown.

This email builds upon the previous discussion Help needed
interrupting accepting a network connection.

In this code, just the accept loop part has been factored out and put
into its own module.  My hope is that if a fully correct version can
be written, it will be useful to other projects.  The source is
available at http://code.catdancer.ws/acceptloop/ and is in the public
domain.

This AcceptLoop module is currently experimental, relying on an
either-or guarantee for interruptible operations... which I don't
know yet whether Haskell implementations provide -- or even intend to
provide.


Chris Kuklewicz provided several critical insights:

* The return value of the 'accept' call can be passed out of the
 accept thread, allowing the code which implements accept with
 graceful shutdown to be separated from the code which handles
 the incoming client connection.

* Inside of a 'block', interruptible operations may not (will not?)
 allow an asynchronous exception to be raised if the operation does
 not block.

* Clarification for me of the desirable property that inside of a
 'block', interruptible operations are either-or: either they allow
 an asynchronous operation to be raised, or they perform their
 operation, but not both.


I made the following design decisions:

In my original implementation, I used a custom datatype to throw a
dynamic asynchronous exception to the thread calling 'accept'.  In
Chris' rewrite, he used 'killThread', which throws a 'ThreadKilled'
asynchronous exception.  I choose to continue to throw (and catch)
only the specific, custom exception for the purpose of breaking out of
the 'accept'.  A robust implementation may need to catch other
exceptions, however the desired behavior of the thread on receiving an
*unexpected* exception may be different, and so I choose to leave
handling of such an unexpected exception unimplemented for now.

Chris uses STM instead of MVar's for communication with the accept
thread.  The challenge of writing code with STM or MVar's in the
presence of asynchronous exceptions is exactly the same: either a call
to 'atomically' or a call to an MVar operation such as 'putMVar' may
allow an asynchronous exception to be raised inside of a 'block', and
the code then needs to deal with that.

It seems to me that MVar's could be implemented in terms of STM, and
so the question is: are MVar's a more natural, higher level
description of the desired semantics in this case, and would
composable transactions be useful?

A key insight is that in this implementation, a separate thread is
used not for the purposes of concurrency, but solely to limit the
scope of the thrown asynchronous exception.  Once a result is
available from the accept thread (either Just an incoming
connection, or Nothing to say that the accept loop has shutdown),
that result can then be used in a concurrent fashion, such as being
handled in a child thread, passed into an STM transaction or written
to a channel, etc.  But there is no need to use composable
transactions *inside* of the AcceptLoop module.

Thus the only reason to use STM instead of MVar's inside the
implementation is if it turns out that STM has the desired either-or
behavior but MVar's don't.

To avoid the unlock (return ()) issue that Chris discovered, this
implementation uses an additional MVar to indicate that a shutdown is
in process.  Thus (if the implementation is correct) the accept loop
will shutdown either because of the MVar flag or by receiving the
asynchronous exception inside of the 'accept'.

To address the issue that Chris noticed of a race condition that new
threads cannot be started in a 'block' state, yet another MVar is set
by the accept thread to indicate that it is now inside of a 'block'
and is ready to receive the asynchronous exception.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] What guarantees (if any) do interruptible operations have in presence of asynchronous exceptions?

2006-12-05 Thread Cat Dancer

From the discussion of Help needed interrupting accepting a network

connection, what we have so far is:

   * To break out of an accept call, an asynchronous exception is needed.

   * The presence of asynchronous exceptions complicates the other code
 used to report if accept completed or was interrupted, whether
 that code is written using MVar's or STM.

Thus the next question is what guarantees, if any, do interruptible
operations possess?

For example, suppose that inside of a block, a putMVar operation was
guaranteed to either interrupt and allow an asynchronous exception to
be raised, or to complete the putMVar operation, but not both.

If this were true, then if you caught an asynchronous exception from
the putMVar operation, you'd know that a value was not put into the
MVar by the operation.

Then it would be easy to program with MVar's in the presence of
asynchronous exceptions.  When you caught an asynchronous exception,
you could set a flag, and then redo the putMVar.

The same question can be asked of other interruptible operations.

For the accept call itself, is it guaranteed (inside of a block)
to either accept a connection, or be interrupted and allow an
asynchronous exception to be raised, but not both?

For STM, is atomically an interruptible operation?  If it is, what
guarantees does it offer in the presence of asynchronous exceptions?
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] What guarantees (if any) do interruptible operations have in presence of asynchronous exceptions?

2006-12-05 Thread Cat Dancer

On 12/5/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:

Making small programs to test these properties is a good sanity check.  For
instance I just leaned that safePoint = unblock ( return () ) does not work.


Maybe if you do something to allocate some memory inside of the unblock?



 If this were true, then if you caught an asynchronous exception from
 the putMVar operation, you'd know that a value was not put into the
 MVar by the operation.

I think that should be a safe assumption when running under block.


I think and should be is nice, how do we find out if it's really
true -- for sure?



 Then it would be easy to program with MVar's in the presence of
 asynchronous exceptions.  When you caught an asynchronous exception,
 you could set a flag, and then redo the putMVar.

If you call that easy then sure.

 For STM, is atomically an interruptible operation?  If it is, what
 guarantees does it offer in the presence of asynchronous exceptions?

block (atomically stm) is interruptible when the operation stm uses retry
and perhaps when it has to be re-attempted due to conflicting updates.  If it
runs without conflict and commits then it cannot be interrupted by an async
exception.

If (atomically stm) is interrupted then it is rolled back and will have had no
visible side effects.


Easy in the sense that the pattern of trying an operation, setting a
flag if an asynchronous exception is raised, and redoing the
operation can be encapsulated in a function.

That function can then be used with any interruptible operation (such
as putMVar, or atomically, or accept) *if* the operation guarantees
that inside of a block it will either perform its operation, or
interrupt and allow an asynchronous to be raised, but not both.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Help needed interrupting accepting a network connection

2006-12-02 Thread Cat Dancer

I'd like to write a server accepting incoming network connections that
can be gracefully shutdown.

When the server is asked to shutdown, it should stop accepting new
connections, finish processing any current connections, and then
terminate.

Clients can retry if they attempt to make a connection and the
connection is refused.  This allows the server to restart seamlessly:
any existing connections are not interrupted, and clients will see at
most a pause while the server restarts.

I am using the model from Simon Marlow's Haskell Web Server (as
updated by Björn Bringert and available at
http://www.cs.chalmers.se/~bringert/darcs/hws/): spawning a
lightweight Haskell child thread for each client connection.

In Control.Exception, I see that operations such as accept are
interruptible by exceptions thrown to the thread, so I can interrupt
an accept with a dynamic exception.


-- create a datatype to use to interrupt the accept
data ExitGracefully = ExitGracefully deriving Typeable


I want to control when I'm paying attention to the ExitGracefully
exception.  I don't want to get the exception when I'm in the middle
of updating a data structure, just in a few controlled points such as
when I'm in an accept.  Reading further in Control.Exception, I see
that I can use block to put off receiving the exception generally,
but accept is an interruptible operation so I don't need to do
anything more to get the exception inside of the accept.


block (
 ...
 result - catchDyn
 (do (clientSocket, addr) - accept sock
 return $ Just clientSocket)
 (\ (e :: ExitGracefully) - return Nothing)


Typing the exception e as an ExitGracefully tells catchDyn that I
only need to catch exceptions of that type.  If the thread has been
thrown a ExitGracefully, result will be Nothing, but if accept
returned with a client connection, result will be Just the
clientSocket.


 case result of

   Nothing - do { putStrLn accept loop exiting;
   putMVar acceptLoopDone ()
 }

   Just clientSocket -


So far so good.

I also want to keep track of when the threads spawned to handle the
client connections are finished, so I use the code from the
Terminating the program section of the Control.Concurrent
documentation to keep a list of MVar's indicating when the child
threads are done:


childDone - newEmptyMVar
childDoneList - takeMVar childrenDone
putMVar childrenDone (childDone : childDoneList)


then I fork a child thread to handle the connection:


clientHandle - socketToHandle clientSocket ReadWriteMode
forkIO $ handleConnection childDone clientHandle


handleConnection runs inside the child thread, communicating with
the client.  When done, it closes the clientHandle, and does an
putMVar childDone () to say that it done.

Except that, whoops, the takeMVar in the accept thread code which updates the
childrenDone MVar is also interruptible.  So now I'm getting an
interruption right where I don't want it, when I'm updating my data
structure.

Only the accept thread is thrown the ExitGracefully exception, so one
thought I had was that I could move those three lines which update the
childrenDone MVar into the child thread.  But this introduces a race
condition: as the server was shutting down, it could look at the
childrenDone list and see that it was empty, before the child thread
had a chance to start running and update the data structure to say
that there was another child that needed to be waited for.

Or, updating the childrenDone MVar could be done in its own thread,
which again would protect it from the ExitGracefully exception...
except that how would the accept thread wait for that thread... except
by using an MVar?  Oops, again.

Any ideas?

For reference sake here's the complete implementation.  (This code is
in the public domain... in case it would be useful to anyone else).

Thank you,

Cat



-- A ConnectionHandler is a function which handles an incoming
-- client connection.  The handler is run in its own thread, and is
-- passed a handle to the client socket.  The handler does whatever
-- communication it wants to do with the client, and when it returns,
-- the client socket handle is closed and the thread terminates.
-- A list of active handlers is kept, and the client connection is
-- also marked as finished when the handler returns.

type ConnectionHandler = Handle - IO ()


example_connection_handler :: ConnectionHandler

example_connection_handler handle = do
  hPutStrLn handle Hello.
  hPutStrLn handle Goodbye.


type ChildrenDone = MVar [MVar ()]

data ExitGracefully = ExitGracefully deriving Typeable


waitForChildren :: ChildrenDone - IO ()

waitForChildren childrenDone = do
  cs - takeMVar childrenDone
  case cs of
[]   - return ()
m:ms - do
  putMVar childrenDone ms
  takeMVar m
  waitForChildren childrenDone


shutdownServer :: MVar () - ChildrenDone - ThreadId 

Re: [Haskell] Help needed interrupting accepting a network connection

2006-12-02 Thread Cat Dancer

On 12/2/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:

Hi, I have taken a crack at this.  The best thing would be not to use the
asynchronous exceptions to signal the thread that calls accept.


I'd certainly be most happy not to use asynchronous exceptions as the
signalling mechanism, but how would you break out of the accept,
except by receiving an asynchronous exception?


But a few minor changes gets closer to what you want.  First, the main problem
you claim to run into is

 Except that, whoops, the takeMVar in the accept thread code which updates 
the
 childrenDone MVar is also interruptible.  So now I'm getting an
 interruption right where I don't want it, when I'm updating my data
 structure.

Short version: There is no problem because it will not become interruptible.
Long version:  The takeMVar unblocks exceptions only if it must
stop and wait for the MVar.  The MVar is only taken by this command/thread and
during graceful shutdown after this thread is dead.  So this MVar should never
be in contention (and in theory does not *need* to be a locked MVar, and an
IORef would do).


Gosh, I think you're right.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell