Skip to content

Commit ac4a7d6

Browse files
committed
[API] Make ?lock_kind always non-optional to avoid breaking the library users after they upgrade their opam root
1 parent 4aa865a commit ac4a7d6

8 files changed

+62
-55
lines changed

src/client/opamListCommand.ml

+3-1
Original file line numberDiff line numberDiff line change
@@ -389,7 +389,9 @@ let apply_selector ~base st = function
389389
in
390390
let selections =
391391
if switch = st.switch then OpamSwitchState.selections st
392-
else OpamSwitchState.load_selections st.switch_global switch
392+
else
393+
OpamSwitchState.load_selections ~lock_kind:`Lock_none
394+
st.switch_global switch
393395
in
394396
List.fold_left (fun acc f ->
395397
let name =

src/client/opamSwitchCommand.ml

+4-1
Original file line numberDiff line numberDiff line change
@@ -528,7 +528,10 @@ let import_t ?ask ?(deps_only=false) importfile t =
528528
opam)
529529
pinned;
530530
(* Save new pinnings *)
531-
let sel = OpamSwitchState.load_selections t.switch_global t.switch in
531+
let sel =
532+
OpamSwitchState.load_selections ~lock_kind:`Lock_write
533+
t.switch_global t.switch
534+
in
532535
S.write
533536
(OpamPath.Switch.selections t.switch_global.root t.switch)
534537
{ sel with sel_pinned = pinned }

src/state/opamGlobalState.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -190,7 +190,7 @@ let drop gt =
190190
let _ = unlock gt in ()
191191

192192
let with_write_lock ?dontblock gt f =
193-
if OpamStateConfig.is_newer_than_self gt then
193+
if OpamStateConfig.is_newer_than_self ~lock_kind:`Lock_write gt then
194194
OpamConsole.error_and_exit `Locked
195195
"The opam root has been upgraded by a newer version of opam-state \
196196
and cannot be written to";

src/state/opamRepositoryState.ml

+3-2
Original file line numberDiff line numberDiff line change
@@ -159,7 +159,7 @@ let load lock_kind gt =
159159
log "LOAD-REPOSITORY-STATE %@ %a" (slog OpamFilename.Dir.to_string) gt.root;
160160
let lock = OpamFilename.flock lock_kind (OpamPath.repos_lock gt.root) in
161161
let repos_map = OpamStateConfig.Repos.safe_read ~lock_kind gt in
162-
if OpamStateConfig.is_newer_than_self gt then
162+
if OpamStateConfig.is_newer_than_self ~lock_kind gt then
163163
log "root version (%s) is greater than running binary's (%s); \
164164
load with best-effort (read-only)"
165165
(OpamVersion.to_string (OpamFile.Config.opam_root_version gt.config))
@@ -260,7 +260,8 @@ let drop ?cleanup rt =
260260
let _ = unlock ?cleanup rt in ()
261261

262262
let with_write_lock ?dontblock rt f =
263-
if OpamStateConfig.is_newer_than_self rt.repos_global then
263+
if OpamStateConfig.is_newer_than_self ~lock_kind:`Lock_write rt.repos_global
264+
then
264265
OpamConsole.error_and_exit `Locked
265266
"The opam root has been upgraded by a newer version of opam-state \
266267
and cannot be written to";

src/state/opamStateConfig.ml

