File: Event.hs

package info (click to toggle)
haskell-concurrent-extra 0.7.0.12-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 184 kB
  • sloc: haskell: 1,040; makefile: 6
file content (181 lines) | stat: -rw-r--r-- 5,639 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
{-# LANGUAGE CPP
           , DeriveDataTypeable
           , NoImplicitPrelude
  #-}

#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#endif

-------------------------------------------------------------------------------
-- |
-- Module     : Control.Concurrent.Event
-- Copyright  : (c) 2010-2011 Bas van Dijk & Roel van Dijk
-- License    : BSD3 (see the file LICENSE)
-- Maintainer : Bas van Dijk <v.dijk.bas@gmail.com>
--            , Roel van Dijk <vandijk.roel@gmail.com>
--
-- An Event is a simple mechanism for communication between threads: one thread
-- signals an event and other threads wait for it.
--
-- An event has a state which is either \"set\" or \"cleared\". This state can
-- be changed with the corresponding functions 'set' and 'clear'. The 'wait'
-- function blocks until the state is \"set\". An important property of setting
-- an event is that /all/ threads waiting for it are woken.
--
-- It was inspired by the Python @Event@ object. See:
--
-- <http://docs.python.org/3.1/library/threading.html#event-objects>
--
-- This module is designed to be imported qualified. We suggest importing it
-- like:
--
-- @
-- import           Control.Concurrent.Event          ( Event )
-- import qualified Control.Concurrent.Event as Event ( ... )
-- @
--
-------------------------------------------------------------------------------

module Control.Concurrent.Event
  ( Event

    -- * Creating events
  , new
  , newSet

    -- * Waiting for events
  , wait
  , waitTimeout
  , isSet

    -- * Setting events
  , set
  , signal
  , clear
  ) where


-------------------------------------------------------------------------------
-- Imports
-------------------------------------------------------------------------------

-- from base:
import Data.Bool               ( Bool(..) )
import Data.Eq                 ( Eq )
import Data.Function           ( (.) )
import Data.Functor            ( fmap, (<$>) )
import Data.Maybe              ( isJust )
import Data.Typeable           ( Typeable )

#ifdef __HADDOCK_VERSION__
import Control.Exception       ( mask )
#endif

import Prelude                 ( Integer )
import System.IO               ( IO )

-- from concurrent-extra (this package):
import           Control.Concurrent.Broadcast ( Broadcast )
import qualified Control.Concurrent.Broadcast as Broadcast
                               ( new, newBroadcasting
                               , listen, tryListen, listenTimeout
                               , broadcast, signal, silence
                               )


-------------------------------------------------------------------------------
-- Events
-------------------------------------------------------------------------------

-- | An event is in one of two possible states: \"set\" or \"cleared\".
newtype Event = Event {evBroadcast :: Broadcast ()} deriving (Eq, Typeable)


-------------------------------------------------------------------------------
-- Creating events
-------------------------------------------------------------------------------

-- | Create an event in the \"cleared\" state.
new :: IO Event
new = Event <$> Broadcast.new

-- | Create an event in the \"set\" state.
newSet :: IO Event
newSet = Event <$> Broadcast.newBroadcasting ()


-------------------------------------------------------------------------------
-- Waiting for events
-------------------------------------------------------------------------------

{-|
Block until the event is 'set'.

If the state of the event is already \"set\" this function will return
immediately. Otherwise it will block until another thread calls 'set'.

(You can also resume a thread that is waiting for an event by throwing an
asynchronous exception.)
-}
wait :: Event -> IO ()
wait = Broadcast.listen . evBroadcast

{-|
Block until the event is 'set' or until a timer expires.

Like 'wait', but with a timeout. A return value of 'False' indicates a timeout
occurred.

The timeout is specified in microseconds.

If the event is \"cleared\" and a timeout of 0 &#x3bc;s is specified the
function returns 'False' without blocking.

Negative timeouts are treated the same as a timeout of 0 &#x3bc;s.
-}
waitTimeout :: Event -> Integer -> IO Bool
waitTimeout ev time = isJust <$> Broadcast.listenTimeout (evBroadcast ev) time

{-|
Returns 'True' if the state of the event is \"set\" and 'False' if the state
is \"cleared\".

Notice that this is only a snapshot of the state. By the time a program reacts
on its result it may already be out of date.
-}
isSet :: Event -> IO Bool
isSet = fmap isJust . Broadcast.tryListen . evBroadcast


-------------------------------------------------------------------------------
-- Setting events
-------------------------------------------------------------------------------

{-|
Changes the state of the event to \"set\". All threads that where waiting
for this event are woken. Threads that 'wait' after the state is changed to
\"set\" will not block at all.
-}
set :: Event -> IO ()
set ev = Broadcast.broadcast (evBroadcast ev) ()

{-|
Changes the state to \"cleared\" after all threads that where waiting for this
event are woken. Threads that 'wait' after a @signal@ will block until the event
is 'set' again.

The semantics of signal are equivalent to the following definition:

@
  signal e = 'mask' $ 'set' e >> 'clear' e
@-}
signal :: Event -> IO ()
signal ev = Broadcast.signal (evBroadcast ev) ()

{-|
Changes the state of the event to \"cleared\". Threads that 'wait' after the
state is changed to \"cleared\" will block until the state is changed to \"set\".
-}
clear :: Event -> IO ()
clear = Broadcast.silence . evBroadcast