ghc rts selection and third party libraries

Hello I hope someone can provide some guidance on how I can solve a certain problem. I have a library that taps into the ghc c rts: specifically when the rts is single threaded I am pumping events in via: stg_pending_events, when the threaded rts is used I use sendIOManagerEvent. i.e. I have two versions of the library with the same api. The problem with this is that either library is only good for one context: either threaded rts or not, and the user needs to select the appropriate library to use depending on the use context. What I want to be able to do is to have ghc automatically select the compiled library version to link in depending on the which rts option is selected: "-thread" or not does any one have any ideas?

Perhaps rtsSupportsBoundThreads can help:
http://www.haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Control-C...
Best regards
Krzysztof Skrzętnicki
On Mon, Feb 1, 2010 at 06:33, John Lask
Hello
I hope someone can provide some guidance on how I can solve a certain problem.
I have a library that taps into the ghc c rts: specifically when the rts is single threaded I am pumping events in via: stg_pending_events, when the threaded rts is used I use sendIOManagerEvent.
i.e. I have two versions of the library with the same api. The problem with this is that either library is only good for one context: either threaded rts or not, and the user needs to select the appropriate library to use depending on the use context.
What I want to be able to do is to have ghc automatically select the compiled library version to link in depending on the which rts option is selected: "-thread" or not
does any one have any ideas? _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 01/02/2010 05:33, John Lask wrote:
I hope someone can provide some guidance on how I can solve a certain problem.
I have a library that taps into the ghc c rts: specifically when the rts is single threaded I am pumping events in via: stg_pending_events, when the threaded rts is used I use sendIOManagerEvent.
These are RTS internal APIs, and could change under your feet. What is it you're trying to do exactly?
i.e. I have two versions of the library with the same api. The problem with this is that either library is only good for one context: either threaded rts or not, and the user needs to select the appropriate library to use depending on the use context.
What I want to be able to do is to have ghc automatically select the compiled library version to link in depending on the which rts option is selected: "-thread" or not
Library code is generally supposed to be independent of -threaded; sometimes we do this by checking at runtime using rtsSupportsBoundThreads(). Cheers, Simon

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. 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 to use under all circumstances, the other alternative is inefficient or unresponsive. Discussion of either of these alternatives distract from the question "shouldn't there be a method for asynchronous call-back that is safe with respect to the Haskell rts state"? But there already exists such a method, that of the backdoor already mentioned, really, all that is required is for this to become more formalised and a single api adopted that is usable from c and consistent across threaded and un-threaded rts, but in the mean time the existing structure is quite usable for this purpose aside from the cumbersome libraries issue. And the reason for this libraries issue is that the methods exposed by the ghc-runtime to collect and post events into the ghc runtime system differ between the threaded and non-threaded runtimes, which is why short of changing ghc rts myself I can't avoid it (or adopting either of the above alternatives) As the facility (to capture arbitrary asynchronous interrupts) is generally useful I believe it to be advantageous to address it rather than side-stepping it.
On 01/02/2010 05:33, John Lask wrote:
I hope someone can provide some guidance on how I can solve a certain problem.
I have a library that taps into the ghc c rts: specifically when the rts is single threaded I am pumping events in via: stg_pending_events, when the threaded rts is used I use sendIOManagerEvent.
These are RTS internal APIs, and could change under your feet. What is it you're trying to do exactly?
i.e. I have two versions of the library with the same api. The problem with this is that either library is only good for one context: either threaded rts or not, and the user needs to select the appropriate library to use depending on the use context.
What I want to be able to do is to have ghc automatically select the compiled library version to link in depending on the which rts option is selected: "-thread" or not
Library code is generally supposed to be independent of -threaded; sometimes we do this by checking at runtime using rtsSupportsBoundThreads().
Cheers, Simon

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 to use under all circumstances, the other alternative is inefficient or unresponsive.
Discussion of either of these alternatives distract from the question "shouldn't there be a method for asynchronous call-back that is safe with respect to the Haskell rts state"?
But there already exists such a method, that of the backdoor already mentioned, really, all that is required is for this to become more formalised and a single api adopted that is usable from c and consistent across threaded and un-threaded rts, but in the mean time the existing structure is quite usable for this purpose aside from the cumbersome libraries issue.
And the reason for this libraries issue is that the methods exposed by the ghc-runtime to collect and post events into the ghc runtime system differ between the threaded and non-threaded runtimes, which is why short of changing ghc rts myself I can't avoid it (or adopting either of the above alternatives)
As the facility (to capture arbitrary asynchronous interrupts) is generally useful I believe it to be advantageous to address it rather than side-stepping it.
You might want to look at the work that Bryan O'Sullivan and Johan Tibell are doing on a new IO manager: http://github.com/bos/event/ There's no Win32 support yet, but it's designed to allow multiple backends. Cheers, Simon

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
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 to use under all circumstances, the other alternative is inefficient or unresponsive.
Discussion of either of these alternatives distract from the question "shouldn't there be a method for asynchronous call-back that is safe with respect to the Haskell rts state"?
But there already exists such a method, that of the backdoor already mentioned, really, all that is required is for this to become more formalised and a single api adopted that is usable from c and consistent across threaded and un-threaded rts, but in the mean time the existing structure is quite usable for this purpose aside from the cumbersome libraries issue.
And the reason for this libraries issue is that the methods exposed by the ghc-runtime to collect and post events into the ghc runtime system differ between the threaded and non-threaded runtimes, which is why short of changing ghc rts myself I can't avoid it (or adopting either of the above alternatives)
As the facility (to capture arbitrary asynchronous interrupts) is generally useful I believe it to be advantageous to address it rather than side-stepping it.
You might want to look at the work that Bryan O'Sullivan and Johan Tibell are doing on a new IO manager:
There's no Win32 support yet, but it's designed to allow multiple backends.
Cheers, Simon

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
#include #include 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 to use under all circumstances, the other alternative is inefficient or unresponsive.
Discussion of either of these alternatives distract from the question "shouldn't there be a method for asynchronous call-back that is safe with respect to the Haskell rts state"?
But there already exists such a method, that of the backdoor already mentioned, really, all that is required is for this to become more formalised and a single api adopted that is usable from c and consistent across threaded and un-threaded rts, but in the mean time the existing structure is quite usable for this purpose aside from the cumbersome libraries issue.
And the reason for this libraries issue is that the methods exposed by the ghc-runtime to collect and post events into the ghc runtime system differ between the threaded and non-threaded runtimes, which is why short of changing ghc rts myself I can't avoid it (or adopting either of the above alternatives)
As the facility (to capture arbitrary asynchronous interrupts) is generally useful I believe it to be advantageous to address it rather than side-stepping it.
You might want to look at the work that Bryan O'Sullivan and Johan Tibell are doing on a new IO manager:
There's no Win32 support yet, but it's designed to allow multiple backends.
Cheers, Simon
participants (3)
-
John Lask
-
Krzysztof Skrzętnicki
-
Simon Marlow