+33-33
Original file line numberDiff line numberDiff line change
@@ -246,21 +246,21 @@ let is_newer config =
246246
(** none -> shouldn't load (write attempt in readonly)
247247
Some true -> everything is fine normal read
248248
Some false -> readonly accorded, load with best effort *)
249-
let is_readonly_opamroot_raw ?(lock_kind=`Lock_write) version =
249+
let is_readonly_opamroot_raw ~lock_kind version =
250250
let newer = is_newer_raw version in
251251
let write = lock_kind = `Lock_write in
252252
if newer && write then None else
253253
Some (newer && not write)
254254

255-
let is_readonly_opamroot_t ?lock_kind gt =
256-
is_readonly_opamroot_raw ?lock_kind
255+
let is_readonly_opamroot_t ~lock_kind gt =
256+
is_readonly_opamroot_raw ~lock_kind
257257
(Some (OpamFile.Config.opam_root_version gt.config))
258258

259-
let is_newer_than_self ?lock_kind gt =
260-
is_readonly_opamroot_t ?lock_kind gt <> Some false
259+
let is_newer_than_self ~lock_kind gt =
260+
is_readonly_opamroot_t ~lock_kind gt <> Some false
261261

262-
let load_if_possible_raw ?lock_kind root version (read,read_wo_err) f =
263-
match is_readonly_opamroot_raw ?lock_kind version with
262+
let load_if_possible_raw ~lock_kind root version (read,read_wo_err) f =
263+
match is_readonly_opamroot_raw ~lock_kind version with
264264
| None ->
265265
OpamConsole.error_and_exit `Locked
266266
"Refusing write access to %s, which is more recent than this version of \
@@ -271,16 +271,16 @@ let load_if_possible_raw ?lock_kind root version (read,read_wo_err) f =
271271
| Some true -> read_wo_err f
272272
| Some false -> read f
273273

274-
let load_if_possible_t ?lock_kind opamroot config readf f =
275-
load_if_possible_raw ?lock_kind
274+
let load_if_possible_t ~lock_kind opamroot config readf f =
275+
load_if_possible_raw ~lock_kind
276276
opamroot (Some (OpamFile.Config.opam_root_version config)) readf f
277277

278-
let load_if_possible ?lock_kind gt =
279-
load_if_possible_t ?lock_kind gt.root gt.config
278+
let load_if_possible ~lock_kind gt =
279+
load_if_possible_t ~lock_kind gt.root gt.config
280280

281-
let load_config_root ?lock_kind readf opamroot =
281+
let load_config_root ~lock_kind readf opamroot =
282282
let f = OpamPath.config opamroot in
283-
load_if_possible_raw ?lock_kind
283+
load_if_possible_raw ~lock_kind
284284
opamroot
285285
(OpamFile.Config.raw_root_version f)
286286
readf f
@@ -289,51 +289,51 @@ let safe read read' default =
289289
let safe r f = OpamStd.Option.default default @@ r f in
290290
safe read, safe read'
291291

292-
let safe_load ?lock_kind opamroot =
293-
load_config_root ?lock_kind
292+
let safe_load ~lock_kind opamroot =
293+
load_config_root ~lock_kind
294294
OpamFile.Config.(safe read_opt BestEffort.read_opt empty) opamroot
295295

296-
let load ?lock_kind opamroot =
297-
load_config_root ?lock_kind
296+
let load ~lock_kind opamroot =
297+
load_config_root ~lock_kind
298298
OpamFile.Config.(read_opt, BestEffort.read_opt) opamroot
299299

300300
(* switches *)
301301
module Switch = struct
302302

303-
let load_raw ?lock_kind root config readf switch =
304-
load_if_possible_t ?lock_kind root config readf
303+
let load_raw ~lock_kind root config readf switch =
304+
load_if_possible_t ~lock_kind root config readf
305305
(OpamPath.Switch.switch_config root switch)
306306

307-
let safe_load_t ?lock_kind root switch =
307+
let safe_load_t ~lock_kind root switch =
308308
let config = safe_load ~lock_kind:`Lock_read root in
309-
load_raw ?lock_kind root config
309+
load_raw ~lock_kind root config
310310
OpamFile.Switch_config.(safe read_opt BestEffort.read_opt empty)
311311
switch
312312

313-
let load ?lock_kind gt readf switch =
314-
load_raw ?lock_kind gt.root gt.config readf switch
313+
let load ~lock_kind gt readf switch =
314+
load_raw ~lock_kind gt.root gt.config readf switch
315315

316-
let safe_load ?lock_kind gt switch =
317-
load ?lock_kind gt
316+
let safe_load ~lock_kind gt switch =
317+
load ~lock_kind gt
318318
OpamFile.Switch_config.(safe read_opt BestEffort.read_opt empty)
319319
switch
320320

321-
let read_opt ?lock_kind gt switch =
322-
load ?lock_kind gt
321+
let read_opt ~lock_kind gt switch =
322+
load ~lock_kind gt
323323
OpamFile.Switch_config.(read_opt, BestEffort.read_opt)
324324
switch
325325

326-
let safe_read_selections ?lock_kind gt switch =
327-
load_if_possible ?lock_kind gt
326+
let safe_read_selections ~lock_kind gt switch =
327+
load_if_possible ~lock_kind gt
328328
OpamFile.SwitchSelections.(safe read_opt BestEffort.read_opt empty)
329329
(OpamPath.Switch.selections gt.root switch)
330330

331331
end
332332

333333
(* repos *)
334334
module Repos = struct
335-
let safe_read ?lock_kind gt =
336-
load_if_possible ?lock_kind gt
335+
let safe_read ~lock_kind gt =
336+
load_if_possible ~lock_kind gt
337337
OpamFile.Repos_config.(safe read_opt BestEffort.read_opt empty)
338338
(OpamPath.repos_config gt.root)
339339
end
@@ -396,13 +396,13 @@ let get_current_switch_from_cwd root =
396396
with OpamPp.Bad_version _ -> None
397397

398398
(* do we want `load_defaults` to fail / run a format upgrade ? *)
399-
let load_defaults ?lock_kind root_dir =
399+
let load_defaults ~lock_kind root_dir =
400400
let current_switch =
401401
match E.switch () with
402402
| Some "" | None -> get_current_switch_from_cwd root_dir
403403
| _ -> (* OPAMSWITCH is set, no need to lookup *) None
404404
in
405-
match try load ?lock_kind root_dir with OpamPp.Bad_version _ -> None with
405+
match try load ~lock_kind root_dir with OpamPp.Bad_version _ -> None with
406406
| None ->
407407
update ?current_switch ();
408408
None

src/state/opamStateConfig.mli

+10-10
Original file line numberDiff line numberDiff line change
@@ -92,8 +92,8 @@ val opamroot_with_provenance: ?root_dir:dirname -> unit -> provenance * dirname
9292
val opamroot: ?root_dir:dirname -> unit -> dirname
9393

9494
(** Loads the global configuration file, protecting against concurrent writes *)
95-
val load: ?lock_kind: 'a lock -> dirname -> OpamFile.Config.t option
96-
val safe_load: ?lock_kind: 'a lock -> dirname -> OpamFile.Config.t
95+
val load: lock_kind: 'a lock -> dirname -> OpamFile.Config.t option
96+
val safe_load: lock_kind: 'a lock -> dirname -> OpamFile.Config.t
9797

9898
(** Loads the config file from the OPAM root and updates default values for all
9999
related OpamXxxConfig modules. Doesn't read the env yet, the {!init}
@@ -102,7 +102,7 @@ val safe_load: ?lock_kind: 'a lock -> dirname -> OpamFile.Config.t
102102
103103
Returns the config file that was found, if any *)
104104
val load_defaults:
105-
?lock_kind:'a lock -> OpamFilename.Dir.t -> OpamFile.Config.t option
105+
lock_kind:'a lock -> OpamFilename.Dir.t -> OpamFile.Config.t option
106106

107107
(** Returns the current switch, failing with an error message is none is set. *)
108108
val get_switch: unit -> switch
@@ -124,31 +124,31 @@ val resolve_local_switch: OpamFilename.Dir.t -> switch -> switch
124124

125125
(** Given the required lock, returns [true] if the opam root is newer than the
126126
binary, so that it can only be loaded read-only by the current binary. *)
127-
val is_newer_than_self: ?lock_kind:'a lock -> 'b global_state -> bool
127+
val is_newer_than_self: lock_kind:'a lock -> 'b global_state -> bool
128128

129129
(** Check config root version regarding self-defined one *)
130130
val is_newer: OpamFile.Config.t -> bool
131131

132132
val load_config_root:
133-
?lock_kind:'a lock ->
133+
lock_kind:'a lock ->
134134
((OpamFile.Config.t OpamFile.t -> 'b) * (OpamFile.Config.t OpamFile.t -> 'b)) ->
135135
dirname -> 'b
136136

137137
module Switch : sig
138138
val safe_load_t:
139-
?lock_kind: 'a lock -> dirname -> switch -> OpamFile.Switch_config.t
139+
lock_kind: 'a lock -> dirname -> switch -> OpamFile.Switch_config.t
140140
val safe_load:
141-
?lock_kind: 'a lock -> 'b global_state -> switch -> OpamFile.Switch_config.t
141+
lock_kind: 'a lock -> 'b global_state -> switch -> OpamFile.Switch_config.t
142142
val safe_read_selections:
143-
?lock_kind: 'a lock -> 'b global_state -> switch -> switch_selections
143+
lock_kind: 'a lock -> 'b global_state -> switch -> switch_selections
144144
val read_opt:
145-
?lock_kind: 'a lock -> 'b global_state -> switch ->
145+
lock_kind: 'a lock -> 'b global_state -> switch ->
146146
OpamFile.Switch_config.t option
147147
end
148148

149149
module Repos : sig
150150
val safe_read:
151-
?lock_kind: 'a lock -> 'b global_state -> OpamFile.Repos_config.t
151+
lock_kind: 'a lock -> 'b global_state -> OpamFile.Repos_config.t
152152
end
153153

154154
(* Raw read an switch config to downgrade its [opam-version] from 2.1 to 2.0.

src/state/opamSwitchState.ml

+7-6
Original file line numberDiff line numberDiff line change
@@ -18,11 +18,11 @@ let slog = OpamConsole.slog
1818

1919
open OpamStateTypes
2020

21-
let load_selections ?lock_kind gt switch =
22-
OpamStateConfig.Switch.safe_read_selections ?lock_kind gt switch
21+
let load_selections ~lock_kind gt switch =
22+
OpamStateConfig.Switch.safe_read_selections ~lock_kind gt switch
2323

24-
let load_switch_config ?lock_kind gt switch =
25-
match OpamStateConfig.Switch.read_opt ?lock_kind gt switch with
24+
let load_switch_config ~lock_kind gt switch =
25+
match OpamStateConfig.Switch.read_opt ~lock_kind gt switch with
2626
| Some c -> c
2727
| exception (OpamPp.Bad_version _ as e) ->
2828
OpamFormatUpgrade.hard_upgrade_from_2_1_intermediates
@@ -257,7 +257,7 @@ let load lock_kind gt rt switch =
257257
OpamFilename.flock lock_kind (OpamPath.Switch.lock gt.root switch)
258258
in
259259
let switch_config = load_switch_config ~lock_kind gt switch in
260-
if OpamStateConfig.is_newer_than_self gt then
260+
if OpamStateConfig.is_newer_than_self ~lock_kind gt then
261261
log "root version (%s) is greater than running binary's (%s); \
262262
load with best-effort (read-only)"
263263
(OpamVersion.to_string (OpamFile.Config.opam_root_version gt.config))
@@ -672,7 +672,8 @@ let drop st =
672672
let _ = unlock st in ()
673673

674674
let with_write_lock ?dontblock st f =
675-
if OpamStateConfig.is_newer_than_self st.switch_global then
675+
if OpamStateConfig.is_newer_than_self ~lock_kind:`Lock_write st.switch_global
676+
then
676677
OpamConsole.error_and_exit `Locked
677678
"The opam root has been upgraded by a newer version of opam-state \
678679
and cannot be written to";

src/state/opamSwitchState.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ val load_virtual:
4545
(** Load the switch's state file, without constructing the package maps: much
4646
faster than loading the full switch state *)
4747
val load_selections:
48-
?lock_kind: 'a lock -> 'b global_state -> switch -> switch_selections
48+
lock_kind: 'a lock -> 'b global_state -> switch -> switch_selections
4949

5050
(** Raw function to compute the availability of all packages, in [opams], given
5151
the switch configuration and the set of pinned packages. (The result is

0 commit comments

Comments
 (0)