Skip to content

Commit

Permalink
Merge pull request #4945 from kit-ty-kate/backport-4908-2.1
Browse files Browse the repository at this point in the history
Backport #4908 on opam 2.1
  • Loading branch information
kit-ty-kate authored Dec 3, 2021
2 parents 83fe748 + d8be1b2 commit b3fdd6c
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 10 deletions.
3 changes: 3 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,9 @@ New option/command/subcommand are prefixed with ◈.

## Global CLI
*
* Fix typo in error message for opam var [#4786 @kit-ty-kate - fix #4785]
* Add cli 2.2 handling [#4853 @rjbou]
* --no-depexts is the default in CLI 2.0 mode [#4908 @dra27]

## Plugins
*
Expand Down
4 changes: 2 additions & 2 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -600,7 +600,7 @@ let create_build_options
assume_depexts; no_depexts;
}

let apply_build_options b =
let apply_build_options cli b =
let open OpamStd.Option.Op in
let flag f = if f then Some true else None in
OpamRepositoryConfig.update
Expand All @@ -624,7 +624,7 @@ let apply_build_options b =
OpamPackage.Name.Set.of_list)
?unlock_base:(flag b.unlock_base)
?locked:(if b.locked then Some (Some b.lock_suffix) else None)
?no_depexts:(flag b.no_depexts)
?no_depexts:(flag (b.no_depexts || OpamCLIVersion.Op.(cli @= cli2_0)))
();
OpamClientConfig.update
?keep_build_dir:(flag b.keep_build_dir)
Expand Down
2 changes: 1 addition & 1 deletion src/client/opamArg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ val recurse: OpamCLIVersion.Sourced.t -> bool Term.t
val subpath: OpamCLIVersion.Sourced.t -> string option Term.t

(** Applly build options *)
val apply_build_options: build_options -> unit
val apply_build_options: OpamCLIVersion.Sourced.t -> build_options -> unit

(** Lock options *)
val locked: ?section:string -> OpamCLIVersion.Sourced.t -> bool Term.t
Expand Down
14 changes: 7 additions & 7 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -311,7 +311,7 @@ let init cli =
show_opamrc bypass_checks
() =
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
(* If show option is set, dump opamrc and exit *)
if show_opamrc then
(OpamFile.InitConfig.write_to_channel stdout @@
Expand Down Expand Up @@ -1615,7 +1615,7 @@ let install cli =
restore destdir assume_built check recurse subpath depext_only
download_only atoms_or_locals () =
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
if atoms_or_locals = [] && not restore then
`Error (true, "required argument PACKAGES is missing")
else
Expand Down Expand Up @@ -1731,7 +1731,7 @@ let remove cli =
let remove global_options build_options autoremove force destdir recurse
subpath atom_locs () =
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
OpamGlobalState.with_ `Lock_none @@ fun gt ->
match destdir with
| Some d ->
Expand Down Expand Up @@ -1804,7 +1804,7 @@ let reinstall cli =
let reinstall global_options build_options assume_built recurse subpath
atoms_locs cmd () =
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
let open OpamPackage.Set.Op in
OpamGlobalState.with_ `Lock_none @@ fun gt ->
match cmd, atoms_locs with
Expand Down Expand Up @@ -1975,7 +1975,7 @@ let upgrade cli =
let upgrade global_options build_options fixup check only_installed all
recurse subpath atom_locs () =
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
let all = all || atom_locs = [] in
OpamGlobalState.with_ `Lock_none @@ fun gt ->
if fixup then
Expand Down Expand Up @@ -2553,7 +2553,7 @@ let switch cli =
OpamConsole.warning "Option %s is deprecated, ignoring it."
(OpamConsole.colorise `bold "--no-autoinstall");
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
let invariant_arg ?repos rt args =
match args, packages, formula, empty with
| [], None, None, false -> None
Expand Down Expand Up @@ -3107,7 +3107,7 @@ let pin ?(unpin_only=false) cli =
with_version
command params () =
apply_global_options cli global_options;
apply_build_options build_options;
apply_build_options cli build_options;
let locked = OpamStateConfig.(!r.locked) <> None in
let action = not no_act in
let get_command = function
Expand Down

0 comments on commit b3fdd6c

Please sign in to comment.