Skip to content

Commit 3fb78d4

Browse files
sheafMistuke
authored andcommitted
Add support for Windows semaphores
This adds the module `System.Win32.Semaphore` which implements Windows semaphores and operations on them. Note that waiting on a semaphore is done using `System.Win32.Event.waitForSingleObject`, and freeing a semaphore is done using `System.Win32.File.closeHandle`.
1 parent 3c26b9b commit 3fb78d4

File tree

6 files changed

+229
-0
lines changed

6 files changed

+229
-0
lines changed

System/Win32/Semaphore.hsc

Lines changed: 146 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,146 @@
1+
#if __GLASGOW_HASKELL__ >= 709
2+
{-# LANGUAGE Safe #-}
3+
#else
4+
{-# LANGUAGE Trustworthy #-}
5+
#endif
6+
7+
-----------------------------------------------------------------------------
8+
-- |
9+
-- Module : System.Win32.Semaphore
10+
-- Copyright : (c) Sam Derbyshire, 2022
11+
-- License : BSD-style (see the file libraries/base/LICENSE)
12+
--
13+
-- Maintainer : Sam Derbyshire
14+
-- Stability : provisional
15+
-- Portability : portable
16+
--
17+
-- Windows Semaphore objects and operations
18+
--
19+
-----------------------------------------------------------------------------
20+
21+
module System.Win32.Semaphore
22+
( -- * Semaphores
23+
Semaphore(..)
24+
25+
-- * Access modes
26+
, AccessMode
27+
, sEMAPHORE_ALL_ACCESS
28+
, sEMAPHORE_MODIFY_STATE
29+
30+
-- * Managing semaphores
31+
, createSemaphore
32+
, openSemaphore
33+
, releaseSemaphore
34+
) where
35+
36+
import System.Win32.File
37+
import System.Win32.Types
38+
39+
import Data.Maybe (fromMaybe)
40+
import Foreign hiding (void)
41+
import Foreign.C (withCAString)
42+
43+
##include "windows_cconv.h"
44+
45+
#include <windows.h>
46+
47+
----------------------------------------------------------------
48+
-- Semaphore access modes
49+
----------------------------------------------------------------
50+
51+
#{enum AccessMode,
52+
, sEMAPHORE_ALL_ACCESS = SEMAPHORE_ALL_ACCESS
53+
, sEMAPHORE_MODIFY_STATE = SEMAPHORE_MODIFY_STATE
54+
}
55+
56+
----------------------------------------------------------------
57+
-- Semaphores
58+
----------------------------------------------------------------
59+
60+
-- | A Windows semaphore.
61+
--
62+
-- To obtain a 'Semaphore', use 'createSemaphore' to create a new one,
63+
-- or 'openSemaphore' to open an existing one.
64+
--
65+
-- To wait on a semaphore, use 'System.Win32.Event.waitForSingleObject'.
66+
--
67+
-- To release resources on a semaphore, use 'releaseSemaphore'.
68+
--
69+
-- To free a semaphore, use 'System.Win32.File.closeHandle'.
70+
-- The semaphore object is destroyed when its last handle has been closed.
71+
-- Closing the handle does not affect the semaphore count; therefore, be sure to call
72+
-- 'releaseSemaphore' before closing the handle or before the process terminates.
73+
-- Otherwise, pending wait operations will either time out or continue indefinitely,
74+
-- depending on whether a time-out value has been specified.
75+
newtype Semaphore = Semaphore { semaphoreHandle :: HANDLE }
76+
77+
-- | Open a 'Semaphore' with the given name, or create a new semaphore
78+
-- if no such semaphore exists, with initial count @i@ and maximum count @m@.
79+
--
80+
-- The counts must satisfy @i >= 0@, @m > 0@ and @i <= m@.
81+
--
82+
-- The returned 'Bool' is 'True' if the function found an existing semaphore
83+
-- with the given name, in which case a handle to that semaphore is returned
84+
-- and the counts are ignored.
85+
--
86+
-- Use 'openSemaphore' if you don't want to create a new semaphore.
87+
createSemaphore :: Maybe SECURITY_ATTRIBUTES
88+
-> LONG -- ^ initial count @i@ with @0 <= i <= m@
89+
-> LONG -- ^ maximum count @m > 0@
90+
-> Maybe String -- ^ (optional) semaphore name
91+
-- (case-sensitive, limited to MAX_PATH characters)
92+
-> IO (Semaphore, Bool)
93+
createSemaphore mb_sec initial_count max_count mb_name =
94+
maybeWith with mb_sec $ \ c_sec -> do
95+
maybeWith withCAString mb_name $ \ c_name -> do
96+
handle <- c_CreateSemaphore c_sec initial_count max_count c_name
97+
err_code <- getLastError
98+
already_exists <-
99+
case err_code of
100+
(# const ERROR_INVALID_HANDLE) ->
101+
errorWin $ "createSemaphore: semaphore name '"
102+
++ fromMaybe "" mb_name
103+
++ "' matches non-semaphore"
104+
(# const ERROR_ALREADY_EXISTS) ->
105+
return True
106+
_ ->
107+
return False
108+
if handle == nullPtr
109+
then errorWin "createSemaphore"
110+
else return (Semaphore handle, already_exists)
111+
112+
foreign import WINDOWS_CCONV unsafe "windows.h CreateSemaphoreA"
113+
c_CreateSemaphore :: LPSECURITY_ATTRIBUTES -> LONG -> LONG -> LPCSTR -> IO HANDLE
114+
115+
-- | Open an existing 'Semaphore'.
116+
openSemaphore :: AccessMode -- ^ desired access mode
117+
-> Bool -- ^ should child processes inherit the handle?
118+
-> String -- ^ name of the semaphore to open (case-sensitive)
119+
-> IO Semaphore
120+
openSemaphore amode inherit name =
121+
withTString name $ \c_name -> do
122+
handle <- failIfNull ("openSemaphore: '" ++ name ++ "'") $
123+
c_OpenSemaphore (fromIntegral amode) inherit c_name
124+
return (Semaphore handle)
125+
126+
foreign import WINDOWS_CCONV unsafe "windows.h OpenSemaphoreW"
127+
c_OpenSemaphore :: DWORD -> BOOL -> LPCWSTR -> IO HANDLE
128+
129+
-- | Increase the count of the 'Semaphore' by the specified amount.
130+
--
131+
-- Returns the count of the semaphore before the increase.
132+
--
133+
-- Throws an error if the count would exceeded the maximum count
134+
-- of the semaphore.
135+
releaseSemaphore :: Semaphore -> LONG -> IO LONG
136+
releaseSemaphore (Semaphore handle) count =
137+
with 0 $ \ ptr_prevCount -> do
138+
failIfFalse_ "releaseSemaphore" $ c_ReleaseSemaphore handle count ptr_prevCount
139+
peek ptr_prevCount
140+
141+
foreign import WINDOWS_CCONV unsafe "windows.h ReleaseSemaphore"
142+
c_ReleaseSemaphore :: HANDLE -> LONG -> Ptr LONG -> IO BOOL
143+
144+
----------------------------------------------------------------
145+
-- End
146+
----------------------------------------------------------------

Win32.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -88,6 +88,7 @@ Library
8888
System.Win32.Time
8989
System.Win32.Console
9090
System.Win32.Security
91+
System.Win32.Semaphore
9192
System.Win32.Types
9293
System.Win32.Shell
9394
System.Win32.Automation

changelog.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@
2525

2626
* Set maximum string size for getComputerName. (See #190)
2727
* Update withHandleToHANDLENative to handle duplex and console handles (See #191)
28+
* Add support for semaphores with `System.Win32.Semaphore`.
2829

2930
## 2.13.1.0 November 2021
3031

tests/Semaphores.hs

Lines changed: 60 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,60 @@
1+
module Main where
2+
3+
import Control.Concurrent
4+
( forkIO, threadDelay )
5+
import Control.Monad
6+
( void )
7+
import Data.Foldable
8+
( for_ )
9+
10+
import System.Win32.Event
11+
( waitForSingleObject )
12+
import System.Win32.File
13+
( closeHandle )
14+
import System.Win32.Semaphore
15+
( Semaphore(..), createSemaphore, releaseSemaphore )
16+
17+
main :: IO ()
18+
main = do
19+
20+
(test_sem, ex1) <- mk_test_sem
21+
(_, ex2) <- mk_test_sem
22+
23+
let sem_name = "win32-test-semaphore"
24+
(sem, ex3) <- createSemaphore Nothing 2 3 (Just sem_name)
25+
26+
putStrLn (show ex1 ++ " " ++ show ex2 ++ " " ++ show ex3)
27+
-- False True False
28+
29+
putStrLn "=========="
30+
for_ [1,2,3] (run_thread sem)
31+
-- finish: 1, 2
32+
33+
putStrLn "=========="
34+
void $ releaseSemaphore sem 3
35+
-- finish: 3
36+
37+
threadDelay 5000 -- 5 ms
38+
for_ [4,5,6,7] (run_thread sem)
39+
-- finish: 4, 5
40+
41+
threadDelay 1000 -- 1 ms
42+
putStrLn "=========="
43+
void $ releaseSemaphore sem 1
44+
-- finish: 6
45+
46+
threadDelay 100000 -- 100 ms
47+
putStrLn "=========="
48+
closeHandle (semaphoreHandle test_sem)
49+
closeHandle (semaphoreHandle sem)
50+
51+
run_thread :: Semaphore -> Int -> IO ()
52+
run_thread sem i = do
53+
threadDelay 1000 -- 1 ms
54+
putStrLn ("start " ++ show i)
55+
void $ forkIO $ do
56+
res <- waitForSingleObject (semaphoreHandle sem) 50 -- 50 ms
57+
putStrLn ("finish " ++ show i ++ ": " ++ show res)
58+
59+
mk_test_sem :: IO (Semaphore, Bool)
60+
mk_test_sem = createSemaphore Nothing 1 1 (Just "test-sem")

tests/Semaphores.stdout

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
False True False
2+
==========
3+
start 1
4+
finish 1: 0
5+
start 2
6+
finish 2: 0
7+
start 3
8+
==========
9+
finish 3: 0
10+
start 4
11+
finish 4: 0
12+
start 5
13+
finish 5: 0
14+
start 6
15+
start 7
16+
==========
17+
finish 6: 0
18+
finish 7: 258
19+
==========

tests/all.T

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,3 +8,5 @@ test('lasterror', normal, compile_and_run, ['-package Win32'])
88
test('T4452', normal, compile_and_run, ['-package Win32'])
99
test('PokeTZI', ignore_stdout, compile_and_run, ['-package Win32'])
1010
test('HandleConversion', normal, compile_and_run, ['-package Win32'])
11+
12+
test('Semaphores', normal, compile_and_run, ['-threaded -package Win32'])

0 commit comments

Comments
 (0)