Skip to content

Commit

Permalink
Revert "support json output"
Browse files Browse the repository at this point in the history
This reverts commit a43e36a.
  • Loading branch information
cannorin authored and kit-ty-kate committed Jul 29, 2022
1 parent 9aaf08d commit 1ec0ba0
Show file tree
Hide file tree
Showing 5 changed files with 13 additions and 63 deletions.
11 changes: 3 additions & 8 deletions src/client/opamCommands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -736,7 +736,7 @@ let tree ?(why=false) cli =
`P ("See section $(b,"^filter_docs^") and $(b,"^selection_docs^") for all the \
ways to select the packages to be displayed, and section $(b,"^display_docs^") to \
customise the output format.");
`P "For a flat list of packages with more detailed information, see $(b,opam list).";
`P "For a flat list of packages which may not be installed, see $(b,opam list).";
`S Manpage.s_arguments;
`S build_docs;
`S filter_docs;
Expand Down Expand Up @@ -789,21 +789,16 @@ let tree ?(why=false) cli =
mk_flag ~cli (cli_from cli2_2) ["no-constraint"] ~section:display_docs
"Do not display the version constraints e.g. $(i,(>= 1.0.0))."
in
let json =
mk_flag ~cli (cli_from cli2_2) ["as-json"] ~section:display_docs
"Display the output as a JSON, but not a Unicode/ASCII-art tree."
in
let tree global_options mode filter post dev doc test tools no_constraint json packages () =
let tree global_options mode filter post dev doc test tools no_constraint packages () =
apply_global_options cli global_options;
OpamGlobalState.with_ `Lock_none @@ fun gt ->
OpamSwitchState.with_ `Lock_none gt @@ fun st ->
OpamTreeCommand.run st ~post ~dev ~doc ~test ~tools ~no_constraint ~json mode filter packages
OpamTreeCommand.run st ~post ~dev ~doc ~test ~tools ~no_constraint mode filter packages
in
mk_command ~cli (cli_from cli2_2) "tree" ~doc ~man
Term.(const tree $global_options cli $mode $filter
$post $dev $doc_flag $test $tools
$no_cstr
$json
$name_list)

(* SHOW *)
Expand Down
54 changes: 5 additions & 49 deletions src/client/opamTreeCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -251,7 +251,7 @@ let string_of_condition (c: condition) =
(OpamPrinter.FullPos.relop_kind relop)
(OpamFilter.to_string ~custom f)
in
OpamFormula.string_of_formula print_atom c
"(" ^ OpamFormula.string_of_formula print_atom c ^ ")"

let print_deps ?(no_constraint=false) = function
| Root p -> OpamPackage.to_string p
Expand All @@ -261,7 +261,7 @@ let print_deps ?(no_constraint=false) = function
match satisfies with
| _ when no_constraint -> Printf.sprintf "%s%s" p dup
| None | Some Empty -> Printf.sprintf "%s%s" p dup
| Some c -> Printf.sprintf "%s (%s)%s" p (string_of_condition c) dup
| Some c -> Printf.sprintf "%s %s%s" p (string_of_condition c) dup

let print_revdeps ?(no_constraint=false) = function
| Root p -> OpamPackage.to_string p
Expand All @@ -271,7 +271,7 @@ let print_revdeps ?(no_constraint=false) = function
match demands with
| _ when no_constraint -> Printf.sprintf "%s%s" p dup
| None | Some Empty -> Printf.sprintf "%s%s" p dup
| Some c -> Printf.sprintf "(%s) %s%s" (string_of_condition c) p dup
| Some c -> Printf.sprintf "%s %s%s" (string_of_condition c) p dup

let print ?no_constraint (forest: result) =
match forest with
Expand All @@ -285,46 +285,6 @@ let print ?no_constraint (forest: result) =
trees |> List.iter (fun tree -> print_newline (); Tree.print ~printer tree)
| DepsForest [] | RevdepsForest [] -> ()

let condition_to_json (co: condition option) =
match co with
| None | Some Empty -> `Null
| Some c -> `String (string_of_condition c)

