[project @ 1999-01-16 16:06:17 by sof]
[ghc-hetmet.git] / ghc / docs / libraries / Concurrent.sgml
1 <sect> <idx/Concurrent/
2 <label id="sec:Concurrent">
3 <p>
4
5 This library provides the Concurrent Haskell extensions as described
6 in  <url name="Concurrent Haskell" url="http://research.microsoft.com/Users/simonpj/Papers/concurrent-haskell.ps.gz">.
7
8 <tscreen><verb>
9 module Concurrent where
10
11 data ThreadId    -- thread identifiers
12 instance Eq  ThreadId
13 instance Ord ThreadId
14
15 forkIO           :: IO () -> IO ThreadId
16 killThread       :: ThreadId -> IO ()
17
18 data MVar a      -- Synchronisation variables
19 newEmptyMVar     :: IO (MVar a)
20 newMVar          :: a -> IO (MVar a)
21 takeMVar         :: MVar a -> IO a
22 putMVar          :: MVar a -> a -> IO ()
23 swapMVar         :: MVar a -> a -> IO a
24 readMVar         :: MVar a -> IO a 
25 isEmptyMVar      :: MVar a -> IO Bool
26 instance Eq (MVar a)
27
28
29 data Chan a      -- channels
30 newChan          :: IO (Chan a)
31 writeChan        :: Chan a -> a -> IO ()
32 readChan         :: Chan a -> IO a
33 dupChan          :: Chan a -> IO (Chan a)
34 unReadChan       :: Chan a -> a -> IO ()
35 getChanContents  :: Chan a -> IO [a]
36 writeList2Chan   :: Chan a -> [a] -> IO ()
37                       
38 data CVar a       -- one element channels
39 newCVar          :: IO (CVar a)
40 putCVar          :: CVar a -> a -> IO ()
41 getCVar          :: CVar a -> IO a
42                       
43 data QSem        -- General/quantity semaphores
44 newQSem          :: Int  -> IO QSem
45 waitQSem         :: QSem -> IO ()
46 signalQSem       :: QSem -> IO ()
47                       
48 data QSemN       -- General/quantity semaphores
49 newQSemN         :: Int   -> IO QSemN
50 waitQSemN        :: QSemN -> Int -> IO ()
51 signalQSemN      :: QSemN -> Int -> IO ()
52
53 type SampleVar a -- Sample variables 
54 newEmptySampleVar:: IO (SampleVar a)
55 newSampleVar     :: a -> IO (SampleVar a)
56 emptySampleVar   :: SampleVar a -> IO ()
57 readSampleVar    :: SampleVar a -> IO a
58 writeSampleVar   :: SampleVar a -> a -> IO ()
59 </verb></tscreen>
60
61 Notes:
62 <itemize>
63
64 <item> 
65   GHC uses preemptive multitasking:
66   Context switches can occur at any time, except if you call a C
67   function (like <tt/getchar/) that blocks waiting for input.
68
69   Hugs uses cooperative multitasking:
70   Context switches only occur when you use one of the primitives
71   defined in this module.  This means that programs such as:
72 s not been implemented yet on
73 Hugs
74 <tscreen><verb>
75 main = forkIO (write 'a') >> write 'b'
76  where write c = putChar c >> write c
77 </verb></tscreen>
78
79   will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,
80   instead of some random interleaving of <tt/a/s and <tt/b/s.
81
82   In practice, cooperative multitasking is sufficient for writing 
83   simple graphical user interfaces.
84
85 <item>
86 Hugs does not provide the functions <tt/mergeIO/ or <tt/nmergeIO/ since these
87 require preemptive multitasking.
88
89 <item>
90 Thread identities and <tt/killThread/ have an experimental
91 implementation in GHC, but are not yet implemented in Hugs. 
92
93 Currently <tt/killThread/ simply kills the nominated thread, but the
94 plan is that in the future <tt/killThread/ will raise an exception in
95 the killed thread which it can catch --- perhaps allowing it to kill
96 its children before exiting.
97
98 <item>
99 The <tt/Ord/ instance for <tt/ThreadId/s provides an arbitrary total ordering
100 which might be used to build an ordered binary tree, say.  
101
102 <item>
103 The operation <tt/isEmptyMVar/ returns a flag indicating
104 whether the <tt/MVar/ is currently empty or filled in, i.e.,
105 will a thread block when performing a <tt/takeMVar/ on that
106 <tt/MVar/ or not?
107
108 Please notice that the Boolean value returned from <tt/isEmptyMVar/
109 represent just a snapshot of the state of the <tt/MVar/. By the
110 time a thread gets to inspect the result and act upon it, other
111 threads may have accessed the <tt/MVar/ and changed its 'filled-in'
112 status of the variable. Please be wary of this.
113
114 </itemize>