asynchronous call-backs

2010-02-19 Thread John Lask

Thanks for your response. I belabour the issue as I am not
entirely comfortable that there is no issue wrt to the unthreaded rts
on windows at least.

Included here is a test of executing a callback from c to haskell
asynchronously this test was run with both threaded rts and non threaded 
rts.


It demonstrates (tentatively) that asynchronous call-backs
seem to be safe with threaded rts and unsafe otherwise.

I have run other tests with the unthreaded rts which confirms
the above (eg with console events) . Details of which I can provide.

It does beg the question what proof can be given that the threaded
rts is safe wrt asynchronous call-backs.

My thoughts go along the lines that the safety of essentially parallel 
evaluation of thunks depends upon there being some level of atomicity in 
those operations, that atomicity being under the control of the rts. My 
concerns boil down to whether that atomicity is broken (by the 
unscheduled attempt at an evaluation of a thunk) or there exists within 
the evaluation model of the rts some guarantee wrt the underlying 
architecture or by happenstance ad-hoc enforcement of 
atomicity/synchronisation as an implementation detail. Has this question
been treated as an implementation detail or is there some literature 
that you could refer me to?




TEST DETAILS

As a test the c routine, starts an alarm thread that runs the call-back
once a second On each iteration a counter is incremented
and passed to the call back.

the threaded rts works fine, the un-threaded rts raises an
error. The error changes depending upon when the rts is interupted.
In one case the error reported was:

test: internal error: resurrectThreads: thread blocked in a strange way
(GHC version 6.10.4 for i386_unknown_mingw32)
Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

This application has requested the Runtime to terminate it in an unusual 
way.

Please contact the application's support team for more information.




 module Main where

 import Foreign
 import Foreign.C
 import System.IO
 import Control.Concurrent

 -- the callback to be executed assynchronous to the main loop
 hsfoo :: Int - IO ()
 hsfoo x = do
putStrLn (Input was:  ++ show x)
return ()

 foreign import  ccall safe wrapper mkfoo :: (Int-IO ())-IO 
(FunPtr (Int-IO ()))


 foreign import ccall safe registerCallback registerCallback :: 
(FunPtr (Int-IO ()))-IO ()




 loop = do
   threadDelay 1000
   mapM_ (putStrLn . show) [(0::Int)..10]
   loop

 main = do
   foo - mkfoo hsfoo
   registerCallback foo
   loop

-
the c code




/* starts an alarm thread that runs the call back
 * once a second.
 * on each iteration a counter is incremented
 * and passed to the call back.
 */

#include stdio.h
#include signal.h
#include windows.h

typedef void (*callback_t)(int);

static callback_t g_callback;

void CALLBACK alarm_callback( unsigned long interval) {

int rc;
int i=0;
printf(alarm thread started\n);
   i=0;
   while (1) {
 i++;
 Sleep(1000);
 printf(alarm\n);
 g_callback(i);
   };
}

void registerCallback(callback_t sighandler)
{
   printf(installing callback);

   g_callback = sighandler;

   CreateThread(NULL,0, (LPTHREAD_START_ROUTINE)alarm_callback,
(void*)0,0,0);

}


On 01/02/10 13:36, John Lask wrote:

I understand these are internals of ghc and subject to change. The
reason for their use: to support asynchronous interrupts safe with
respect to the Haskell code that is being interrupted. To my knowledge
(please correct me if I am wrong) there is no way to do this other than
the following alternatives and the already mentioned functions.

As an example, suppose I want to provide a call back to a win32 OS hook
which takes a c-call-back routine. My understanding is that I cannot use
a wrapped Haskell call-back routine as there are no guarantees what
state the Haskell rts will be in when the routine is called.


It's not clear to me that this wouldn't work.

I believe it would be perfectly safe for the Win32 console handler 
callback to invoke Haskell functions, because the handler is executed in 
a separate thread, unlike Unix signals which happen in the context of 
one of the existing threads (which is why you can't use any inter-thread 
communication or synchronisation in a Unix signal handler).



At least initially I have used the above mentioned functions to support
win32 signal handling, as the ghc rts just catches (and dispatches)
console events, which do not encompass all the (rather limited) c-rts
signals.

The obvious solution is to provide a c call-back routine, use an WIN32
event object, use a Haskell bound thread to wait on that event.

another alternative would be to poll.

The first alternative requires threaded rts which for various reasons I
don't wish 

Re: asynchronous call-backs

2010-02-19 Thread Simon Marlow

On 19/02/10 08:15, John Lask wrote:

Thanks for your response. I belabour the issue as I am not
entirely comfortable that there is no issue wrt to the unthreaded rts
on windows at least.