let deps_to_json ?(no_constraint=false) = function
| Root p -> OpamPackage.to_json p
| Dependency { package; satisfies; is_dup } ->
match OpamPackage.to_json package with
| `O pfs ->
let sfs =
if no_constraint then []
else ["satisfies", condition_to_json satisfies]
in
`O (pfs @ sfs @ ["is_dup", `Bool is_dup])
| _ -> failwith "impossible"

let revdeps_to_json ?(no_constraint=false) = function
| Root p -> OpamPackage.to_json p
| Requirement { package; demands; is_dup } ->
match OpamPackage.to_json package with
| `O pfs ->
let sfs =
if no_constraint then []
else ["demands", condition_to_json demands]
in
`O (pfs @ sfs @ ["is_dup", `Bool is_dup])
| _ -> failwith "impossible"

let to_json ?no_constraint (forest: result) =
match forest with
| DepsForest trees ->
`A (trees |> List.map (fun tree ->
Tree.to_json ~children:"dependencies" ~flatten:true (deps_to_json ?no_constraint) tree
))
| RevdepsForest trees ->
`A (trees |> List.map (fun tree ->
Tree.to_json ~children:"dependants" ~flatten:true (revdeps_to_json ?no_constraint) tree
))

let get_universe ?doc ?test ?tools st =
OpamSwitchState.universe st ?doc ?test ?tools ~requested:st.installed Query

Expand Down Expand Up @@ -382,7 +342,7 @@ let dry_install ?doc ?test ?tools st universe missing =
(OpamSwitchState.unavailable_reason st) cs);
OpamStd.Sys.exit_because `No_solution

let run st ?post ?dev ?doc ?test ?tools ?no_constraint ?(json=false) mode filter packages =
let run st ?post ?dev ?doc ?test ?tools ?no_constraint mode filter packages =
let select, missing =
List.partition (OpamSwitchState.is_name_installed st) packages
in
Expand Down Expand Up @@ -410,8 +370,4 @@ let run st ?post ?dev ?doc ?test ?tools ?no_constraint ?(json=false) mode filter
let result =
build st universe ?post ?dev ?doc ?test ?tools mode filter (select @ missing)
in
if json then
let json = to_json ?no_constraint result in
print_endline (OpamJson.to_string json)
else
print ?no_constraint result
print ?no_constraint result
2 changes: 1 addition & 1 deletion src/client/opamTreeCommand.mli
Original file line number Diff line number Diff line change
Expand Up @@ -30,5 +30,5 @@ val run :
(* package selection options *)
?post:bool -> ?dev:bool -> ?doc:bool -> ?test:bool -> ?tools:bool ->
(* output format options *)
?no_constraint:bool -> ?json:bool ->
?no_constraint:bool ->
mode -> tree_filter -> name list -> unit
6 changes: 3 additions & 3 deletions src/core/opamConsole.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1103,11 +1103,11 @@ module Tree = struct
go_children "" children;
msg "%s" (Buffer.contents buff)

let rec to_json ?(children="children") ?(flatten=false) encoder { value; children=cs } : OpamJson.t =
let rec to_json ?(flatten=false) ~encoder { value; children } : OpamJson.t =
let fields =
match cs with
match children with
| [] -> []
| _ -> [children, `A (List.map (to_json ~children ~flatten encoder) cs)]
| _ -> ["children", `A (List.map (to_json ~flatten ~encoder) children)]
in
match flatten, encoder value with
| false, value -> `O (("value", value) :: fields)
Expand Down
3 changes: 1 addition & 2 deletions src/core/opamConsole.mli
Original file line number Diff line number Diff line change
Expand Up @@ -181,7 +181,6 @@ module Tree : sig
val print: ?symbols:symbols -> printer:('a -> string) -> 'a t -> unit

(** Encodes the given tree as JSON.
@param children sets the name of the field containing the children of a node.
@param encoder must return [`O fields] when [~flatten:true]. *)
val to_json: ?children:string -> ?flatten:bool -> 'a OpamJson.encoder -> 'a t OpamJson.encoder
val to_json: ?flatten:bool -> encoder:('a -> OpamJson.t) -> 'a t -> OpamJson.t
end

0 comments on commit 1ec0ba0

Please sign in to comment.