#5091: Proposal: Retrieving the System Event Manager
---------------------------------+------------------------------------------
    Reporter:  basvandijk        |       Owner:                
        Type:  task              |      Status:  new           
    Priority:  normal            |   Component:  libraries/base
     Version:  7.0.3             |    Keywords:                
    Testcase:                    |   Blockedby:                
          Os:  Unknown/Multiple  |    Blocking:                
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown  
---------------------------------+------------------------------------------
 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)
 }}}

 I propose to abstract this ugliness in a function:

 {{{
 getSystemEventManager :: IO (Maybe EventManager)
 getSystemEventManager = readIORef eventManager
 }}}

 and export it from `GHC.Event`.

 I don't think this needs to go through the library submission process
 since the module is GHC specific.

 See the [http://thread.gmane.org/gmane.comp.lang.haskell.libraries/15458/
 thread on the libraries list].

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5091>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to