Skip to content

Commit

Permalink
Revert "attempt to move checkums flags from build options to global o…
Browse files Browse the repository at this point in the history
…ption. The counterpart of that is that we loose the fact that the newly effective options (in opam source for ex) are not flaggued as new in cli 2.2"

This reverts commit a2e7b21ccaad48ca11432e9fbd0a7a2c90377aee.
  • Loading branch information
rjbou committed Nov 22, 2024
1 parent e6066a2 commit a5171aa
Show file tree
Hide file tree
Showing 3 changed files with 45 additions and 35 deletions.
56 changes: 25 additions & 31 deletions src/client/opamArg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -460,8 +460,6 @@ type global_options = {
no_auto_upgrade : bool;
working_dir : bool;
ignore_pin_depends : bool;
no_checksums: bool;
req_checksums : bool;
cli : OpamCLIVersion.t;
}

Expand All @@ -473,7 +471,6 @@ let create_global_options
opt_root external_solver use_internal_solver
cudf_file solver_preferences best_effort safe_mode json no_auto_upgrade
working_dir ignore_pin_depends
no_checksums req_checksums
d_no_aspcud _ =
if d_no_aspcud then
OpamConsole.warning
Expand All @@ -490,9 +487,7 @@ let create_global_options
{ git_version; debug_level; verbose; quiet; color; opt_switch; confirm_level; yes;
strict; opt_root; external_solver; use_internal_solver;
cudf_file; solver_preferences; best_effort; safe_mode; json;
no_auto_upgrade; working_dir; ignore_pin_depends;
no_checksums; req_checksums;
cli }
no_auto_upgrade; working_dir; ignore_pin_depends; cli }

