Skip to content

Commit

Permalink
Introduce dune ocaml command group
Browse files Browse the repository at this point in the history
This subgroup includes: utop, top, and merlin.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Nov 10, 2020
1 parent 2f525ab commit a978089
Show file tree
Hide file tree
Showing 5 changed files with 56 additions and 26 deletions.
2 changes: 2 additions & 0 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,8 @@ module Profile = Dune_rules.Profile
module Log = Dune_util.Log
include Common.Let_syntax

let in_group (t, info) = (Term.Group.Term t, info)

let make_cache (config : Config.t) =
let make_cache () =
let command_handler (Cache.Dedup file) =
Expand Down
57 changes: 31 additions & 26 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -172,31 +172,36 @@ let command_alias cmd name =
in
(term, Term.info name ~docs:"COMMAND ALIASES" ~doc ~man)

let all =
[ Installed_libraries.command
; External_lib_deps.command
; build_targets
; runtest
; command_alias runtest "test"
; clean
; Install_uninstall.install
; Install_uninstall.uninstall
; Exec.command
; Subst.command
; Print_rules.command
; Utop.command
; Init.command
; promote
; Printenv.command
; Help.command
; Format_dune_file.command
; Compute.command
; Upgrade.command
; Caching.command
; Describe.command
; Top.command
; Ocaml_merlin.command
]
let all : _ Term.Group.t list =
let terms =
[ Installed_libraries.command
; External_lib_deps.command
; build_targets
; runtest
; command_alias runtest "test"
; clean
; Install_uninstall.install
; Install_uninstall.uninstall
; Exec.command
; Subst.command
; Print_rules.command
; Utop.command
; Init.command
; promote
; Printenv.command
; Help.command
; Format_dune_file.command
; Compute.command
; Upgrade.command
; Caching.command
; Describe.command
; Top.command
; Ocaml_merlin.command
]
|> List.map ~f:in_group
in
let groups = [ Ocaml.group ] in
terms @ groups

let common_commands_synopsis =
(* Short reminders for the most used and useful commands *)
Expand Down Expand Up @@ -259,7 +264,7 @@ let default =
let () =
Colors.setup_err_formatter_colors ();
try
match Term.eval_choice default all ~catch:false with
match Term.Group.eval default all ~catch:false with
| `Error _ -> exit 1
| _ -> exit 0
with exn ->
Expand Down
11 changes: 11 additions & 0 deletions bin/ocaml.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
open Import

let info = Term.info "ocaml"

let group =
( Term.Group.Group
[ in_group Utop.command
; in_group Ocaml_merlin.command
; in_group Top.command
]
, info )
3 changes: 3 additions & 0 deletions bin/ocaml.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
open Import

val group : unit Term.Group.t
9 changes: 9 additions & 0 deletions doc/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -107,6 +107,15 @@
(package dune)
(files dune-installed-libraries.1))

(rule
(with-stdout-to dune-ocaml.1
(run dune ocaml --help=groff)))

(install
(section man)
(package dune)
(files dune-ocaml.1))

(rule
(with-stdout-to dune-ocaml-merlin.1
(run dune ocaml-merlin --help=groff)))
Expand Down

0 comments on commit a978089

Please sign in to comment.