Skip to content

Commit

Permalink
Add --cli / OPAMCLI
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed Aug 18, 2020
1 parent f130639 commit 36d6448
Show file tree
Hide file tree
Showing 16 changed files with 478 additions and 194 deletions.
24 changes: 24 additions & 0 deletions doc/pages/FAQ.md
Original file line number Diff line number Diff line change
Expand Up @@ -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.
8 changes: 8 additions & 0 deletions doc/pages/Usage.md
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
3 changes: 3 additions & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -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
*

Expand Down
74 changes: 42 additions & 32 deletions src/client/opamAdminCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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))
Expand All @@ -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"
Expand All @@ -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 = [
Expand Down Expand Up @@ -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


Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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

Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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 = [
Expand Down Expand Up @@ -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 *)
Expand Down Expand Up @@ -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";
Expand All @@ -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
4 changes: 2 additions & 2 deletions src/client/opamAdminCommand.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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
Loading

0 comments on commit 36d6448

Please sign in to comment.