diff --git a/doc/pages/FAQ.md b/doc/pages/FAQ.md index 6f5edbb2823..0629fbb8108 100644 --- a/doc/pages/FAQ.md +++ b/doc/pages/FAQ.md @@ -411,3 +411,27 @@ you could lose your opam configuration at each reboot. You can use the [`nfsopam`](https://github.com/UnixJunkie/nfsopam) script to have the best of both worlds: persistence of NFS directories and fast operations of local directories. + +--- + +#### 🐫 What does the `--cli` option do? Should I be using it everywhere? + +`--cli` was introduced in opam 2.1 to deal with changes in the command line +interface between releases. It tells opam to interpret the command line as a +specific version, in particular it means that new options or options which +have had their meaning altered will not be available, or will be behave as they +did in that version. It only affects the command-line - it does not, for +example, stop a root from being upgraded from an older version to the current +version. + +We recommend using it in scripts (and programs which call opam) since they can +then expect to work seamlessly with future versions of the opam client. It's +also a good idea to use it in blog posts, or other documentation you may share, +since it allows copy-and-paste to work reliably (a user with a newer version of +opam should have no issues and a user with an older opam gets a clearer error +message). + +We don't recommend using it in day-to-day use of opam in the shell, because +you'll be typing more and you won't get to notice exciting new features! If the +behaviour of a command or option is altered, and you write something which in no +longer valid, opam will try to tell you what the new command should look like. diff --git a/doc/pages/Usage.md b/doc/pages/Usage.md index f61f3f68d20..6306145370b 100644 --- a/doc/pages/Usage.md +++ b/doc/pages/Usage.md @@ -45,6 +45,14 @@ you find a package there but not on your computer, either it has been recently added and you should simply run `opam update`, or it's not available on your system or OCaml version — `opam install PACKAGE` will give you the reason. +## `--cli` option + +Since opam 2.1, opam is able to be invoked using a previous version of its +command line. It's recommended that all opam commands in scripts use it, and +also blog posts and other sources of information, so you may come across +examples which include it. We don't recommend using it in the shell because it's +more to type! + ## Details on commands ### opam init diff --git a/master_changes.md b/master_changes.md index de38d98de3c..26c4bac23b1 100644 --- a/master_changes.md +++ b/master_changes.md @@ -3,6 +3,9 @@ note. Possibly scripts breaking changes are prefixed with ✘. New option/command/subcommand are prefixed with ◈. +## Global CLI + * ◈ --cli / OPAMCLI option added [#4316 @dra27] + ## Init * diff --git a/src/client/opamAdminCommand.ml b/src/client/opamAdminCommand.ml index 8d40f8f159a..a50c3a8281e 100644 --- a/src/client/opamAdminCommand.ml +++ b/src/client/opamAdminCommand.ml @@ -14,6 +14,8 @@ open OpamProcess.Job.Op open OpamStateTypes open Cmdliner +type command = unit Cmdliner.Term.t * Cmdliner.Term.info + let checked_repo_root () = let repo_root = OpamFilename.cwd () in if not (OpamFilename.exists_dir (OpamRepositoryPath.packages_dir repo_root)) @@ -23,6 +25,9 @@ let checked_repo_root () = Please make sure there is a \"packages%s\" directory" OpamArg.dir_sep; repo_root +let global_options cli = + let apply_cli options = {options with OpamArg.cli} in + Term.(const apply_cli $ OpamArg.global_options) let admin_command_doc = "Tools for repository administrators" @@ -41,7 +46,7 @@ let admin_command_man = [ let index_command_doc = "Generate an inclusive index file for serving over HTTP." -let index_command = +let index_command cli = let command = "index" in let doc = index_command_doc in let man = [ @@ -116,7 +121,7 @@ let index_command = OpamHTTP.make_index_tar_gz repo_root; OpamConsole.msg "Done.\n"; in - Term.(const cmd $ OpamArg.global_options $ urls_txt_arg), + Term.(const cmd $ global_options cli $ urls_txt_arg), OpamArg.term_info command ~doc ~man @@ -174,7 +179,7 @@ let package_files_to_cache repo_root cache_dir ?link (nv, prefix) = OpamProcess.Job.seq urls OpamPackage.Map.empty let cache_command_doc = "Fills a local cache of package archives" -let cache_command = +let cache_command cli = let command = "cache" in let doc = cache_command_doc in let man = [ @@ -251,13 +256,13 @@ let cache_command = OpamConsole.msg "Done.\n"; in - Term.(const cmd $ OpamArg.global_options $ + Term.(const cmd $ global_options cli $ cache_dir_arg $ no_repo_update_arg $ link_arg $ jobs_arg), OpamArg.term_info command ~doc ~man let add_hashes_command_doc = "Add archive hashes to an opam repository." -let add_hashes_command = +let add_hashes_command cli = let command = "add-hashes" in let doc = add_hashes_command_doc in let cache_dir = OpamFilename.Dir.of_string "~/.cache/opam-hash-cache" in @@ -479,13 +484,13 @@ let add_hashes_command = if has_error then OpamStd.Sys.exit_because `Sync_error else OpamStd.Sys.exit_because `Success in - Term.(const cmd $ OpamArg.global_options $ + Term.(const cmd $ global_options cli $ hash_types_arg $ replace_arg $ packages), OpamArg.term_info command ~doc ~man let upgrade_command_doc = "Upgrades repository from earlier opam versions." -let upgrade_command = +let upgrade_command cli = let command = "upgrade" in let doc = upgrade_command_doc in let man = [ @@ -533,13 +538,13 @@ let upgrade_command = \ opam admin index" | Some m -> OpamAdminRepoUpgrade.do_upgrade_mirror (OpamFilename.cwd ()) m in - Term.(const cmd $ OpamArg.global_options $ + Term.(const cmd $ global_options cli $ clear_cache_arg $ create_mirror_arg), OpamArg.term_info command ~doc ~man let lint_command_doc = "Runs 'opam lint' and reports on a whole repository" -let lint_command = +let lint_command cli = let command = "lint" in let doc = lint_command_doc in let man = [ @@ -616,14 +621,14 @@ let lint_command = in OpamStd.Sys.exit_because (if ret then `Success else `False) in - Term.(const cmd $ OpamArg.global_options $ + Term.(const cmd $ global_options cli $ short_arg $ list_arg $ include_arg $ exclude_arg $ ignore_arg $ warn_error_arg), OpamArg.term_info command ~doc ~man let check_command_doc = "Runs some consistency checks on a repository" -let check_command = +let check_command cli = let command = "check" in let doc = check_command_doc in let man = [ @@ -700,7 +705,7 @@ let check_command = (pr obsolete "obsolete packages")); OpamStd.Sys.exit_because (if all_ok then `Success else `False) in - Term.(const cmd $ OpamArg.global_options $ ignore_test_arg $ print_short_arg + Term.(const cmd $ global_options cli $ ignore_test_arg $ print_short_arg $ installability_arg $ cycles_arg $ obsolete_arg), OpamArg.term_info command ~doc ~man @@ -796,7 +801,7 @@ let or_arg = criteria, select packages that match $(i,any) of them") let list_command_doc = "Lists packages from a repository" -let list_command = +let list_command cli = let command = "list" in let doc = list_command_doc in let man = [ @@ -849,13 +854,13 @@ let list_command = in OpamListCommand.display st format results in - Term.(const cmd $ OpamArg.global_options $ OpamArg.package_selection $ + Term.(const cmd $ global_options cli $ OpamArg.package_selection $ or_arg $ state_selection_arg $ OpamArg.package_listing $ env_arg $ pattern_list_arg), OpamArg.term_info command ~doc ~man let filter_command_doc = "Filters a repository to only keep selected packages" -let filter_command = +let filter_command cli = let command = "filter" in let doc = filter_command_doc in let man = [ @@ -936,14 +941,14 @@ let filter_command = OpamFilename.rmdir_cleanup d)) pkg_prefixes in - Term.(const cmd $ OpamArg.global_options $ OpamArg.package_selection $ or_arg $ + Term.(const cmd $ global_options cli $ OpamArg.package_selection $ or_arg $ state_selection_arg $ env_arg $ remove_arg $ dryrun_arg $ pattern_list_arg), OpamArg.term_info command ~doc ~man let add_constraint_command_doc = "Adds version constraints on all dependencies towards a given package" -let add_constraint_command = +let add_constraint_command cli = let command = "add-constraint" in let doc = add_constraint_command_doc in let man = [ @@ -1044,7 +1049,7 @@ let add_constraint_command = |> OpamFile.OPAM.with_conflicts conflicts)) pkg_prefixes in - Term.(pure cmd $ OpamArg.global_options $ force_arg $ atom_arg), + Term.(pure cmd $ global_options cli $ force_arg $ atom_arg), OpamArg.term_info command ~doc ~man (* HELP *) @@ -1073,20 +1078,22 @@ let help = Term.(ret (const help $Term.man_format $Term.choice_names $topic)), Term.info "help" ~doc ~man -let admin_subcommands = [ - index_command; OpamArg.make_command_alias index_command "make"; - cache_command; - upgrade_command; - lint_command; - check_command; - list_command; - filter_command; - add_constraint_command; - add_hashes_command; - help; -] +let admin_subcommands cli = + let index_command = index_command cli in + [ + index_command; OpamArg.make_command_alias index_command "make"; + cache_command cli; + upgrade_command cli; + lint_command cli; + check_command cli; + list_command cli; + filter_command cli; + add_constraint_command cli; + add_hashes_command cli; + help; + ] -let default_subcommand = +let default_subcommand cli = let man = admin_command_man @ [ `S "COMMANDS"; @@ -1111,9 +1118,12 @@ let default_subcommand = cache_command_doc upgrade_command_doc in - Term.(const usage $ OpamArg.global_options), + Term.(const usage $ global_options cli), Term.info "opam admin" ~version:(OpamVersion.to_string OpamVersion.current) ~sdocs:OpamArg.global_option_section ~doc:admin_command_doc ~man + +let get_cmdliner_parser cli = + default_subcommand cli, admin_subcommands cli diff --git a/src/client/opamAdminCommand.mli b/src/client/opamAdminCommand.mli index e0b616fb049..21f587cc98f 100644 --- a/src/client/opamAdminCommand.mli +++ b/src/client/opamAdminCommand.mli @@ -11,6 +11,6 @@ val admin_command_doc: string -val admin_subcommands: (unit Cmdliner.Term.t * Cmdliner.Term.info) list +type command = unit Cmdliner.Term.t * Cmdliner.Term.info -val default_subcommand: unit Cmdliner.Term.t * Cmdliner.Term.info +val get_cmdliner_parser: OpamCLIVersion.t -> command * command list diff --git a/src/client/opamArg.ml b/src/client/opamArg.ml index 0651d659bac..50307c2bc3f 100644 --- a/src/client/opamArg.ml +++ b/src/client/opamArg.ml @@ -35,6 +35,7 @@ type global_options = { no_auto_upgrade : bool; working_dir : bool; ignore_pin_depends : bool; + cli : OpamCLIVersion.t; } let deprecated_option option absent name instead = @@ -45,21 +46,23 @@ let deprecated_option option absent name instead = | None -> "" | Some instead -> Printf.sprintf " You can use %s instead." instead) +(* The --cli passed by cmdliner is ignored (it's only there for --help) *) let create_global_options git_version debug debug_level verbose quiet color opt_switch 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 - d_no_aspcud = + d_no_aspcud _ = deprecated_option d_no_aspcud false "no-aspcud" None; let debug_level = OpamStd.Option.Op.( debug_level >>+ fun () -> if debug then Some 1 else None ) in let verbose = List.length verbose in + let cli = OpamCLIVersion.current in { git_version; debug_level; verbose; quiet; color; opt_switch; 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_auto_upgrade; working_dir; ignore_pin_depends; cli } let apply_global_options o = if o.git_version then ( @@ -135,6 +138,7 @@ let apply_global_options o = (* ?pin_kind_auto:bool *) (* ?autoremove:bool *) (* ?editor:string *) + ~cli:o.cli (); if OpamClientConfig.(!r.json_out <> None) then ( OpamJson.append "opam-version" (`String OpamVersion.(to_string (full ()))); @@ -215,6 +219,17 @@ let apply_build_options b = let when_enum = [ "always", `Always; "never", `Never; "auto", `Auto ] +(* Windows directory separators need to be escaped for manpages *) +let dir_sep, escape_path = + match Filename.dir_sep with + | "\\" -> + let esc = "\\\\" in + esc, + fun p -> + OpamStd.List.concat_map esc (fun x -> x) + (OpamStd.String.split_delim p '\\') + | ds -> ds, fun x -> x + (* Help sections common to all commands *) let global_option_section = "COMMON OPTIONS" let help_sections = [ @@ -233,6 +248,7 @@ let help_sections = [ `P "$(i,OPAMBESTEFFORTPREFIXCRITERIA) sets the string that must be prepended \ to the criteria when the `--best-effort` option is set, and is expected \ to maximise the `opam-query` property in the solution "; + `P "$(i,OPAMCLI) see option `--cli'"; `P "$(i,OPAMCOLOR), when set to $(i,always) or $(i,never), sets a default \ value for the --color option."; `P "$(i,OPAMCRITERIA) specifies user $(i,preferences) for dependency \ @@ -342,6 +358,26 @@ let help_sections = [ `P "$(i,OPAMWORKINGDIR) see option `--working-dir`"; `P "$(i,OPAMYES) see option `--yes'."; + `S "CLI VERSION"; + `P "All scripts and programmatic invocations of opam should use `--cli' in \ + order to ensure that they work seamlessly with future versions of the \ + opam client. Additionally, blog posts or other documentation can \ + benefit, as it prevents information from becoming stale."; + `P (Printf.sprintf + "Although opam only supports roots ($(i,~%s.opam%s)) for the current \ + version, it does provide backwards compatibility for its command-line \ + interface." dir_sep dir_sep); + `P "The command-line version is selected by using the `--cli' option or the \ + $(i,OPAMCLI) environment variable. `--cli' may be specified more than \ + once, where the last instance takes precedence. $(i,OPAMCLI) is only \ + inspected if `--cli' is not given."; + `P "Since CLI version support was only added in opam 2.1, use $(i,OPAMCLI) \ + to select 2.0 support (as opam 2.0 will just ignore it), and `--cli=2.1' \ + for 2.1 later versions, since an environment variable controlling the \ + parsing of syntax is brittle. To this end, opam displays a warning if \ + $(i,OPAMCLI) specifies a valid version other than 2.0, and also if \ + `--cli=2.0' is specified."; + `S "EXIT STATUS"; `P "As an exception to the following, the `exec' command returns 127 if the \ command was not found or couldn't be executed, and the command's exit \ @@ -414,17 +450,6 @@ let help_sections = [ (* Converters *) -(* Windows directory separator need to be escaped for manpage *) -let dir_sep, escape_path = - match Filename.dir_sep with - | "\\" -> - let esc = "\\\\" in - esc, - fun p -> - OpamStd.List.concat_map esc (fun x -> x) - (OpamStd.String.split_delim p '\\') - | ds -> ds, fun x -> x - let pr_str = Format.pp_print_string let repository_name = @@ -982,6 +1007,17 @@ let global_options = mk_tristate_opt ~section ["color"] "WHEN" (Printf.sprintf "Colorize the output. $(docv) must be %s." (Arg.doc_alts_enum when_enum)) in + (* The --cli option is pre-processed, because it has to be able to appear + before sub-commands. The one here is present only for --help. *) + let cli_arg = + mk_opt ~section ["cli"] "MAJOR.MINOR" + "Use the command-line interface syntax and semantics of $(docv). \ + Intended for any persistent use of opam (scripts, blog posts, etc.), \ + any version of opam in the same MAJOR series will behave as for the \ + specified MINOR release. The flag was not available in opam 2.0, so for \ + 2.0, use $(b,\\$OPAMCLI). This is equivalent to setting $(b,\\$OPAMCLI) \ + to $(i,MAJOR.MINOR)." + Arg.string (OpamCLIVersion.to_string OpamCLIVersion.current) in let switch = mk_opt ~section ["switch"] "SWITCH" "Use $(docv) as the current compiler switch. \ @@ -1091,7 +1127,7 @@ let global_options = $use_internal_solver $cudf_file $solver_preferences $best_effort $safe_mode $json_flag $no_auto_upgrade $working_dir $ignore_pin_depends - $d_no_aspcud) + $d_no_aspcud $cli_arg) (* lock options *) let locked section = diff --git a/src/client/opamArg.mli b/src/client/opamArg.mli index f788a3d94e2..6a5bad8b70c 100644 --- a/src/client/opamArg.mli +++ b/src/client/opamArg.mli @@ -102,6 +102,7 @@ type global_options = { no_auto_upgrade : bool; working_dir : bool; ignore_pin_depends : bool; + cli : OpamCLIVersion.t; } (** Global options *) diff --git a/src/client/opamCLIVersion.ml b/src/client/opamCLIVersion.ml new file mode 100644 index 00000000000..5f60c1eb489 --- /dev/null +++ b/src/client/opamCLIVersion.ml @@ -0,0 +1,52 @@ +(**************************************************************************) +(* *) +(* Copyright 2020 David Allsopp Ltd. *) +(* *) +(* All rights reserved. This file is distributed under the terms of the *) +(* GNU Lesser General Public License version 2.1, with the special *) +(* exception on linking described in the file LICENSE. *) +(* *) +(**************************************************************************) + +type t = int * int + +let supported_versions = [(2, 0); (2, 1)] + +let is_supported v = List.mem v supported_versions + +let of_string s = + match String.index s '.' with + | i when s.[0] <> '0' && (i >= String.length s - 2 || s.[i + 1] <> '0') -> + begin + try Scanf.sscanf s "%u.%u%!" (fun major minor -> (major, minor)) + with Scanf.Scan_failure _ -> failwith "OpamVersion.CLI.of_string" + end + | _ + | exception Not_found -> failwith "OpamVersion.CLI.of_string" + +let current = of_string @@ OpamVersion.(to_string current_nopatch) + +let of_string_opt s = try Some (of_string s) with Failure _ -> None + +let to_string (major, minor) = Printf.sprintf "%d.%d" major minor + +let to_json v = `String (to_string v) +let of_json = function +| `String x -> of_string_opt x +| _ -> None + +let env = OpamStd.Config.env of_string + +let ( >= ) = Stdlib.( >= ) +let ( < ) = Stdlib.( < ) + +module O = struct + type nonrec t = t + let to_string = to_string + let to_json = to_json + let of_json = of_json + let compare = compare +end + +module Set = OpamStd.Set.Make(O) +module Map = OpamStd.Map.Make(O) diff --git a/src/client/opamCLIVersion.mli b/src/client/opamCLIVersion.mli new file mode 100644 index 00000000000..f2994a89bbb --- /dev/null +++ b/src/client/opamCLIVersion.mli @@ -0,0 +1,31 @@ +(**************************************************************************) +(* *) +(* Copyright 2020 David Allsopp Ltd. *) +(* *) +(* All rights reserved. This file is distributed under the terms of the *) +(* GNU Lesser General Public License version 2.1, with the special *) +(* exception on linking described in the file LICENSE. *) +(* *) +(**************************************************************************) + +(** CLI Versions *) + +include OpamStd.ABSTRACT + +(** The current version of the CLI (major and minor of OpamVersion.current *) +val current : t + +(** Tests whether a valid CLI version is supported by the client library *) +val is_supported : t -> bool + +(** Parse the given environment variable as MAJOR.MINOR *) +val env: OpamStd.Config.env_var -> t option + +(** ['a option] version of {!to_string} *) +val of_string_opt : string -> t option + +(** Comparison [>]] with [(major, minor)] *) +val ( >= ) : t -> int * int -> bool + +(** Comparison [<] with [(major, minor)] *) +val ( < ) : t -> int * int -> bool diff --git a/src/client/opamClientConfig.ml b/src/client/opamClientConfig.ml index 3936e9a0a6c..2cae6a7e266 100644 --- a/src/client/opamClientConfig.ml +++ b/src/client/opamClientConfig.ml @@ -26,6 +26,7 @@ type t = { root_is_ok: bool; no_auto_upgrade: bool; assume_depexts: bool; + cli: OpamCLIVersion.t; } let default = { @@ -46,6 +47,7 @@ let default = { root_is_ok = false; no_auto_upgrade = false; assume_depexts = false; + cli = OpamCLIVersion.current; } type 'a options_fun = @@ -66,6 +68,7 @@ type 'a options_fun = ?root_is_ok:bool -> ?no_auto_upgrade:bool -> ?assume_depexts:bool -> + ?cli:OpamCLIVersion.t -> 'a let setk k t @@ -86,6 +89,7 @@ let setk k t ?root_is_ok ?no_auto_upgrade ?assume_depexts + ?cli = let (+) x opt = match opt with Some x -> x | None -> x in k { @@ -106,6 +110,7 @@ let setk k t root_is_ok = t.root_is_ok + root_is_ok; no_auto_upgrade = t.no_auto_upgrade + no_auto_upgrade; assume_depexts = t.assume_depexts + assume_depexts; + cli = t.cli + cli; } let set t = setk (fun x () -> x) t @@ -138,6 +143,7 @@ let initk k = ?root_is_ok:(env_bool "ROOTISOK") ?no_auto_upgrade:(env_bool "NOAUTOUPGRADE") ?assume_depexts:None + ?cli:None let init ?noop:_ = initk (fun () -> ()) diff --git a/src/client/opamClientConfig.mli b/src/client/opamClientConfig.mli index 77da78c2ad0..23655b0b6b5 100644 --- a/src/client/opamClientConfig.mli +++ b/src/client/opamClientConfig.mli @@ -29,6 +29,7 @@ type t = private { root_is_ok: bool; no_auto_upgrade: bool; assume_depexts: bool; + cli: OpamCLIVersion.t; } type 'a options_fun = @@ -50,6 +51,7 @@ type 'a options_fun = ?root_is_ok:bool -> ?no_auto_upgrade:bool -> ?assume_depexts:bool -> + ?cli:OpamCLIVersion.t -> 'a (* constraint 'a = 'b -> 'c *) @@ -86,6 +88,7 @@ val opam_init: ?root_is_ok:bool -> ?no_auto_upgrade:bool -> ?assume_depexts:bool -> + ?cli:OpamCLIVersion.t -> ?current_switch:OpamSwitch.t -> ?switch_from:OpamStateTypes.provenance -> ?jobs:int Lazy.t -> diff --git a/src/client/opamCommands.ml b/src/client/opamCommands.ml index 452401ad3b8..e7432a984f4 100644 --- a/src/client/opamCommands.ml +++ b/src/client/opamCommands.ml @@ -72,7 +72,7 @@ let switch_to_updated_self debug opamroot = updated_self_str (OpamVersion.to_string OpamVersion.current))) -let global_options = +let global_options cli = let no_self_upgrade = mk_flag ~section:global_option_section ["no-self-upgrade"] (Printf.sprintf @@ -99,7 +99,7 @@ let global_options = if not (options.safe_mode || root_is_ok) && Unix.getuid () = 0 then OpamConsole.warning "Running as root is not recommended"; - options, self_upgrade_status + {options with cli}, self_upgrade_status in Term.(const self_upgrade $ no_self_upgrade $ global_options) @@ -166,7 +166,7 @@ let get_init_config ~no_sandboxing ~no_default_config_file ~add_config_file = (* INIT *) let init_doc = "Initialize opam state, or set init options." -let init = +let init cli = let doc = init_doc in let man = [ `S "DESCRIPTION"; @@ -416,7 +416,7 @@ let init = OpamSwitchState.drop st in Term.(const init - $global_options $build_options $repo_kind_flag $repo_name $repo_url + $global_options cli $build_options $repo_kind_flag $repo_name $repo_url $interactive $update_config $setup_completion $env_hook $no_sandboxing $shell_opt $dot_profile_flag $compiler $no_compiler @@ -425,7 +425,7 @@ let init = (* LIST *) let list_doc = "Display the list of available packages." -let list ?(force_search=false) () = +let list ?(force_search=false) cli = let doc = list_doc in let selection_docs = OpamArg.package_selection_section in let display_docs = OpamArg.package_listing_section in @@ -664,7 +664,7 @@ let list ?(force_search=false) () = else if OpamSysPkg.Set.is_empty results_depexts then OpamStd.Sys.exit_because `False in - Term.(const list $global_options $package_selection $state_selector + Term.(const list $global_options cli $package_selection $state_selector $no_switch $depexts $vars $repos $owns_file $disjunction $search $silent $no_depexts $package_listing $pattern_list), term_info "list" ~doc ~man @@ -672,7 +672,7 @@ let list ?(force_search=false) () = (* SHOW *) let show_doc = "Display information about specific packages." -let show = +let show cli = let doc = show_doc in let man = [ `S "DESCRIPTION"; @@ -866,7 +866,7 @@ let show = `Ok () in Term.(ret - (const pkg_info $global_options $fields $show_empty $raw $where + (const pkg_info $global_options cli $fields $show_empty $raw $where $list_files $file $normalise $no_lint $just_file $all_versions $sort $atom_or_local_list)), term_info "show" ~doc ~man @@ -977,7 +977,7 @@ end (* VAR *) let var_doc = "Display and update the value associated with a given variable" -let var = +let var cli = let doc = var_doc in let man = [ `S "DESCRIPTION"; @@ -1017,13 +1017,13 @@ let var = 'pkg:var' instead.") in Term.ret ( - Term.(const print_var $global_options $package $varvalue $global) + Term.(const print_var $global_options cli $package $varvalue $global) ), term_info "var" ~doc ~man (* OPTION *) let option_doc = "Global and switch configuration options settings" -let option = +let option cli = let doc = option_doc in let man = [ `S "DESCRIPTION"; @@ -1050,7 +1050,7 @@ let option = var_option global global_options `option fieldvalue in Term.ret ( - Term.(const option $global_options $fieldvalue $global) + Term.(const option $global_options cli $fieldvalue $global) ), term_info "option" ~doc ~man @@ -1082,7 +1082,7 @@ end (* CONFIG *) let config_doc = "Display configuration options for packages." -let config = +let config cli = let doc = config_doc in let commands = [ "env", `env, [], @@ -1371,7 +1371,7 @@ let config = Term.ret ( Term.(const config - $global_options $command $shell_opt $sexp + $global_options cli $command $shell_opt $sexp $inplace_path $set_opamroot $set_opamswitch $params) @@ -1380,7 +1380,7 @@ let config = (* EXEC *) let exec_doc = "Executes a command in the proper opam environment" -let exec = +let exec cli = let doc = exec_doc in let man = [ `S "DESCRIPTION"; @@ -1402,14 +1402,14 @@ let exec = ~set_opamroot ~set_opamswitch ~inplace_path cmd in let open Common_config_flags in - Term.(const exec $global_options $inplace_path + Term.(const exec $global_options cli $inplace_path $set_opamroot $set_opamswitch $cmd), term_info "exec" ~doc ~man (* ENV *) let env_doc = "Prints appropriate shell variable assignments to stdout" -let env = +let env cli = let doc = env_doc in let man = [ `S "DESCRIPTION"; @@ -1460,13 +1460,13 @@ let env = in let open Common_config_flags in Term.(const env - $global_options $shell_opt $sexp $inplace_path + $global_options cli $shell_opt $sexp $inplace_path $set_opamroot $set_opamswitch $revert $check), term_info "env" ~doc ~man (* INSTALL *) let install_doc = "Install a list of packages." -let install = +let install cli = let doc = install_doc in let man = [ `S "DESCRIPTION"; @@ -1610,7 +1610,7 @@ let install = `Ok () in Term.ret - Term.(const install $global_options $build_options + Term.(const install $global_options cli $build_options $add_to_roots $deps_only $ignore_conflicts $restore $destdir $assume_built $check $recurse $subpath $depext_only $atom_or_local_list), @@ -1618,7 +1618,7 @@ let install = (* REMOVE *) let remove_doc = "Remove a list of packages." -let remove = +let remove cli = let doc = remove_doc in let man = [ `S "DESCRIPTION"; @@ -1694,12 +1694,12 @@ let remove = let autoremove = autoremove || OpamClientConfig.(!r.autoremove) in OpamSwitchState.drop (OpamClient.remove st ~autoremove ~force atoms) in - Term.(const remove $global_options $build_options $autoremove $force $destdir + Term.(const remove $global_options cli $build_options $autoremove $force $destdir $recurse $subpath $atom_or_dir_list), term_info "remove" ~doc ~man (* REINSTALL *) -let reinstall = +let reinstall cli = let doc = "Reinstall a list of packages." in let man = [ `S "DESCRIPTION"; @@ -1782,13 +1782,13 @@ let reinstall = | _, _::_ -> `Error (true, "Package arguments not allowed with this option") in - Term.(ret (const reinstall $global_options $build_options $assume_built + Term.(ret (const reinstall $global_options cli $build_options $assume_built $recurse $subpath $atom_or_dir_list $cmd)), term_info "reinstall" ~doc ~man (* UPDATE *) let update_doc = "Update the list of available packages." -let update = +let update cli = let doc = update_doc in let man = [ `S "DESCRIPTION"; @@ -1851,13 +1851,13 @@ let update = OpamConsole.msg "Now run 'opam upgrade' to apply any package updates.\n"; if not success then OpamStd.Sys.exit_because `Sync_error in - Term.(const update $global_options $jobs_flag $name_list + Term.(const update $global_options cli $jobs_flag $name_list $repos_only $dev_only $all $check $upgrade), term_info "update" ~doc ~man (* UPGRADE *) let upgrade_doc = "Upgrade the installed package to latest version." -let upgrade = +let upgrade cli = let doc = upgrade_doc in let man = [ `S "DESCRIPTION"; @@ -1909,13 +1909,13 @@ let upgrade = OpamSwitchState.drop @@ OpamClient.upgrade st ~check ~only_installed ~all atoms; `Ok () in - Term.(ret (const upgrade $global_options $build_options $fixup $check + Term.(ret (const upgrade $global_options cli $build_options $fixup $check $installed $all $recurse $subpath $atom_or_dir_list)), term_info "upgrade" ~doc ~man (* REPOSITORY *) let repository_doc = "Manage opam repositories." -let repository = +let repository cli = let doc = repository_doc in let scope_section = "SCOPE SPECIFICATION OPTIONS" in let commands = [ @@ -2203,7 +2203,7 @@ let repository = | command, params -> bad_subcommand commands ("repository", command, params) in Term.ret - Term.(const repository $global_options $command $repo_kind_flag + Term.(const repository $global_options cli $command $repo_kind_flag $print_short_flag $scope $rank $params), term_info "repository" ~doc ~man @@ -2273,7 +2273,7 @@ let with_repos_rt gt repos f = f (repos, rt) let switch_doc = "Manage multiple installation prefixes." -let switch = +let switch cli = let doc = switch_doc in let commands = [ "create", `install, ["SWITCH"; "[COMPILER]"], @@ -2743,7 +2743,7 @@ let switch = | command, params -> bad_subcommand commands ("switch", command, params) in Term.(ret (const switch - $global_options $build_options $command + $global_options cli $build_options $command $print_short_flag $no_switch $packages $formula $empty $descr $full $freeze $no_install @@ -2753,7 +2753,7 @@ let switch = (* PIN *) let pin_doc = "Pin a given package to a specific version or source." -let pin ?(unpin_only=false) () = +let pin ?(unpin_only=false) cli = let doc = pin_doc in let commands = [ "list", `list, [], "Lists pinned packages."; @@ -3097,14 +3097,14 @@ let pin ?(unpin_only=false) () = in Term.ret Term.(const pin - $global_options $build_options + $global_options cli $build_options $kind $edit $no_act $dev_repo $print_short_flag $recurse $subpath $command $params), term_info "pin" ~doc ~man (* SOURCE *) let source_doc = "Get the source of an opam package." -let source = +let source cli = let doc = source_doc in let man = [ `S "DESCRIPTION"; @@ -3229,12 +3229,12 @@ let source = (OpamClient.PIN.pin t nv.name ~version:nv.version target) in Term.(const source - $global_options $atom $dev_repo $pin $dir), + $global_options cli $atom $dev_repo $pin $dir), term_info "source" ~doc ~man (* LINT *) let lint_doc = "Checks and validate package description ('opam') files." -let lint = +let lint cli = let doc = lint_doc in let man = [ `S "DESCRIPTION"; @@ -3402,13 +3402,13 @@ let lint = OpamStd.Option.iter (fun json -> OpamJson.append "lint" (`A json)) json; if err then OpamStd.Sys.exit_because `False in - Term.(const lint $global_options $files $package $normalise $short + Term.(const lint $global_options cli $files $package $normalise $short $warnings $check_upstream $recurse $subpath), term_info "lint" ~doc ~man (* CLEAN *) let clean_doc = "Cleans up opam caches" -let clean = +let clean cli = let doc = clean_doc in let man = [ `S "DESCRIPTION"; @@ -3580,13 +3580,13 @@ let clean = (OpamConsole.msg "Clearing logs\n"; cleandir (OpamPath.log root)) in - Term.(const clean $global_options $dry_run $download_cache $repos $repo_cache + Term.(const clean $global_options cli $dry_run $download_cache $repos $repo_cache $logs $switch $all_switches), term_info "clean" ~doc ~man (* LOCK *) let lock_doc = "Create locked opam files to share build environments across hosts." -let lock = +let lock cli = let doc = lock_doc in let man = [ `S "DESCRIPTION"; @@ -3650,7 +3650,7 @@ let lock = (OpamPackage.to_string nv) (OpamFilename.to_string file)) pkg_done) in - Term.(pure lock $global_options $only_direct_flag $lock_suffix + Term.(pure lock $global_options cli $only_direct_flag $lock_suffix $atom_or_local_list), Term.info "lock" ~doc ~man @@ -3680,7 +3680,7 @@ let help = Term.(ret (const help $Term.man_format $Term.choice_names $topic)), Term.info "help" ~doc ~man -let default = +let default cli = let doc = "source-based package management" in let man = [ `S "DESCRIPTION"; @@ -3724,7 +3724,7 @@ let default = upgrade_doc config_doc repository_doc switch_doc pin_doc OpamAdminCommand.admin_command_doc in - Term.(const usage $global_options), + Term.(const usage $global_options cli), Term.info "opam" ~version:(OpamVersion.to_string OpamVersion.current) ~sdocs:global_option_section @@ -3737,40 +3737,50 @@ let admin = Term.(ret (const (`Error (true, doc)))), Term.info "admin" -let commands = [ - init; - list (); - make_command_alias (list ~force_search:true ()) ~options:" --search" "search"; - show; make_command_alias show "info"; - install; - remove; make_command_alias remove "uninstall"; - reinstall; - update; upgrade; - var; option; - config; - exec; env; - repository; make_command_alias repository "remote"; - switch; - pin (); make_command_alias (pin ~unpin_only:true ()) ~options:" remove" "unpin"; - source; - lint; - clean; - lock; - admin; - help; -] +let commands cli = + let show = show cli in + let remove = remove cli in + let repository = repository cli in + (* This list must always include *all* commands, regardless of cli *) + [ + init cli; + list cli; + make_command_alias (list ~force_search:true cli) ~options:" --search" "search"; + show; make_command_alias show "info"; + install cli; + remove; make_command_alias remove "uninstall"; + reinstall cli; + update cli; upgrade cli; + var cli; option cli; + config cli; + exec cli; env cli; + repository; make_command_alias repository "remote"; + switch cli; + pin cli; make_command_alias (pin ~unpin_only:true cli) ~options:" remove" "unpin"; + source cli; + lint cli; + clean cli; + lock cli; + admin; + help; + ] + +let current_commands = commands OpamCLIVersion.current let is_builtin_command prefix = List.exists (fun (_,info) -> OpamStd.String.starts_with ~prefix (Term.name info)) - commands + current_commands let is_admin_subcommand prefix = prefix = "admin" || let matches = List.filter (fun (_,info) -> OpamStd.String.starts_with ~prefix (Term.name info)) - commands in + current_commands in match matches with | [(_,info)] when Term.name info = "admin" -> true | _ -> false + +let get_cmdliner_parser cli = + (default cli, commands cli) diff --git a/src/client/opamCommands.mli b/src/client/opamCommands.mli index d21090c0566..d4deb4a476b 100644 --- a/src/client/opamCommands.mli +++ b/src/client/opamCommands.mli @@ -11,15 +11,10 @@ (** Opam CLI main entry point *) -open Cmdliner - (** {2 Commands} *) (** Type of commands *) -type command = unit Term.t * Term.info - -(** The default list of commands *) -val commands: command list +type command = unit Cmdliner.Term.t * Cmdliner.Term.info (** [is_builtin_command arg] is [true] if [arg] is a prefix of any built-in command *) @@ -29,44 +24,4 @@ val is_builtin_command: string -> bool sub-command. *) val is_admin_subcommand: string -> bool -(** opam *) -val default: command - -(** opam init *) -val init: command - -(** opam list *) -val list: ?force_search:bool -> unit -> command - -(** opam show *) -val show: command - -(** opam install *) -val install: command - -(** opam remove *) -val remove: command - -(** opam reinstall *) -val reinstall: command - -(** opam update *) -val update: command - -(** opam upgrade *) -val upgrade: command - -(** opam config *) -val config: command - -(** opam repository *) -val repository: command - -(** opam switch *) -val switch: command - -(** opam pin *) -val pin: ?unpin_only:bool -> unit -> command - -(** opam help *) -val help: command +val get_cmdliner_parser: OpamCLIVersion.t -> command * command list diff --git a/src/client/opamMain.ml b/src/client/opamMain.ml index 463eec811df..b812abeb730 100644 --- a/src/client/opamMain.ml +++ b/src/client/opamMain.ml @@ -15,23 +15,122 @@ open OpamStateTypes open OpamTypesBase open OpamStd.Op +exception InvalidCLI of (OpamCLIVersion.t * provenance, string option) OpamCompat.Result.t + +(* Filter and parse "--cli=v" or "--cli v" options *) +let rec filter_cli_arg cli acc args = + match args with + | [] + | "--" :: _ -> (cli, List.rev_append acc args) + | "--cl" :: args -> filter_cli_arg cli acc ("--cli"::args) + | ["--cli"] | "--cli" :: "--" :: _ -> + raise (InvalidCLI(Error None)) + | "--cli" :: arg :: args -> + let version = + match OpamCLIVersion.of_string_opt arg with + | Some cli -> + if OpamCLIVersion.is_supported cli then + cli + else + raise (InvalidCLI(Ok(cli, `Command_line))) + | None -> raise (InvalidCLI(Error(Some arg))) + in + filter_cli_arg (Some version) acc args + | arg :: args -> + match OpamStd.String.cut_at arg '=' with + | Some ("--cl", value) + | Some ("--cli", value) -> + filter_cli_arg cli acc ("--cli"::value::args) + | _ -> + filter_cli_arg cli (arg::acc) args + +(* Pre-process argv processing the --yes and --cli. Returns Some cli, if --cli + was encountered, a boolean indicating if a valid --yes/-y was encountered + (it returns false if multiple flags were encountered) and the list of + arguments to continue with processing. *) +let rec preprocess_argv cli yes args = + let is_valid_yes = function [_] -> true | _ -> false in + match args with + | [] -> + (cli, is_valid_yes yes, yes) + | "--" :: _ -> + (cli, is_valid_yes yes, yes @ args) + (* Note that because this is evaluated before a sub-command, all the + prefixes of --yes are assumed to valid at all times. *) + | ("-y" | "--y" | "--ye" | "--yes") as yes_opt :: args -> + if yes = [] then + preprocess_argv cli [yes_opt] args + else + (cli, false, yes @ [yes_opt]) + | "--cl" :: args -> preprocess_argv cli yes ("--cli"::args) + | ["--cli"] | "--cli" :: "--" :: _ -> + raise (InvalidCLI(Error None)) + | "--cli" :: arg :: args -> + let version = + match OpamCLIVersion.of_string_opt arg with + | Some cli -> + if OpamCLIVersion.is_supported cli then + cli + else + raise (InvalidCLI(Ok(cli, `Command_line))) + | _ -> raise (InvalidCLI(Error(Some arg))) + in + preprocess_argv (Some version) yes args + | arg :: rest -> + match OpamStd.String.cut_at arg '=' with + | Some ("--cl", value) + | Some ("--cli", value) -> + preprocess_argv cli yes ("--cli"::value::rest) + | _ -> + if OpamCommands.is_builtin_command arg then + let (cli, rest) = filter_cli_arg cli [] rest in + (cli, is_valid_yes yes, arg :: (yes @ rest)) + else + (cli, is_valid_yes yes, args) + (* Handle git-like plugins *) let check_and_run_external_commands () = let plugin_prefix = "opam-" in - match Array.to_list Sys.argv with - | [] | [_] -> () - | _ :: ("-y" | "--yes") :: name :: args + (* Pre-process the --yes and --cli options *) + let (cli, yes, argv) = + match Array.to_list Sys.argv with + | prog::args -> + let (cli, yes, args) = preprocess_argv None [] args in + let cli = + match cli with + | Some cli -> + if OpamCLIVersion.(cli < (2, 1)) then begin + let cli = OpamCLIVersion.to_string cli in + OpamConsole.warning "--cli is not supported by opam %s; setting OPAMCLI=%s is more portable" cli cli + end; + (cli, `Command_line) + | None -> + match OpamCLIVersion.env "CLI" with + | Some cli -> + if OpamCLIVersion.is_supported cli then + let () = + if OpamCLIVersion.(cli >= (2, 1)) then + OpamConsole.warning "Setting OPAMCLI is brittle - consider using the '--cli .' flag." + in + cli, `Env + else + raise (InvalidCLI(Ok(cli, `Env))) + | None -> + OpamCLIVersion.current, `Default + in + (cli, yes, prog::args) + | args -> ((OpamCLIVersion.current, `Default), false, args) + in + match argv with + | [] | [_] -> (cli, argv) | _ :: name :: args -> if - not (OpamStd.String.starts_with ~prefix:"-" name) - && not (OpamCommands.is_builtin_command name) - then + String.length name > 0 && name.[0] = '-' || OpamCommands.is_builtin_command name + then (cli, argv) + else (* No such command, check if there is a matching plugin *) let command = plugin_prefix ^ name in - let answer = match Sys.argv.(1) with - | "-y" | "--yes" -> Some true - | _ -> OpamStd.Config.env_bool "YES" - in + let answer = if yes then Some true else OpamStd.Config.env_bool "YES" in OpamStd.Config.init ~answer (); OpamFormatConfig.init (); let root_dir = OpamStateConfig.opamroot () in @@ -55,11 +154,11 @@ let check_and_run_external_commands () = | Some command -> let argv = Array.of_list (command :: args) in raise (OpamStd.Sys.Exec (command, argv, env)) - | None when not has_init -> () + | None when not has_init -> (cli, argv) | None -> (* Look for a corresponding package *) match OpamStateConfig.get_switch_opt () with - | None -> () + | None -> (cli, argv) | Some sw -> OpamGlobalState.with_ `Lock_none @@ fun gt -> OpamSwitchState.with_ `Lock_none gt ~switch:sw @@ fun st -> @@ -80,7 +179,7 @@ let check_and_run_external_commands () = candidates in let installed = OpamPackage.Set.inter plugins st.installed in - if OpamPackage.Set.is_empty candidates then () + if OpamPackage.Set.is_empty candidates then (cli, argv) else if not OpamPackage.Set.(is_empty installed) then (OpamConsole.error "Plugin %s is already installed, but no %s command was found.\n\ @@ -129,6 +228,14 @@ let check_and_run_external_commands () = OpamConsole.msg "\n"; let argv = Array.of_list (command :: args) in raise (OpamStd.Sys.Exec (command, argv, env)) + else (cli, argv) + +let display_cli_error msg = + Format.eprintf "@[opam: @[%a@]@,@[Usage: @[opam COMMAND ...@]@]@,Try `opam --help' for more information.@]@." + Format.pp_print_text msg + +let display_cli_error fmt = + Format.ksprintf display_cli_error fmt let rec main_catch_all f = try f () with @@ -173,6 +280,24 @@ let rec main_catch_all f = (* workaround warning 52, this is a fallback (we already handle the signal) and there is no way around at the moment *) 141 + | InvalidCLI (Ok(cli, source)) -> + (* Unsupported CLI version *) + let suffix = + if source = `Env then + " Please fix the value of the OPAMCLI environment variable, or use the '--cli .' flag" + else + "" + in + OpamConsole.error "opam command-line version %s is not supported.%s" (OpamCLIVersion.to_string cli) suffix; + OpamStd.Sys.get_exit_code `Bad_arguments + | InvalidCLI (Error None) -> + (* No CLI version given *) + display_cli_error "option `--cli' needs an argument"; + OpamStd.Sys.get_exit_code `Bad_arguments + | InvalidCLI (Error (Some invalid)) -> + (* Corrupt CLI version *) + display_cli_error "option `--cli': invalid value `%s', expected major.minor" invalid; + OpamStd.Sys.get_exit_code `Bad_arguments | Failure msg -> OpamConsole.errmsg "Fatal error: %s\n" msg; OpamConsole.errmsg "%s" (OpamStd.Exn.pretty_backtrace e); @@ -184,27 +309,21 @@ let rec main_catch_all f = in exit exit_code -let run default commands = +let run () = OpamStd.Option.iter OpamVersion.set_git OpamGitVersion.version; OpamSystem.init (); main_catch_all @@ fun () -> - check_and_run_external_commands (); - let admin, argv1 = - if Array.length Sys.argv > 1 && OpamCommands.is_admin_subcommand Sys.argv.(1) then - true, - Array.init (Array.length Sys.argv - 1) (function - | 0 -> Sys.argv.(0) - | i -> Sys.argv.(i+1)) - else false, Sys.argv - in - let eval () = - if admin then - Term.eval_choice ~catch:false ~argv:argv1 - OpamAdminCommand.default_subcommand OpamAdminCommand.admin_subcommands - else - Term.eval_choice ~catch:false ~argv:argv1 default commands + let (cli, _), argv = check_and_run_external_commands () in + let (default, commands), argv1 = + match argv with + | prog :: command :: argv when OpamCommands.is_admin_subcommand command -> + OpamAdminCommand.get_cmdliner_parser cli, prog::argv + | _ -> + OpamCommands.get_cmdliner_parser cli, argv in - match eval () with + let argv = Array.of_list argv1 in + OpamConsole.log "CLI" "Parsing CLI version %s" @@ OpamCLIVersion.to_string cli; + match Term.eval_choice ~catch:false ~argv default commands with | `Error _ -> exit (OpamStd.Sys.get_exit_code `Bad_arguments) | _ -> exit (OpamStd.Sys.get_exit_code `Success) @@ -240,4 +359,4 @@ let () = ); json_out () ); - run OpamCommands.default OpamCommands.commands + run () diff --git a/src/core/opamCompat.ml b/src/core/opamCompat.ml index e09a6fea730..315d0d509c4 100644 --- a/src/core/opamCompat.ml +++ b/src/core/opamCompat.ml @@ -110,6 +110,19 @@ struct end #endif +module Result = +#if OCAML_VERSION >= (4, 8, 0) + Result +#else +: sig + type ('a, 'e) t +#if OCAML_VERSION >= (4, 3, 0) + = ('a, 'e) result +#endif + = Ok of 'a | Error of 'e +end +#endif + #if OCAML_VERSION < (4, 7, 0) module Stdlib = Pervasives #endif diff --git a/src/core/opamCompat.mli b/src/core/opamCompat.mli index c9a3309c331..93daafa3dd3 100644 --- a/src/core/opamCompat.mli +++ b/src/core/opamCompat.mli @@ -90,6 +90,19 @@ module Filename end #endif +module Result +#if OCAML_VERSION >= (4, 8, 0) += Result +#else +: sig + type ('a, 'e) t +#if OCAML_VERSION >= (4, 3, 0) + = ('a, 'e) result +#endif + = Ok of 'a | Error of 'e +end +#endif + #if OCAML_VERSION < (4, 7, 0) module Stdlib = Pervasives #endif