New Bound Threads Proposal

John Meacham john at repetae.net
Fri May 9 10:41:38 EDT 2003


On Tue, May 06, 2003 at 03:19:17PM +0200, Wolfgang Thaller wrote:
> 1) bind the "main" Haskell thread to the "main" OS thread
> 2) don't bind the "main" Haskell thread to the "main" OS thread
> 	2a) complicate the system by adding a way to access the "main" OS 
> thread
> 	2b) keep the system simple, use the hack I described above for GHC 
> programs that use Apple's libraries, and hope that Apple fixes it's 
> libraries before people want to use them with other implementations of 
> proposal4 where the hack doesn't work.

I don't see any problem with 1. It is no worse than the situation in
other languages and is significantly better in that Haskell can easily
pass around IO actions for the main thread to run. plus, any library
documentation for other languages will carry over into Haskell easily.

I can imagine something like this: (pseudo-ish code)


main = do
        forkIO restOfApp
        mainLoop

restOfApp = do
        ..
        ..
        x <- runInMain sillyFuncion
        ..
        ..


runInMain :: IO a -> IO a
runInMain action = do
        v <- newMVar
        writeChan mainChannel (action >>= putMVar v)
        takeMVar v
        

{-# NOTINLINE mainChannel #-}
mainChannel :: Chan (IO ())
mainChannel = unsafePerformIO (newChan)

mainLoop = repeatM_ $ readChan mainChannel >>= \x -> x


I did something similar for a UI library where actions needed to be
serialized (and sometimes dropped/combined, which is why i didn't use a
simple lock) and it worked well.
        John

-- 
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john at foo.net
---------------------------------------------------------------------------



More information about the FFI mailing list