Skip to content

Commit

Permalink
refactor: move runtest to own module (#11043)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Oct 26, 2024
1 parent 7464d0f commit c1c2dec
Show file tree
Hide file tree
Showing 5 changed files with 71 additions and 67 deletions.
40 changes: 0 additions & 40 deletions bin/build_cmd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -127,46 +127,6 @@ let run_build_command ~(common : Common.t) ~config ~request =
~request
;;

let runtest_info =
let doc = "Run tests." in
let man =
[ `S "DESCRIPTION"
; `P {|This is a short-hand for calling:|}
; `Pre {| dune build @runtest|}
; `Blocks Common.help_secs
; Common.examples
[ ( "Run all tests in the current source tree (including those that passed on \
the last run)"
, "dune runtest --force" )
; ( "Run tests sequentially without output buffering"
, "dune runtest --no-buffer -j 1" )
]
]
in
Cmd.info "runtest" ~doc ~man ~envs:Common.envs
;;

let runtest_term =
let name_ = Arg.info [] ~docv:"DIR" in
let+ builder = Common.Builder.term
and+ dirs = Arg.(value & pos_all string [ "." ] name_) in
let common, config = Common.init builder in
let request (setup : Import.Main.build_system) =
Action_builder.all_unit
(List.map dirs ~f:(fun dir ->
let dir = Path.(relative root) (Common.prefix_target common dir) in
Alias.in_dir
~name:Dune_rules.Alias.runtest
~recursive:true
~contexts:setup.contexts
dir
|> Alias.request))
in
run_build_command ~common ~config ~request
;;

let runtest = Cmd.v runtest_info runtest_term

let build =
let doc = "Build the given targets, or the default ones if none are given." in
let man =
Expand Down
2 changes: 0 additions & 2 deletions bin/build_cmd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,6 @@ val run_build_system
-> request:(Dune_rules.Main.build_system -> unit Action_builder.t)
-> (unit, [ `Already_reported ]) result Fiber.t

val runtest : unit Cmd.t
val runtest_term : unit Term.t
val build : unit Cmd.t
val fmt : unit Cmd.t

Expand Down
49 changes: 24 additions & 25 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,31 +2,30 @@ open Import

let all : _ Cmdliner.Cmd.t list =
let terms =
[ Installed_libraries.command
; External_lib_deps.command
; Build_cmd.build
; Build_cmd.runtest
; Build_cmd.fmt
; command_alias Build_cmd.runtest Build_cmd.runtest_term "test"
; Clean.command
; Install_uninstall.install
; Install_uninstall.uninstall
; Exec.command
; Subst.command
; Print_rules.command
; Utop.command
; Promotion.promote
; command_alias Printenv.command Printenv.term "printenv"
; Help.command
; Format_dune_file.command
; Upgrade.command
; Cache.command
; Top.command
; Ocaml_merlin.command
; Shutdown.command
; Diagnostics.command
; Monitor.command
]
Runtest.commands
@ [ Installed_libraries.command
; External_lib_deps.command
; Build_cmd.build
; Build_cmd.fmt
; Clean.command
; Install_uninstall.install
; Install_uninstall.uninstall
; Exec.command
; Subst.command
; Print_rules.command
; Utop.command
; Promotion.promote
; command_alias Printenv.command Printenv.term "printenv"
; Help.command
; Format_dune_file.command
; Upgrade.command
; Cache.command
; Top.command
; Ocaml_merlin.command
; Shutdown.command
; Diagnostics.command
; Monitor.command
]
in
let groups =
[ Ocaml_cmd.group
Expand Down
44 changes: 44 additions & 0 deletions bin/runtest.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
open Import

let runtest_info =
let doc = "Run tests." in
let man =
[ `S "DESCRIPTION"
; `P {|This is a short-hand for calling:|}
; `Pre {| dune build @runtest|}
; `Blocks Common.help_secs
; Common.examples
[ ( "Run all tests in the current source tree (including those that passed on \
the last run)"
, "dune runtest --force" )
; ( "Run tests sequentially without output buffering"
, "dune runtest --no-buffer -j 1" )
]
]
in
Cmd.info "runtest" ~doc ~man ~envs:Common.envs
;;

let runtest_term =
let name_ = Arg.info [] ~docv:"DIR" in
let+ builder = Common.Builder.term
and+ dirs = Arg.(value & pos_all string [ "." ] name_) in
let common, config = Common.init builder in
let request (setup : Import.Main.build_system) =
Action_builder.all_unit
(List.map dirs ~f:(fun dir ->
let dir = Path.(relative root) (Common.prefix_target common dir) in
Alias.in_dir
~name:Dune_rules.Alias.runtest
~recursive:true
~contexts:setup.contexts
dir
|> Alias.request))
in
Build_cmd.run_build_command ~common ~config ~request
;;

let commands =
let command = Cmd.v runtest_info runtest_term in
[ command; command_alias command runtest_term "test" ]
;;
3 changes: 3 additions & 0 deletions bin/runtest.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
open Import

val commands : unit Cmd.t list

0 comments on commit c1c2dec

Please sign in to comment.