1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: jan@swi-prolog.org 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2023, SWI-Prolog Solutions b.v. 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(rwlocks, 36 [ with_rwlock/3, % +LockId, :Goal, +Mode 37 with_rwlock/4 % +LockId, :Goal, +ModeSpec, +Options 38 ]). 39:- autoload(library(error), [must_be/2, type_error/2]). 40:- autoload(library(lists), [member/2]). 41:- autoload(library(option), [option/2]). 42 43:- meta_predicate 44 with_rwlock( , , ), 45 with_rwlock( , , , ).
read
, write
, read(Priority)
or write(Priority)
. The default
read
priority is 100 and the default write
priority is 200.
These values prioritize writers over readers. Goal may start if
If Goal may not start immediately the thread waits using
thread_wait/2. The Options timeout
and deadline
are passed to
thread_wait/2. If the time limit is exceeded an exception is raised.
Read/write locks are widely critized for their poor behaviour on several workloads. They perform well in scenarios where read operations take long, and write operations are relatively fast and occur only occasionally. Transactions, as implemented by transaction/1,2 are often a better alternative.
This predicate uses a normal mutex and a flag with the same name. See with_mutex/2 and flag/3. Neither the mutex nor the flag should be used directly.
86with_rwlock(LockId, Goal, ModeSpec) :- 87 with_rwlock(LockId, Goal, ModeSpec, []). 88 89with_rwlock(LockId, Goal, ModeSpec, Options) :- 90 must_be(atom, LockId), 91 must_be(callable, Goal), 92 rwmode(ModeSpec, Mode, Pri), 93 94 flag(LockId, Id, Id+1), 95 ( with_mutex(LockId, may_start(LockId, Mode, Pri, Id)) 96 -> true 97 ; wait(LockId, Mode, Pri, Id, Options) 98 ), 99 call_cleanup(once(Goal), 100 with_mutex(LockId, completed(LockId, Id))). 101 102 103rwmode(read, Mode, Pri) => 104 Mode = read, 105 Pri = 100. 106rwmode(write, Mode, Pri) => 107 Mode = write, 108 Pri = 200. 109rwmode(read(X), Mode, Pri), number(X) => 110 Mode = read, 111 Pri = X. 112rwmode(write(X), Mode, Pri), number(X) => 113 Mode = write, 114 Pri = X. 115rwmode(Mode, _, _) => 116 type_error(rwlock_mode, Mode). 117 118:- dynamic 119 ( access/3, % LockId, Mode, Id 120 waiting/4 % LockId, Mode, Pri, Id 121 ) as volatile. 122 123may_start(LockId, _Mode, Pri, _) :- 124 waiting(LockId, _, WPri, _), 125 WPri > Pri, 126 !, 127 fail. 128may_start(LockId, read, _Pri, Id) :- 129 \+ access(LockId, write, _), 130 !, 131 asserta(access(LockId, read, Id)). 132may_start(LockId, write, _Pri, Id) :- 133 \+ access(LockId, _, _), 134 !, 135 asserta(access(LockId, write, Id)). 136 137wait(LockId, Mode, Pri, Id, Options) :- 138 deadline_option(DOption, Options), 139 assertz(waiting(LockId, Mode, Pri, Id)), 140 ( thread_wait(\+ waiting(LockId, _, _, Id), 141 [ wait_preds([waiting/4]) 142 | DOption 143 ]) 144 -> true 145 ; retractall(waiting(LockId, _, _, Id)), 146 throw(time_limit_exceeded(rwlock)) 147 ). 148 149deadline_option([deadline(Time)], Options) :- 150 ( option(deadline(Time), Options) 151 -> true 152 ; option(timeout(Rel), Options) 153 -> get_time(Now), 154 Time is Now+Rel 155 ), 156 !. 157deadline_option([], _). 158 159completed(LockId, Id) :- 160 retractall(access(LockId, _, Id)), 161 with_mutex(LockId, wakeup(LockId)). 162 163wakeup(LockId) :- 164 findall(t(Mode,Pri,Id), waiting(LockId, Mode, Pri, Id), Triples), 165 sort(2, >=, Triples, Sorted), 166 member(t(Mode,Pri,Id), Sorted), 167 ( Mode == write 168 -> \+ access(LockId, _, _) 169 ; \+ access(LockId, _, _) 170 ), !, 171 retractall(waiting(LockId, _, _, Id)). 172wakeup(_)
Read/write locks
This library implements read/write locks on top of with_mutex/2. Read/write locks are synchronization objects that allow for multiple readers or a single writer to be active. */