Skip to content
Snippets Groups Projects
Commit 84501c25 authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1998-06-04 16:15:10 by simonm]

Add a few simple concurrency tests.  More to come.
parent 965b595c
No related branches found
No related tags found
No related merge requests found
#-----------------------------------------------------------------------------
# $Id: Makefile,v 1.1 1998/06/04 16:15:10 simonm Exp $
TOP = ..
include $(TOP)/mk/boilerplate.mk
SUBDIRS = should_run
include $(TOP)/mk/target.mk
module Main where
import Concurrent
-- two processes, one MVar communication.
main = do
s <- newEmptyMVar
let
reader = do
str <- takeMVar s
putStr str
forkIO reader
putMVar s "hello world\n"
hello world
module Main where
import Concurrent
main = do
c <- newChan
let
reader = do
char <- readChan c
if (char == '\n')
then return ()
else do putChar char; reader
forkIO reader
writeList2Chan c "Hello World\n"
Hello World
\ No newline at end of file
module Main where
import Concurrent
-- simple handshaking using two MVars,
-- must context switch twice for each character.
main = do
ready <- newEmptyMVar
datum <- newEmptyMVar
let
reader = do
putMVar ready ()
char <- takeMVar datum
if (char == '\n')
then return ()
else do putChar char; reader
writer "" = do
takeMVar ready
putMVar datum '\n'
writer (c:cs) = do
takeMVar ready
putMVar datum c
writer cs
forkIO reader
writer "Hello World"
Hello World
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment