Hello everyone,

Yhc now includes support for concurrency! The interface is the same as Concurrent GHC, so for example the following is a concurrent Yhc program:

------------------------------------------------------------------
module Fair where

import Control.Concurrent
import Control.Concurrent.MVar


consumer :: MVar () -> Char -> IO ()
consumer mv c = do _ <- takeMVar mv
                   putChar c
                   consumer mv c

producer :: MVar () -> Int -> IO ()
producer mv 0 = return ()
producer mv n = do putMVar mv ()
                   producer mv (n-1)

main :: IO ()
main = do mv <- newEmptyMVar
          _ <- forkIO (consumer mv 'A')
          _ <- forkIO (consumer mv 'B')
          _ <- forkIO (consumer mv 'C')
          producer mv 1000
          putStrLn ""
------------------------------------------------------------------

Currently only

        Control.Concurrent
        Control.Concurrent.MVar
        Control.Concurrent.QSem

are implemented, however all the rest can easily be written in Haskell in terms of MVars.

Because the introduction of concurrency has changed the way stacks work for *all* of Yhc it is possible some bugs have been introduced. The concurrent yhc implementation passes all the unit tests that the single threaded yhc passed, but of course unit tests don't cover all cases. If you find your previously working single threaded programs are now breaking please submit a BUG REPORT to the list :-)

Also concurrency support is still new and relatively untested so you might find some concurrent programs that segfault/crash/lock up/etc. ALL BUG REPORTS HIGHLY WELCOME!

NOTE: the Windows release for concurrency isn't quite ready but it should be quite soon (thanks Neil for handling this).


Anyway, enjoy :-)



Tom

_______________________________________________
Yhc mailing list
[email protected]
http://haskell.org/mailman/listinfo/yhc

Reply via email to