Included here is a test of executing a callback from c to haskell
asynchronously this test was run with both threaded rts and non threaded
rts.

It demonstrates (tentatively) that asynchronous call-backs
seem to be safe with threaded rts and unsafe otherwise.


Correct.  The threaded RTS is designed to handle call-ins on multiple 
threads.



I have run other tests with the unthreaded rts which confirms
the above (eg with console events) . Details of which I can provide.

It does beg the question what proof can be given that the threaded
rts is safe wrt asynchronous call-backs.

My thoughts go along the lines that the safety of essentially parallel
evaluation of thunks depends upon there being some level of atomicity in
those operations, that atomicity being under the control of the rts. My
concerns boil down to whether that atomicity is broken (by the
unscheduled attempt at an evaluation of a thunk) or there exists within
the evaluation model of the rts some guarantee wrt the underlying
architecture or by happenstance ad-hoc enforcement of
atomicity/synchronisation as an implementation detail. Has this question
been treated as an implementation detail or is there some literature
that you could refer me to?


Yes, I suggest starting with this paper, it describes the fundamental 
ideas behind GHC's parallel execution model:


http://www.haskell.org/~simonmar/papers/multiproc.pdf

Cheers,
Simon




TEST DETAILS

As a test the c routine, starts an alarm thread that runs the call-back
once a second On each iteration a counter is incremented
and passed to the call back.

the threaded rts works fine, the un-threaded rts raises an
error. The error changes depending upon when the rts is interupted.
In one case the error reported was:

test: internal error: resurrectThreads: thread blocked in a strange way
(GHC version 6.10.4 for i386_unknown_mingw32)
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug

This application has requested the Runtime to terminate it in an unusual
way.
Please contact the application's support team for more information.




  module Main where

  import Foreign
  import Foreign.C
  import System.IO
  import Control.Concurrent

  -- the callback to be executed assynchronous to the main loop
  hsfoo :: Int - IO ()
  hsfoo x = do
  putStrLn (Input was:  ++ show x)
  return ()

  foreign import ccall safe wrapper mkfoo :: (Int-IO ())-IO (FunPtr
(Int-IO ()))

  foreign import ccall safe registerCallback registerCallback ::
(FunPtr (Int-IO ()))-IO ()



  loop = do
  threadDelay 1000
  mapM_ (putStrLn . show) [(0::Int)..10]
  loop

  main = do
  foo - mkfoo hsfoo
  registerCallback foo
  loop

-

the c code




/* starts an alarm thread that runs the call back
* once a second.
* on each iteration a counter is incremented
* and passed to the call back.
*/

#include stdio.h
#include signal.h
#include windows.h

typedef void (*callback_t)(int);

static callback_t g_callback;

void CALLBACK alarm_callback( unsigned long interval) {

int rc;
int i=0;
printf(alarm thread started\n);
i=0;
while (1) {
i++;
Sleep(1000);
printf(alarm\n);
g_callback(i);
};
}

void registerCallback(callback_t sighandler)
{
printf(installing callback);

g_callback = sighandler;

CreateThread(NULL,0, (LPTHREAD_START_ROUTINE)alarm_callback,
(void*)0,0,0);

}


On 01/02/10 13:36, John Lask wrote:

I understand these are internals of ghc and subject to change. The
reason for their use: to support asynchronous interrupts safe with
respect to the Haskell code that is being interrupted. To my knowledge
(please correct me if I am wrong) there is no way to do this other than
the following alternatives and the already mentioned functions.

As an example, suppose I want to provide a call back to a win32 OS hook
which takes a c-call-back routine. My understanding is that I cannot use
a wrapped Haskell call-back routine as there are no guarantees what
state the Haskell rts will be in when the routine is called.


It's not clear to me that this wouldn't work.

I believe it would be perfectly safe for the Win32 console handler
callback to invoke Haskell functions, because the handler is executed
in a separate thread, unlike Unix signals which happen in the context
of one of the existing threads (which is why you can't use any
inter-thread communication or synchronisation in a Unix signal handler).


At least initially I have used the above mentioned functions to support
win32 signal handling, as the ghc rts just catches (and dispatches)
console events, which do not encompass all the (rather limited) c-rts
signals.

The obvious solution is to provide a c call-back routine, use an WIN32

Re: integer-simple by default

2010-02-19 Thread Don Stewart
garious:
 Static linking to GMP on Windows is sending me towards a bunch of red
 tape at work.  What can I do to make integer-simple the default
 integer library for GHC?  Need anything more than test suite and
 performance metrics?  Any date planned for the 6.12.2 release?

You can dynamically link libgmp on windows. That might be easier:

http://haskell.forkio.com/gmpwindows
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users