The System Event Manager

Bas van Dijk v.dijk.bas at gmail.com
Wed Mar 16 15:38:55 CET 2011


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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: getSystemEventManager.dpatch
Type: application/octet-stream
Size: 71108 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110316/2c0be40e/attachment-0001.obj>


More information about the Libraries mailing list