Skip to content

Commit

Permalink
refactor(cache): use cmdliner groups in dune cache commands
Browse files Browse the repository at this point in the history
We also do some cleanup of the documentation. This will make adding
more subcommands easier in the future.

closes #4471

<!-- ps-id: 60b331a0-d183-498b-9bba-5ea3d4538fb2 -->

Signed-off-by: Ali Caglayan <alizter@gmail.com>
  • Loading branch information
Alizter committed Dec 5, 2022
1 parent ab19b38 commit 0a66f65
Show file tree
Hide file tree
Showing 3 changed files with 77 additions and 216 deletions.
127 changes: 48 additions & 79 deletions bin/cache.ml
Original file line number Diff line number Diff line change
@@ -1,85 +1,28 @@
open Stdune
open Import

let name = "cache"

(* CR-someday amokhov: Implement other commands supported by Jenga. *)

let man =
[ `S "DESCRIPTION"
; `P
{|Dune can share build artifacts between workspaces. Currently, the only
action supported by this command is `trim`, but we plan to provide more
functionality soon. |}
; `S "ACTIONS"
; `P {|$(b,trim) trim the shared cache to free space.|}
; `S "EXAMPLES"
; `Pre
{|Trimming the Dune cache to 1 GB.

\$ dune cache trim --trimmed-size=1GB |}
; `Pre
{|Trimming 500 MB from the Dune cache.

\$ dune cache trim --size=500MB |}
; `Blocks Common.help_secs
]

let doc = "Manage the shared cache of build artifacts"
let trim =
let info =
let doc = "Trim the Dune cache" in
let man =
[ `P "Trim the Dune cache to a specified size or by a specified amount."
; `S "EXAMPLES"
; `Pre
{|Trimming the Dune cache to 1 GB.

let info = Cmd.info name ~doc ~man
\$ dune cache trim --trimmed-size=1GB |}
; `Pre
{|Trimming 500 MB from the Dune cache.

let trim ~trimmed_size ~size =
Log.init_disabled ();
let open Result.O in
match
let+ goal =
match (trimmed_size, size) with
| Some trimmed_size, None -> Result.Ok trimmed_size
| None, Some size ->
Result.Ok (Int64.sub (Dune_cache.Trimmer.overhead_size ()) size)
| _ -> Result.Error "specify either --size or --trimmed-size"
\$ dune cache trim --size=500MB |}
]
in
Dune_cache.Trimmer.trim ~goal
with
| Error s -> User_error.raise [ Pp.text s ]
| Ok { trimmed_bytes } ->
User_message.print
(User_message.make [ Pp.textf "Freed %s" (Bytes_unit.pp trimmed_bytes) ])

type mode =
| Trim
| Start_deprecated
| Stop_deprecated

let modes =
[ ("start", Start_deprecated); ("stop", Stop_deprecated); ("trim", Trim) ]

(* CR-someday amokhov: See https://github.com/ocaml/dune/issues/4471. *)

(* We don't want to list deprecated subcommands in help. *)
let non_deprecated_modes = [ ("trim", Trim) ]

(* We do want to print a nice error message if a deprecated subcommand is
run. *)
let deprecated_error () =
User_error.raise
[ Pp.text
"Dune no longer uses the cache daemon, and so the `start` and `stop` \
subcommands of `dune cache` were removed."
]

let term =
Term.ret
@@ let+ mode =
Arg.(
value
& pos 0 (some (enum modes)) None
& info [] ~docv:"ACTION"
~doc:
(Printf.sprintf "The cache action to perform (%s)"
(Arg.doc_alts_enum non_deprecated_modes)))
and+ trimmed_size =
Cmd.info "trim" ~doc ~man
in
Cmd.v info
@@ let+ trimmed_size =
Arg.(
value
& opt (some bytes) None
Expand All @@ -91,9 +34,35 @@ let term =
& opt (some bytes) None
& info ~docv:"BYTES" [ "size" ] ~doc:"Size to trim the cache to.")
in
match mode with
| Some Trim -> `Ok (trim ~trimmed_size ~size)
| Some Start_deprecated | Some Stop_deprecated -> deprecated_error ()
| None -> `Help (`Pager, Some name)
Log.init_disabled ();
let open Result.O in
match
let+ goal =
match (trimmed_size, size) with
| Some trimmed_size, None -> Result.Ok trimmed_size
| None, Some size ->
Result.Ok (Int64.sub (Dune_cache.Trimmer.overhead_size ()) size)
| _ -> Result.Error "please specify either --size or --trimmed-size"
in
Dune_cache.Trimmer.trim ~goal
with
| Error s -> User_error.raise [ Pp.text s ]
| Ok { trimmed_bytes } ->
User_message.print
(User_message.make
[ Pp.textf "Freed %s" (Bytes_unit.pp trimmed_bytes) ])

let command = Cmd.v info term
let command =
let info =
let doc = "Manage the shared cache of build artifacts" in
let man =
[ `S "DESCRIPTION"
; `P
"Dune can share build artifacts between workspaces. Currently, the \
only action supported by this command is `trim`, but we plan to \
provide more functionality soon."
]
in
Cmd.info "cache" ~doc ~man
in
Cmd.group info [ trim ]
Loading

0 comments on commit 0a66f65

Please sign in to comment.