|
3 | 3 |
|
4 | 4 | open Astring
|
5 | 5 |
|
6 |
| -let gen_preamble _cmds = |
7 |
| - Printf.printf "{0 Odoc}\n\nOdoc is made of several sub-commands." |
| 6 | +let with_process_in cmd args f = |
| 7 | + let inp = Unix.open_process_in (Filename.quote_command cmd args) in |
| 8 | + let finally () = ignore (Unix.close_process_in inp) in |
| 9 | + Fun.protect ~finally (fun () -> f inp) |
8 | 10 |
|
9 |
| -let gen_subcommand cmd = |
10 |
| - Printf.printf "\n{1 odoc %s}\n\n{@man[\n%!" cmd; |
11 |
| - ignore (Sys.command (Filename.quote_command "odoc" [ cmd; "--help" ])); |
| 11 | +let cat_command cmd args = |
| 12 | + with_process_in cmd args (fun inp -> |
| 13 | + try |
| 14 | + while true do |
| 15 | + Printf.printf "%s\n" (input_line inp) |
| 16 | + done |
| 17 | + with End_of_file -> ()) |
| 18 | + |
| 19 | +type cmd = { name : string; section : string; summary : string } |
| 20 | + |
| 21 | +let section_prefix = "COMMANDS: " |
| 22 | + |
| 23 | +let parse_man' = |
| 24 | + let rec collect acc kind = function |
| 25 | + | (kind', line) :: tl when kind = kind' -> collect (line :: acc) kind tl |
| 26 | + | tl -> (List.rev acc, tl) |
| 27 | + in |
| 28 | + let rec commands ~section = function |
| 29 | + | (`Command, line) :: tl -> |
| 30 | + let name = List.hd (String.fields ~empty:false line) in |
| 31 | + let _, tl = collect [] `Command tl in |
| 32 | + let summary, tl = collect [] `Summary tl in |
| 33 | + { name; section; summary = String.concat ~sep:" " summary } |
| 34 | + :: commands ~section tl |
| 35 | + | tl -> sections tl |
| 36 | + and sections = function |
| 37 | + | (`Section, line) :: tl when String.is_prefix ~affix:section_prefix line -> |
| 38 | + let first = String.length section_prefix in |
| 39 | + let section = String.with_range ~first line in |
| 40 | + commands ~section tl |
| 41 | + | _ :: tl -> sections tl |
| 42 | + | [] -> [] |
| 43 | + in |
| 44 | + sections |
| 45 | + |
| 46 | +let parse_man inp = |
| 47 | + let lines = ref [] in |
| 48 | + (try |
| 49 | + while true do |
| 50 | + let line = input_line inp in |
| 51 | + if line = "" then () |
| 52 | + else |
| 53 | + let kind = |
| 54 | + if String.is_prefix ~affix:" " line then `Summary |
| 55 | + else if String.is_prefix ~affix:" " line then `Command |
| 56 | + else `Section |
| 57 | + in |
| 58 | + lines := (kind, String.trim line) :: !lines |
| 59 | + done |
| 60 | + with End_of_file -> ()); |
| 61 | + parse_man' (List.rev !lines) |
| 62 | + |
| 63 | +let gen_preamble cmds = |
| 64 | + Printf.printf "{0 Odoc}\n\n{1 odoc}\nOdoc is made of several sub-commands.\n"; |
| 65 | + List.iter |
| 66 | + (fun { name; summary; _ } -> |
| 67 | + Printf.printf "- {!\"odoc-%s\"} %s\n" name summary) |
| 68 | + cmds |
| 69 | + |
| 70 | +let gen_subcommand { name; _ } = |
| 71 | + Printf.printf "\n{1 odoc %s}\n\n{@man[\n%!" name; |
| 72 | + cat_command "odoc" [ name; "--help" ]; |
12 | 73 | Printf.printf "]}\n"
|
13 | 74 |
|
14 | 75 | let () =
|
15 |
| - let line0 = input_line stdin in |
16 |
| - let subcommands = |
17 |
| - match String.cut ~sep:":" line0 with |
18 |
| - | Some (_, s) -> String.cuts ~sep:"," s |> List.map String.trim |
19 |
| - | None -> assert false |
20 |
| - in |
| 76 | + let subcommands = with_process_in "odoc" [ "--help" ] parse_man in |
21 | 77 | gen_preamble subcommands;
|
22 | 78 | List.iter gen_subcommand subcommands
|
0 commit comments