let apply_global_options cli o =
if o.git_version then (
Expand Down Expand Up @@ -539,10 +534,7 @@ let apply_global_options cli o =
(* - repository options - *)
(* ?download_tool:(OpamTypes.arg list * dl_tool_kind) Lazy.t *)
(* ?retries:int *)
?force_checksums:(if o.req_checksums then Some (Some true)
else if o.no_checksums then Some (Some false)
else None)
(* ?repo_tarring: bool *)
(* ?force_checksums:bool option *)
(* - solver options *)
?cudf_file:(some o.cudf_file)
?solver
Expand Down Expand Up @@ -641,6 +633,8 @@ type build_options = {
reuse_build_dir: bool;
inplace_build : bool;
make : string option;
no_checksums : bool;
req_checksums : bool;
build_test : bool;
build_doc : bool;
dev_setup : bool;
Expand All @@ -659,29 +653,28 @@ type build_options = {
}

let create_build_options
keep_build_dir reuse_build_dir inplace_build make
build_test build_doc dev_setup show dryrun skip_update
keep_build_dir reuse_build_dir inplace_build make no_checksums
req_checksums build_test build_doc dev_setup show dryrun skip_update
fake jobs ignore_constraints_on unlock_base locked lock_suffix
assume_depexts no_depexts verbose_on
=
{
keep_build_dir; reuse_build_dir; inplace_build; make;
build_test; build_doc; dev_setup; show; dryrun; skip_update;
keep_build_dir; reuse_build_dir; inplace_build; make; no_checksums;
req_checksums; build_test; build_doc; dev_setup; show; dryrun; skip_update;
fake; jobs; ignore_constraints_on; unlock_base; locked; lock_suffix;
assume_depexts; no_depexts; verbose_on;
}

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
(* ?download_tool:(OpamTypes.arg list * dl_tool_kind) Lazy.t *)
(* ?retries:int *)
(* ?force_checksums:bool option *)
(* ?repo_tarring: bool *)
?force_checksums:(if b.req_checksums then Some (Some true)
else if b.no_checksums then Some (Some false)
else None)
();
*)
OpamStateConfig.update
(* ?root: -- handled globally *)
?jobs:(b.jobs >>| fun j -> lazy j)
Expand Down Expand Up @@ -1393,25 +1386,13 @@ let global_options cli =
through $(i,opam pin) or through $(i,opam install DIR). This is \
equivalent to setting $(b,IGNOREPINDEPENDS=true)."
in
let no_checksums =
mk_flag ~cli cli_original ~section ["no-checksums"]
"Do not verify the checksum of downloaded archives.\
This is equivalent to setting $(b,\\$OPAMNOCHECKSUMS) to \"true\"."
in
let req_checksums =
mk_flag ~cli cli_original ~section ["require-checksums"]
"Reject the installation of packages that don't provide a checksum for \
the upstream archives. \ This is equivalent to setting \
$(b,\\$OPAMREQUIRECHECKSUMS) to \"true\"."
in
Term.(const create_global_options
$git_version $debug $debug_level $verbose $quiet $color $switch
$yes $confirm_level
$strict $root $external_solver
$use_internal_solver $cudf_file $solver_preferences $best_effort
$safe_mode $json_flag $no_auto_upgrade $working_dir
$ignore_pin_depends
$no_checksums $req_checksums
$d_no_aspcud $cli_arg)

(* lock options *)
Expand All @@ -1431,6 +1412,17 @@ let lock_suffix ?section cli =
"Set locked files suffix to $(i,SUFFIX)."
Arg.(string) ("locked")

(* Checksums options *)
let no_checksums ?section cli from_cli =
mk_flag ~cli from_cli ?section ["no-checksums"]
"Do not verify the checksum of downloaded archives.\
This is equivalent to setting $(b,\\$OPAMNOCHECKSUMS) to \"true\"."
let require_checksums ?section cli from_cli =
mk_flag ~cli from_cli ?section ["require-checksums"]
"Reject the installation of packages that don't provide a checksum for\
the upstream archives. This is equivalent to setting \
$(b,\\$OPAMREQUIRECHECKSUMS) to \"true\"."

(* Options common to all build commands *)
let build_option_section = "PACKAGE BUILD OPTIONS"
let man_build_option_section =
Expand Down Expand Up @@ -1459,6 +1451,8 @@ let build_options cli =
affects packages that are explicitly listed on the command-line. \
This is equivalent to setting $(b,\\$OPAMINPLACEBUILD) to \"true\"."
in
let no_checksums = no_checksums ~section cli cli_original in
let req_checksums = require_checksums ~section cli cli_original in
let build_test =
mk_flag_replaced ~cli ~section [
cli_between cli2_0 cli2_1 ~replaced:"--with-test", ["build-test"];
Expand Down Expand Up @@ -1551,7 +1545,7 @@ let build_options cli =
in
Term.(const create_build_options
$keep_build_dir $reuse_build_dir $inplace_build $make
$build_test $build_doc $dev_setup $show
$no_checksums $req_checksums $build_test $build_doc $dev_setup $show
$dryrun $skip_update $fake $jobs_flag ~section cli cli_original
$ignore_constraints_on $unlock_base $locked $lock_suffix
$assume_depexts $no_depexts $verbose_on)
Expand Down
8 changes: 6 additions & 2 deletions src/client/opamArg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -176,8 +176,6 @@ type global_options = {
no_auto_upgrade : bool;
working_dir : bool;
ignore_pin_depends : bool;
no_checksums: bool;
req_checksums : bool;
cli : OpamCLIVersion.t;
}

Expand Down Expand Up @@ -215,6 +213,12 @@ val apply_build_options: OpamCLIVersion.Sourced.t -> build_options -> unit
val locked: ?section:string -> OpamCLIVersion.Sourced.t -> bool Term.t
val lock_suffix: ?section:string -> OpamCLIVersion.Sourced.t -> string Term.t

(** Checksum options *)
val no_checksums:
?section:string -> OpamCLIVersion.Sourced.t -> validity -> bool Term.t
val require_checksums:
?section:string -> OpamCLIVersion.Sourced.t -> validity -> bool Term.t

(** {3 Package listing and filtering options} *)

(** Man section name *)
Expand Down
16 changes: 14 additions & 2 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3710,8 +3710,19 @@ let source cli =
"Choose package without consideration for \
the current (or any other) switch (installed or pinned packages, etc.)"
in
let source global_options atom dev_repo pin no_switch dir () =
let no_checksums = no_checksums cli (cli_from cli2_2) in
let req_checksums = require_checksums cli (cli_from cli2_2) in
let source global_options atom dev_repo pin no_switch dir
no_checksums req_checksums () =
apply_global_options cli global_options;
let force_checksums =
if req_checksums then Some (Some true)
else if no_checksums then Some (Some false)
else None
in
OpamStd.Option.iter (fun force_checksums ->
OpamRepositoryConfig.update ~force_checksums ())
force_checksums;
OpamGlobalState.with_ `Lock_none @@ fun gt ->
let get_package_dir t =
let nv =
Expand Down Expand Up @@ -3839,7 +3850,8 @@ let source cli =
mk_command ~cli cli_original "source" ~doc ~man
Term.(const source
$global_options cli
$atom $dev_repo $pin $no_switch $dir)
$atom $dev_repo $pin $no_switch $dir
$no_checksums $req_checksums)

(* LINT *)
let lint_doc = "Checks and validate package description ('opam') files."
Expand Down

0 comments on commit a5171aa

Please sign in to comment.