[GHC] #15998: GHC.Event.Thread.eventManager has a lot of indirections
GHC
ghc-devs at haskell.org
Wed Dec 5 16:25:44 UTC 2018
#15998: GHC.Event.Thread.eventManager has a lot of indirections
-------------------------------------+-------------------------------------
Reporter: chessai | Owner: (none)
Type: feature | Status: new
request |
Priority: normal | Milestone: 8.6.3
Component: | Version: 8.6.2
libraries/base |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Current `eventManager`:
{{{#!hs
eventManager :: IORef (IOArray Int (Maybe (ThreadId, EventManager)))
eventManager = unsafePerformIO $ do
...
}}}
That's a lot of indirections just to grab your thread's event manager.
Consider the following, which I believe would improve the performance of
this:
{{{#!hs
data UnliftedIORef :: TYPE 'UnliftedRep -> Type where
UnliftedIORef :: MutVar# RealWorld a -> UnliftedIORef a
eventManager :: UnliftedIORef (MutableArray# RealWorld Things)
data Things = Things !ThreadId !EventManager
}}}
I think the Maybe can be eliminated. I'm unsure. What makes me think it
can be is the following snippet:
{{{#!hs
getSystemEventManager :: IO (Maybe EventManager)
getSystemEventManager = do
t <- myThreadId
(cap, _) <- threadCapability t
eventManagerArray <- readIORef eventManager
mmgr <- readIOArray eventManagerArray cap
return $ fmap snd mmgr
getSystemEventManager_ :: IO EventManager
getSystemEventManager_ = do
Just mgr <- getSystemEventManager
return mgr
{-# INLINE getSystemEventManager_ #-}
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15998>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list