Skip to content

Commit

Permalink
refactor: move [$ dune fmt] to separate module (#11044)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored Oct 26, 2024
1 parent c1c2dec commit b61e9d6
Show file tree
Hide file tree
Showing 5 changed files with 59 additions and 54 deletions.
52 changes: 0 additions & 52 deletions bin/build_cmd.ml
Original file line number Diff line number Diff line change
Expand Up @@ -160,55 +160,3 @@ let build =
in
Cmd.v (Cmd.info "build" ~doc ~man ~envs:Common.envs) term
;;

let fmt =
let doc = "Format source code." in
let man =
[ `S "DESCRIPTION"
; `P
{|$(b,dune fmt) runs the formatter on the source code. The formatter is
automatically selected. ocamlformat is used to format OCaml source code
(*.ml and *.mli files) and refmt is used to format Reason source code
(*.re and *.rei files).|}
; `Blocks Common.help_secs
]
in
let term =
let+ builder = Common.Builder.term
and+ no_promote =
Arg.(
value
& flag
& info
[ "preview" ]
~doc:
"Just print the changes that would be made without actually applying them. \
This takes precedence over auto-promote as that flag is assumed for this \
command.")
in
let builder =
Common.Builder.set_promote builder (if no_promote then Never else Automatically)
in
let common, config = Common.init builder in
let request (setup : Import.Main.build_system) =
let open Action_builder.O in
let* () =
if Lazy.force Lock_dev_tool.is_enabled
then
(* Note that generating the ocamlformat lockdir here means
that it will be created when a user runs `dune fmt` but not
when a user runs `dune build @fmt`. It's important that
this logic remain outside of `dune build`, as `dune
build` is intended to only build targets, and generating
a lockdir is not building a target. *)
Action_builder.of_memo (Lock_dev_tool.lock_ocamlformat ())
else Action_builder.return ()
in
let dir = Path.(relative root) (Common.prefix_target common ".") in
Alias.in_dir ~name:Dune_rules.Alias.fmt ~recursive:true ~contexts:setup.contexts dir
|> Alias.request
in
run_build_command ~common ~config ~request
in
Cmd.v (Cmd.info "fmt" ~doc ~man ~envs:Common.envs) term
;;
1 change: 0 additions & 1 deletion bin/build_cmd.mli
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ val run_build_system
-> (unit, [ `Already_reported ]) result Fiber.t

val build : unit Cmd.t
val fmt : unit Cmd.t

val run_build_command
: common:Common.t
Expand Down
55 changes: 55 additions & 0 deletions bin/fmt.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
open Import

let doc = "Format source code."

let man =
[ `S "DESCRIPTION"
; `P
{|$(b,dune fmt) runs the formatter on the source code. The formatter is
automatically selected. ocamlformat is used to format OCaml source code
(*.ml and *.mli files) and refmt is used to format Reason source code
(*.re and *.rei files).|}
; `Blocks Common.help_secs
]
;;
let command =
let term =
let+ builder = Common.Builder.term
and+ no_promote =
Arg.(
value
& flag
& info
[ "preview" ]
~doc:
"Just print the changes that would be made without actually applying them. \
This takes precedence over auto-promote as that flag is assumed for this \
command.")
in
let builder =
Common.Builder.set_promote builder (if no_promote then Never else Automatically)
in
let common, config = Common.init builder in
let request (setup : Import.Main.build_system) =
let open Action_builder.O in
let* () =
if Lazy.force Lock_dev_tool.is_enabled
then
(* Note that generating the ocamlformat lockdir here means
that it will be created when a user runs `dune fmt` but not
when a user runs `dune build @fmt`. It's important that
this logic remain outside of `dune build`, as `dune
build` is intended to only build targets, and generating
a lockdir is not building a target. *)
Action_builder.of_memo (Lock_dev_tool.lock_ocamlformat ())
else Action_builder.return ()
in
let dir = Path.(relative root) (Common.prefix_target common ".") in
Alias.in_dir ~name:Dune_rules.Alias.fmt ~recursive:true ~contexts:setup.contexts dir
|> Alias.request
in
Build_cmd.run_build_command ~common ~config ~request
in
Cmd.v (Cmd.info "fmt" ~doc ~man ~envs:Common.envs) term
;;
3 changes: 3 additions & 0 deletions bin/fmt.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
open Import

val command : unit Cmd.t
2 changes: 1 addition & 1 deletion bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ let all : _ Cmdliner.Cmd.t list =
@ [ Installed_libraries.command
; External_lib_deps.command
; Build_cmd.build
; Build_cmd.fmt
; Fmt.command
; Clean.command
; Install_uninstall.install
; Install_uninstall.uninstall
Expand Down

0 comments on commit b61e9d6

Please sign in to comment.