Skip to content

Commit f4cb122

Browse files
committed
refactor(describe): remove describe_common lib
Signed-off-by: Ali Caglayan <[email protected]>
1 parent 7b20edd commit f4cb122

File tree

7 files changed

+230
-319
lines changed

7 files changed

+230
-319
lines changed

bin/describe/describe_common.ml

Lines changed: 0 additions & 174 deletions
This file was deleted.

bin/describe/describe_common.mli

Lines changed: 0 additions & 133 deletions
This file was deleted.

bin/describe/describe_external_lib_deps.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -160,7 +160,7 @@ let to_dyn context_name external_resolved_libs =
160160
let term =
161161
let+ common = Common.term
162162
and+ context_name = Common.context_arg ~doc:"Build context to use."
163-
and+ format = Describe_common.Format.arg in
163+
and+ format = Describe_format.arg in
164164
let config = Common.init common in
165165
Scheduler.go ~common ~config @@ fun () ->
166166
let open Fiber.O in
@@ -175,7 +175,7 @@ let term =
175175
in
176176
external_resolved_libs setup super_context
177177
>>| to_dyn context_name
178-
>>| Describe_common.Format.print_dyn format
178+
>>| Describe_format.print_dyn format
179179

180180
let command =
181181
let doc =

bin/describe/describe_format.ml

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
open Stdune
2+
open Import
3+
4+
type t =
5+
| Sexp
6+
| Csexp
7+
8+
let all = [ ("sexp", Sexp); ("csexp", Csexp) ]
9+
10+
let arg =
11+
let doc = Printf.sprintf "$(docv) must be %s" (Arg.doc_alts_enum all) in
12+
Arg.(value & opt (enum all) Sexp & info [ "format" ] ~docv:"FORMAT" ~doc)
13+
14+
let print_as_sexp dyn =
15+
let rec dune_lang_of_sexp : Sexp.t -> Dune_lang.t = function
16+
| Atom s -> Dune_lang.atom_or_quoted_string s
17+
| List l -> List (List.map l ~f:dune_lang_of_sexp)
18+
in
19+
let cst =
20+
dyn |> Sexp.of_dyn |> dune_lang_of_sexp
21+
|> Dune_lang.Ast.add_loc ~loc:Loc.none
22+
|> Dune_lang.Cst.concrete
23+
in
24+
let version = Dune_lang.Syntax.greatest_supported_version Stanza.syntax in
25+
Pp.to_fmt Stdlib.Format.std_formatter
26+
(Dune_lang.Format.pp_top_sexps ~version [ cst ])
27+
28+
let print_dyn t dyn =
29+
match t with
30+
| Csexp -> Csexp.to_channel stdout (Sexp.of_dyn dyn)
31+
| Sexp -> print_as_sexp dyn

bin/describe/describe_format.mli

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
open Import
2+
3+
(** Formatting utilities for dune describe commands *)
4+
5+
type t =
6+
| Sexp
7+
| Csexp
8+
9+
val arg : t Term.t
10+
11+
val print_dyn : t -> Dyn.t -> unit

bin/describe/describe_opam_files.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ open Stdune
33

44
let term =
55
let+ common = Common.term
6-
and+ format = Describe_common.Format.arg in
6+
and+ format = Describe_format.arg in
77
let config = Common.init common in
88
Scheduler.go ~common ~config @@ fun () ->
99
Build_system.run_exn @@ fun () ->
@@ -26,7 +26,7 @@ let term =
2626
Dyn.Tuple [ String (Path.to_string opam_file); String contents ]
2727
in
2828
Dyn.List (List.map packages ~f:opam_file_to_dyn)
29-
|> Describe_common.Format.print_dyn format
29+
|> Describe_format.print_dyn format
3030

3131
let command =
3232
let doc =

0 commit comments

Comments
 (0)