Concurrency in GHCi

John Knottenbelt jak97@doc.ic.ac.uk
Thu, 1 Mar 2001 18:03:45 +0000


Hi

The little program below is to test an idea to try to interact
using Hugs or GHCi with a running program. 

To use the program:
	1. Start the server with "addServer addChan"
	2. Write requests to addChan "writeChan addChan (Add 3 4)"

The program seems to work OK in Hugs, but crashes out with 
"ghc: no threads to run". 

Can anybody suggest a way of getting this to run properly with
GHCi?

Thanks

Johnny

----
Transcript of a Hugs session:

Type :? for help
ConcTest> addServer addChan
addServer started

ConcTest> writeChan addChan (Add 3 4)
1: addServer: 3 + 4 = 7

----
Transcript of a GHCi session:

Loading package concurrent ... linking ... done.
Compiling ConcTest ... compilation IS required
ConcTest> addServer addChan
addServer started
ghc: no threads to run:  infinite loop or deadlock?
bash$

----
module ConcTest where
import Concurrent
import IOExts

data AddMsg = Add Int Int | Quit

addServer :: Chan AddMsg -> IO ()
addServer c =
  do putStrLn "addServer started"
     loop 1
     putStrLn "addServer finished"

  where loop msgNum =
          do msg <- readChan c
             case msg of
               Add x y ->
                 do putStrLn (show msgNum ++ ": addServer: " ++
                                   show x ++ " + " ++ show y ++ " = " ++
                                   show (x + y))
                    loop (msgNum + 1)
               Quit ->
                 return ()

addChan :: Chan AddMsg
addChan = unsafePerformIO newChan