
Hello, When you want to use the system event manager (the one started by the RTS) you currently have to do something like this: ----------------------------------------------------------------------- {-# LANGUAGE ForeignFunctionInterface #-} import System.Event (EventManager) import GHC.Conc.Sync (sharedCAF) import Foreign.Ptr (Ptr) import Data.IORef (IORef, newIORef, readIORef) import System.IO.Unsafe (unsafePerformIO) main = do Just mgr <- readIORef eventManager ... eventManager :: IORef (Maybe EventManager) eventManager = unsafePerformIO $ do em <- newIORef Nothing sharedCAF em getOrSetSystemEventThreadEventManagerStore {-# NOINLINE eventManager #-} foreign import ccall unsafe "getOrSetSystemEventThreadEventManagerStore" getOrSetSystemEventThreadEventManagerStore :: Ptr a -> IO (Ptr a) ----------------------------------------------------------------------- What about abstracting this ugliness in a function: getSystemEventManager :: IO EventManager getSystemEventManager = do Just mgr <- readIORef eventManager return mgr I'm not entirely comfortable about the partial pattern match. I guess it fails when the program is linked with the non-threaded RTS. Can we use #ifdef THREADED_RTS here? I'm also not sure from which module to export this function. The attached patch defines it in and exports it from System.Event.Thread. It also exports it from the public System.Event. However maybe it's better to export it from GHC.Conc instead. What do you think? Regards, Bas

Hi Bas,
Apologies for the late reply.
On Wed, Mar 16, 2011 at 3:38 PM, Bas van Dijk
What about abstracting this ugliness in a function:
getSystemEventManager :: IO EventManager getSystemEventManager = do Just mgr <- readIORef eventManager return mgr
I'm not entirely comfortable about the partial pattern match. I guess it fails when the program is linked with the non-threaded RTS. Can we use #ifdef THREADED_RTS here?
I general I support having a way to get at the system event manager. Note that in the future we might have one event manager per capability so we might add getSystemEventManagerOn :: Int -> IO (Maybe EventManager) where the first argument would be the capability. If we do add an event manager per capability we could have getSystemEventManager get the current thread's capability and call getSystemEventManagerOn. The question in my mind is whether getSystemEventManager* should return IO EventManager or IO (Maybe EventManager). I don't like having an API which conditionally exports different entities depending on some CPP, this means that the CPP code needs to be copied into every use sight as well. That argues for having it return (Maybe EventManager).
I'm also not sure from which module to export this function. The attached patch defines it in and exports it from System.Event.Thread. It also exports it from the public System.Event. However maybe it's better to export it from GHC.Conc instead.
System.Event sounds right to me. Johan

On 30 March 2011 11:16, Johan Tibell
Apologies for the late reply.
Thanks for your reply.
I general I support having a way to get at the system event manager. Note that in the future we might have one event manager per capability so we might add getSystemEventManagerOn :: Int -> IO (Maybe EventManager) where the first argument would be the capability.
That makes sense. But let's propose that one when we need it.
The question in my mind is whether getSystemEventManager* should return IO EventManager or IO (Maybe EventManager). I don't like having an API which conditionally exports different entities depending on some CPP, this means that the CPP code needs to be copied into every use sight as well. That argues for having it return (Maybe EventManager).
Agreed. I will update the patch. Thanks, Bas

On 4 April 2011 00:26, Bas van Dijk
The question in my mind is whether getSystemEventManager* should return IO EventManager or IO (Maybe EventManager). I don't like having an API which conditionally exports different entities depending on some CPP, this means that the CPP code needs to be copied into every use sight as well. That argues for having it return (Maybe EventManager).
Agreed. I will update the patch.
Ticket with git patch created: http://hackage.haskell.org/trac/ghc/ticket/5091 Bas
participants (2)
-
Bas van Dijk
-
Johan Tibell