2016-09-08 21:13:10 +04:00
|
|
|
(**************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Copyright (c) 2014 - 2016. *)
|
|
|
|
(* Dynamic Ledger Solutions, Inc. <contact@tezos.com> *)
|
|
|
|
(* *)
|
|
|
|
(* All rights reserved. No warranty, explicit or implicit, provided. *)
|
|
|
|
(* *)
|
|
|
|
(**************************************************************************)
|
|
|
|
|
|
|
|
(* Tezos Command line interface - Command Line Parsing *)
|
|
|
|
|
2017-04-05 12:22:41 +04:00
|
|
|
open Error_monad
|
2017-04-05 01:35:41 +04:00
|
|
|
open Lwt.Infix
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* User catchable exceptions *)
|
2017-04-05 12:22:41 +04:00
|
|
|
type error += Command_not_found
|
2017-04-07 23:21:20 +04:00
|
|
|
type error += Bad_argument of int * string
|
2017-04-05 12:22:41 +04:00
|
|
|
|
2017-04-07 23:21:20 +04:00
|
|
|
let () =
|
|
|
|
register_error_kind
|
|
|
|
`Branch
|
|
|
|
~id: "cli.command_not_found"
|
|
|
|
~title: "Command not found"
|
|
|
|
~description: "No command found to interpret the given command line"
|
|
|
|
~pp:
|
|
|
|
(fun ppf () ->
|
|
|
|
Format.fprintf ppf "Command not found")
|
|
|
|
Data_encoding.empty
|
|
|
|
(function Command_not_found -> Some () | _ -> None)
|
|
|
|
(fun () -> Command_not_found) ;
|
|
|
|
register_error_kind
|
|
|
|
`Branch
|
|
|
|
~id: "cli.bad_argument"
|
|
|
|
~title: "Bad argument"
|
|
|
|
~description: "Error in a command line argument"
|
|
|
|
~pp:
|
|
|
|
(fun ppf (i, v) ->
|
|
|
|
Format.fprintf ppf "Error in command line argument %d (%s)" i v)
|
|
|
|
Data_encoding.(obj2 (req "index" uint8) (req "value" string))
|
|
|
|
(function Bad_argument (i, v) -> Some (i, v) | _ -> None)
|
|
|
|
(fun (i, v) -> Bad_argument (i, v))
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-22 17:23:40 +04:00
|
|
|
(* A simple structure for command interpreters.
|
|
|
|
This is more generic than the exported one, see end of file. *)
|
2016-12-03 16:05:02 +04:00
|
|
|
type ('a, 'arg, 'ret) params =
|
|
|
|
| Prefix : string * ('a, 'arg, 'ret) params ->
|
|
|
|
('a, 'arg, 'ret) params
|
2016-11-22 17:23:40 +04:00
|
|
|
| Param : string * string *
|
2017-04-05 12:22:41 +04:00
|
|
|
('arg -> string -> 'p tzresult Lwt.t) *
|
2016-12-03 16:05:02 +04:00
|
|
|
('a, 'arg, 'ret) params ->
|
|
|
|
('p -> 'a, 'arg, 'ret) params
|
2016-11-22 17:23:40 +04:00
|
|
|
| Stop :
|
2017-04-05 12:22:41 +04:00
|
|
|
('arg -> 'ret tzresult Lwt.t, 'arg, 'ret) params
|
2016-11-22 17:23:40 +04:00
|
|
|
| More :
|
2017-04-05 12:22:41 +04:00
|
|
|
(string list -> 'arg -> 'ret tzresult Lwt.t, 'arg, 'ret) params
|
2016-11-22 17:23:40 +04:00
|
|
|
| Seq : string * string *
|
2017-04-05 12:22:41 +04:00
|
|
|
('arg -> string -> 'p tzresult Lwt.t) ->
|
|
|
|
('p list -> 'arg -> 'ret tzresult Lwt.t, 'arg, 'ret) params
|
2016-12-03 16:05:02 +04:00
|
|
|
|
|
|
|
(* A command group *)
|
|
|
|
type group =
|
|
|
|
{ name : string ;
|
|
|
|
title : string }
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* A command wraps a callback with its type and info *)
|
2016-12-03 16:05:02 +04:00
|
|
|
type ('arg, 'ret) command =
|
2016-09-08 21:13:10 +04:00
|
|
|
| Command
|
2016-12-03 16:05:02 +04:00
|
|
|
: { params: ('a, 'arg, 'ret) params ;
|
|
|
|
handler : 'a ;
|
|
|
|
desc : string ;
|
|
|
|
group : group option ;
|
|
|
|
args : (Arg.key * Arg.spec * Arg.doc) list }
|
|
|
|
-> ('arg, 'ret) command
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* Some combinators for writing commands concisely. *)
|
|
|
|
let param ~name ~desc kind next = Param (name, desc, kind, next)
|
|
|
|
let seq ~name ~desc kind = Seq (name, desc, kind)
|
|
|
|
let seq_of_param param =
|
|
|
|
match param Stop with
|
|
|
|
| Param (n, desc, f, Stop) -> Seq (n, desc, f)
|
|
|
|
| _ -> invalid_arg "Cli_entries.seq_of_param"
|
|
|
|
|
|
|
|
let prefix keyword next = Prefix (keyword, next)
|
|
|
|
let rec fixed =
|
|
|
|
function [] -> Stop | n :: r -> Prefix (n, fixed r)
|
|
|
|
let rec prefixes p next =
|
|
|
|
match p with [] -> next | n :: r -> Prefix (n, prefixes r next)
|
|
|
|
let stop = Stop
|
|
|
|
let more = More
|
|
|
|
let void = Stop
|
|
|
|
let any = More
|
2016-12-03 16:05:02 +04:00
|
|
|
let command ?group ?(args = []) ~desc params handler =
|
|
|
|
Command { params ; handler ; desc ; group ; args }
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* Param combinators *)
|
2016-12-03 16:05:02 +04:00
|
|
|
let string ~name ~desc next =
|
2017-04-05 12:22:41 +04:00
|
|
|
param name desc (fun _ s -> return s) next
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* Command execution *)
|
2016-11-22 17:23:40 +04:00
|
|
|
let exec
|
|
|
|
(type arg) (type ret)
|
2016-12-03 16:05:02 +04:00
|
|
|
(Command { params ; handler }) (last : arg) args =
|
2016-09-08 21:13:10 +04:00
|
|
|
let rec exec
|
2017-04-05 12:22:41 +04:00
|
|
|
: type a. int -> (a, arg, ret) params -> a -> string list -> ret tzresult Lwt.t
|
2016-11-22 17:23:40 +04:00
|
|
|
= fun i params cb args ->
|
2016-09-08 21:13:10 +04:00
|
|
|
match params, args with
|
2016-11-22 17:23:40 +04:00
|
|
|
| Stop, [] -> cb last
|
2017-04-05 12:22:41 +04:00
|
|
|
| Stop, _ -> fail Command_not_found
|
2016-09-08 21:13:10 +04:00
|
|
|
| Seq (_, _, f), seq ->
|
|
|
|
let rec do_seq i acc = function
|
2017-04-05 12:22:41 +04:00
|
|
|
| [] -> return (List.rev acc)
|
2016-09-08 21:13:10 +04:00
|
|
|
| p :: rest ->
|
2017-04-05 01:35:41 +04:00
|
|
|
Lwt.catch
|
2016-12-03 16:05:02 +04:00
|
|
|
(fun () -> f last p)
|
2016-09-08 21:13:10 +04:00
|
|
|
(function
|
2017-04-07 23:21:20 +04:00
|
|
|
| Failure msg -> Error_monad.failwith "%s" msg
|
|
|
|
| exn -> fail (Exn exn))
|
|
|
|
|> trace (Bad_argument (i, p)) >>=? fun v ->
|
2016-09-08 21:13:10 +04:00
|
|
|
do_seq (succ i) (v :: acc) rest in
|
2017-04-05 12:22:41 +04:00
|
|
|
do_seq i [] seq >>=? fun parsed ->
|
2016-11-22 17:23:40 +04:00
|
|
|
cb parsed last
|
|
|
|
| More, rest -> cb rest last
|
2016-09-08 21:13:10 +04:00
|
|
|
| Prefix (n, next), p :: rest when n = p ->
|
|
|
|
exec (succ i) next cb rest
|
|
|
|
| Param (_, _, f, next), p :: rest ->
|
2017-04-05 01:35:41 +04:00
|
|
|
Lwt.catch
|
2016-12-03 16:05:02 +04:00
|
|
|
(fun () -> f last p)
|
2016-09-08 21:13:10 +04:00
|
|
|
(function
|
2017-04-07 23:21:20 +04:00
|
|
|
| Failure msg -> Error_monad.failwith "%s" msg
|
|
|
|
| exn -> fail (Exn exn))
|
|
|
|
|> trace (Bad_argument (i, p)) >>=? fun v ->
|
2016-09-08 21:13:10 +04:00
|
|
|
exec (succ i) next (cb v) rest
|
2017-04-05 12:22:41 +04:00
|
|
|
| _ -> fail Command_not_found
|
2016-12-03 16:05:02 +04:00
|
|
|
in exec 1 params handler args
|
2016-09-08 21:13:10 +04:00
|
|
|
|
2016-11-22 17:23:40 +04:00
|
|
|
(* Command dispatch tree *)
|
|
|
|
type ('arg, 'ret) level =
|
2016-12-03 16:05:02 +04:00
|
|
|
{ stop : ('arg, 'ret) command option ;
|
2016-11-22 17:23:40 +04:00
|
|
|
prefix : (string * ('arg, 'ret) tree) list }
|
|
|
|
and ('arg, 'ret) param_level =
|
2016-12-03 16:05:02 +04:00
|
|
|
{ stop : ('arg, 'ret) command option ;
|
2016-11-22 17:23:40 +04:00
|
|
|
tree : ('arg, 'ret) tree }
|
|
|
|
and ('arg, 'ret) tree =
|
|
|
|
| TPrefix of ('arg, 'ret) level
|
|
|
|
| TParam of ('arg, 'ret) param_level
|
2016-12-03 16:05:02 +04:00
|
|
|
| TStop of ('arg, 'ret) command
|
|
|
|
| TMore of ('arg, 'ret) command
|
2016-11-22 17:23:40 +04:00
|
|
|
| TEmpty
|
|
|
|
|
|
|
|
let insert_in_dispatch_tree
|
|
|
|
(type arg) (type ret)
|
2016-12-03 16:05:02 +04:00
|
|
|
root (Command { params } as command) =
|
2016-11-22 17:23:40 +04:00
|
|
|
let rec insert_tree
|
2016-12-03 16:05:02 +04:00
|
|
|
: type a. (arg, ret) tree -> (a, arg, ret) params -> (arg, ret) tree
|
2016-11-22 17:23:40 +04:00
|
|
|
= fun t c -> match t, c with
|
|
|
|
| TEmpty, Stop -> TStop command
|
|
|
|
| TEmpty, More -> TMore command
|
|
|
|
| TEmpty, Seq _ -> TMore command
|
|
|
|
| TEmpty, Param (_, _, _, next) ->
|
|
|
|
TParam { tree = insert_tree TEmpty next ; stop = None }
|
|
|
|
| TEmpty, Prefix (n, next) ->
|
|
|
|
TPrefix { stop = None ; prefix = [ (n, insert_tree TEmpty next) ] }
|
|
|
|
| TStop command, Param (_, _, _, next) ->
|
|
|
|
TParam { tree = insert_tree TEmpty next ; stop = Some command }
|
|
|
|
| TStop command, Prefix (n, next) ->
|
|
|
|
TPrefix { stop = Some command ;
|
|
|
|
prefix = [ (n, insert_tree TEmpty next) ] }
|
|
|
|
| TParam t, Param (_, _, _, next) ->
|
|
|
|
TParam { t with tree = insert_tree t.tree next }
|
|
|
|
| TPrefix ({ prefix } as l), Prefix (n, next) ->
|
|
|
|
let rec insert_prefix = function
|
|
|
|
| [] -> [ (n, insert_tree TEmpty next) ]
|
|
|
|
| (n', t) :: rest when n = n' -> (n, insert_tree t next) :: rest
|
|
|
|
| item :: rest -> item :: insert_prefix rest in
|
|
|
|
TPrefix { l with prefix = insert_prefix prefix }
|
|
|
|
| TPrefix ({ stop = None } as l), Stop ->
|
|
|
|
TPrefix { l with stop = Some command }
|
|
|
|
| TParam ({ stop = None } as l), Stop ->
|
|
|
|
TParam { l with stop = Some command }
|
|
|
|
| _, _ ->
|
|
|
|
Pervasives.failwith
|
|
|
|
"Cli_entries.Command_tree.insert: conflicting commands" in
|
|
|
|
insert_tree root params
|
|
|
|
|
|
|
|
let make_dispatch_tree commands =
|
|
|
|
List.fold_left insert_in_dispatch_tree TEmpty commands
|
|
|
|
|
|
|
|
let tree_dispatch tree last args =
|
|
|
|
let rec loop = function
|
|
|
|
| TStop c, [] -> exec c last args
|
|
|
|
| TPrefix { stop = Some c }, [] -> exec c last args
|
|
|
|
| TMore c, _ -> exec c last args
|
|
|
|
| TPrefix { prefix }, n :: rest ->
|
|
|
|
begin try
|
|
|
|
let t = List.assoc n prefix in
|
|
|
|
loop (t, rest)
|
2017-04-05 12:22:41 +04:00
|
|
|
with Not_found -> fail Command_not_found end
|
2016-11-22 17:23:40 +04:00
|
|
|
| TParam { tree }, _ :: rest ->
|
|
|
|
loop (tree, rest)
|
2017-04-05 12:22:41 +04:00
|
|
|
| _, _ -> fail Command_not_found
|
2016-11-22 17:23:40 +04:00
|
|
|
in
|
|
|
|
loop (tree, args)
|
|
|
|
|
2016-12-02 02:20:23 +04:00
|
|
|
let inline_tree_dispatch tree () =
|
2016-11-22 17:23:40 +04:00
|
|
|
let state = ref (tree, []) in
|
|
|
|
fun arg -> match !state, arg with
|
|
|
|
| (( TStop c |
|
|
|
|
TMore c |
|
|
|
|
TPrefix { stop = Some c } |
|
|
|
|
TParam { stop = Some c}), acc),
|
|
|
|
`End ->
|
|
|
|
state := (TEmpty, []) ;
|
2016-12-02 02:20:23 +04:00
|
|
|
`Res (fun last -> exec c last (List.rev acc))
|
2016-11-22 17:23:40 +04:00
|
|
|
| (TMore c, acc), `Arg n ->
|
|
|
|
state := (TMore c, n :: acc) ;
|
|
|
|
`Nop
|
|
|
|
| (TPrefix { prefix }, acc), `Arg n ->
|
|
|
|
begin try
|
|
|
|
let t = List.assoc n prefix in
|
|
|
|
state := (t, n :: acc) ;
|
|
|
|
begin match t with
|
2016-12-03 16:05:02 +04:00
|
|
|
| TStop (Command { args })
|
|
|
|
| TMore (Command { args }) -> `Args args
|
2016-11-22 17:23:40 +04:00
|
|
|
| _ -> `Nop end
|
2017-04-05 12:22:41 +04:00
|
|
|
with Not_found -> `Fail [Command_not_found] end
|
2016-11-22 17:23:40 +04:00
|
|
|
| (TParam { tree }, acc), `Arg n ->
|
|
|
|
state := (tree, n :: acc) ;
|
|
|
|
begin match tree with
|
2016-12-03 16:05:02 +04:00
|
|
|
| TStop (Command { args })
|
|
|
|
| TMore (Command { args }) -> `Args args
|
2016-11-22 17:23:40 +04:00
|
|
|
| _ -> `Nop end
|
2017-04-05 12:22:41 +04:00
|
|
|
| _, _ -> `Fail [Command_not_found]
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* Try a list of commands on a list of arguments *)
|
2016-11-22 17:23:40 +04:00
|
|
|
let dispatch commands =
|
|
|
|
let tree = make_dispatch_tree commands in
|
|
|
|
tree_dispatch tree
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* Argument-by-argument dispatcher to be used during argument parsing *)
|
2016-11-22 17:23:40 +04:00
|
|
|
let inline_dispatch commands =
|
|
|
|
let tree = make_dispatch_tree commands in
|
|
|
|
inline_tree_dispatch tree
|
2016-09-08 21:13:10 +04:00
|
|
|
|
|
|
|
(* Command line help for a set of commands *)
|
2016-11-22 17:23:40 +04:00
|
|
|
let usage
|
2016-12-03 16:05:02 +04:00
|
|
|
(type arg) (type ret)
|
|
|
|
~commands options =
|
2016-09-08 21:13:10 +04:00
|
|
|
let trim s = (* config-file wokaround *)
|
|
|
|
Utils.split '\n' s |>
|
|
|
|
List.map String.trim |>
|
|
|
|
String.concat "\n" in
|
2016-11-22 17:23:40 +04:00
|
|
|
let rec help
|
2016-12-03 16:05:02 +04:00
|
|
|
: type a. Format.formatter -> (a, arg, ret) params -> unit
|
2016-11-22 17:23:40 +04:00
|
|
|
= fun ppf -> function
|
2016-09-08 21:13:10 +04:00
|
|
|
| Stop -> ()
|
|
|
|
| More -> Format.fprintf ppf "..."
|
|
|
|
| Seq (n, "", _) -> Format.fprintf ppf "[ (%s) ...]" n
|
|
|
|
| Seq (_, desc, _) -> Format.fprintf ppf "[ (%s) ... ]" desc
|
|
|
|
| Prefix (n, Stop) -> Format.fprintf ppf "%s" n
|
|
|
|
| Param (n, "", _, Stop) -> Format.fprintf ppf "(%s)" n
|
|
|
|
| Param (_, desc, _, Stop) -> Format.fprintf ppf "(%s)" desc
|
|
|
|
| Prefix (n, next) -> Format.fprintf ppf "%s %a" n help next
|
|
|
|
| Param (n, "", _, next) -> Format.fprintf ppf "(%s) %a" n help next
|
|
|
|
| Param (_, desc, _, next) -> Format.fprintf ppf "(%s) %a" desc help next in
|
2016-11-22 17:23:40 +04:00
|
|
|
let rec help_sum
|
2016-12-03 16:05:02 +04:00
|
|
|
: type a. Format.formatter -> (a, arg, ret) params -> unit
|
2016-11-22 17:23:40 +04:00
|
|
|
= fun ppf -> function
|
2016-09-08 21:13:10 +04:00
|
|
|
| Stop -> ()
|
|
|
|
| More -> Format.fprintf ppf "..."
|
|
|
|
| Seq (n, _, _) -> Format.fprintf ppf "[ (%s) ... ]" n
|
|
|
|
| Prefix (n, Stop) -> Format.fprintf ppf "%s" n
|
|
|
|
| Param (n, _, _, Stop) -> Format.fprintf ppf "(%s)" n
|
|
|
|
| Prefix (n, next) -> Format.fprintf ppf "%s %a" n help_sum next
|
|
|
|
| Param (n, _, _, next) -> Format.fprintf ppf "(%s) %a" n help_sum next in
|
2016-11-22 17:23:40 +04:00
|
|
|
let rec help_args
|
2016-12-03 16:05:02 +04:00
|
|
|
: type a. Format.formatter -> (a, arg, ret) params -> unit
|
2016-11-22 17:23:40 +04:00
|
|
|
= fun ppf -> function
|
|
|
|
| Stop -> ()
|
|
|
|
| More -> Format.fprintf ppf "..."
|
|
|
|
| Seq (n, desc, _) ->
|
|
|
|
Format.fprintf ppf "(%s): @[<hov>%a@]"
|
|
|
|
n Format.pp_print_text (trim desc)
|
|
|
|
| Prefix (_, next) -> help_args ppf next
|
|
|
|
| Param (n, desc, _, Stop) ->
|
|
|
|
Format.fprintf ppf "(%s): @[<hov>%a@]"
|
|
|
|
n Format.pp_print_text (trim desc)
|
|
|
|
| Param (n, desc, _, next) ->
|
|
|
|
Format.fprintf ppf "(%s): @[<hov>%a@]@,%a"
|
|
|
|
n Format.pp_print_text (trim desc) help_args next in
|
2016-09-08 21:13:10 +04:00
|
|
|
let option_help ppf (n, opt, desc) =
|
|
|
|
Format.fprintf ppf "%s%s" n
|
|
|
|
Arg.(let rec example opt = match opt with
|
|
|
|
| Unit _ -> ""
|
|
|
|
| Bool _ -> " <true | false>"
|
|
|
|
| Set _ -> ""
|
|
|
|
| Clear _ -> ""
|
|
|
|
| String _ -> " <text>"
|
|
|
|
| Set_string _ -> " <text>"
|
|
|
|
| Int _ -> " <integer>"
|
|
|
|
| Set_int _ -> " <integer>"
|
|
|
|
| Float _ -> " <number>"
|
|
|
|
| Set_float _ -> " <number>"
|
|
|
|
| Tuple opts -> List.map example opts |> String.concat ""
|
|
|
|
| Symbol (syms, _) -> " <" ^ String.concat " | " syms ^ ">"
|
|
|
|
| Rest _ -> "" in example opt) ;
|
|
|
|
if desc <> "" then
|
|
|
|
Format.fprintf ppf "@, @[<hov>%a@]" Format.pp_print_text (trim desc) in
|
2016-12-03 16:05:02 +04:00
|
|
|
let command_help ppf (Command { params ; desc ; args }) =
|
|
|
|
let small = Format.asprintf "@[<h>%a@]" help params in
|
|
|
|
let desc = trim desc in
|
2016-09-08 21:13:10 +04:00
|
|
|
if String.length small < 50 then begin
|
|
|
|
Format.fprintf ppf "@[<v 2>%s@,@[<hov>%a@]"
|
2016-11-22 17:23:40 +04:00
|
|
|
small Format.pp_print_text desc
|
2016-09-08 21:13:10 +04:00
|
|
|
end else begin
|
|
|
|
Format.fprintf ppf "@[<v 2>%a@,@[<hov 0>%a@]@,%a"
|
2016-12-03 16:05:02 +04:00
|
|
|
help_sum params
|
2016-11-22 17:23:40 +04:00
|
|
|
Format.pp_print_text desc
|
2016-12-03 16:05:02 +04:00
|
|
|
help_args params ;
|
2016-09-08 21:13:10 +04:00
|
|
|
end ;
|
2016-12-05 16:18:12 +04:00
|
|
|
if args = [] then
|
2016-09-08 21:13:10 +04:00
|
|
|
Format.fprintf ppf "@]"
|
|
|
|
else
|
2016-11-22 17:23:40 +04:00
|
|
|
Format.fprintf ppf "@,%a@]"
|
|
|
|
(Format.pp_print_list option_help)
|
2016-12-05 16:18:12 +04:00
|
|
|
args in
|
2016-12-03 16:05:02 +04:00
|
|
|
let rec group_help ppf ({ title }, commands) =
|
2016-09-08 21:13:10 +04:00
|
|
|
Format.fprintf ppf "@[<v 2>%s:@,%a@]"
|
2016-11-22 17:23:40 +04:00
|
|
|
title
|
2016-12-03 16:05:02 +04:00
|
|
|
(Format.pp_print_list command_help) commands in
|
2016-09-08 21:13:10 +04:00
|
|
|
let usage ppf (by_group, options) =
|
|
|
|
Format.fprintf ppf
|
2016-11-22 17:23:40 +04:00
|
|
|
"@[<v>@[<v 2>Usage:@,%s [ options ] command [ command options ]@]@,\
|
|
|
|
@[<v 2>Options:@,%a@]@,\
|
|
|
|
%a@]"
|
2016-09-08 21:13:10 +04:00
|
|
|
Sys.argv.(0)
|
|
|
|
(Format.pp_print_list option_help) options
|
|
|
|
(Format.pp_print_list group_help) by_group in
|
|
|
|
let by_group =
|
2016-12-03 16:05:02 +04:00
|
|
|
let ungrouped = ref [] in
|
|
|
|
let grouped =
|
|
|
|
List.fold_left
|
|
|
|
(fun acc (Command { group } as command) ->
|
|
|
|
match group with
|
|
|
|
| None ->
|
|
|
|
ungrouped := command :: !ungrouped ;
|
|
|
|
acc
|
|
|
|
| Some group ->
|
|
|
|
try
|
|
|
|
let ({ title }, r) =
|
|
|
|
List.find (fun ({ name }, _) -> group.name = name) acc in
|
|
|
|
if title <> group.title then
|
|
|
|
invalid_arg "Cli_entries.usage: duplicate group name" ;
|
|
|
|
r := command :: !r ;
|
|
|
|
acc
|
|
|
|
with Not_found ->
|
|
|
|
(group, ref [ command ]) :: acc)
|
|
|
|
[] commands in
|
2017-03-15 04:17:20 +04:00
|
|
|
let misc = match !ungrouped with
|
|
|
|
| [] -> []
|
|
|
|
| l ->
|
|
|
|
[ { name = "untitled" ; title = "Miscellaneous commands" },
|
|
|
|
List.rev l ]
|
|
|
|
in
|
|
|
|
List.map (fun (g, c) -> (g, List.rev !c)) grouped @ misc in
|
2016-09-08 21:13:10 +04:00
|
|
|
Format.asprintf "%a" usage (by_group, options)
|