@@ -111,6 +111,22 @@ let open_modules =
111111 let default = [ " Stdlib" ] in
112112 Arg. (value & opt_all string default & info ~docv: " MODULE" ~doc [ " open" ])
113113
114+ let section_pipeline = " COMMANDS: Compilation pipeline"
115+ let section_generators = " COMMANDS: Alternative generators"
116+ let section_support = " COMMANDS: Scripting"
117+ let section_legacy = " COMMANDS: Legacy pipeline"
118+ let section_deprecated = " COMMANDS: Deprecated"
119+
120+ (* * Sections in the order they should appear. *)
121+ let sections =
122+ [
123+ section_pipeline;
124+ section_generators;
125+ section_support;
126+ section_legacy;
127+ section_deprecated;
128+ ]
129+
114130module Compile : sig
115131 val output_file : dst :string option -> input :Fs .file -> Fs .file
116132
@@ -224,7 +240,7 @@ end = struct
224240 $ warnings_options))
225241
226242 let info =
227- Term. info " compile"
243+ Term. info " compile" ~docs: section_pipeline
228244 ~doc: " Compile a cmti, cmt, cmi or mld file to an odoc file."
229245end
230246
@@ -243,7 +259,7 @@ module Support_files_command = struct
243259 " Copy the support files (e.g. default theme, JavaScript files) to the \
244260 output directory."
245261 in
246- Term. info ~doc " support-files"
262+ Term. info ~docs: section_pipeline ~ doc " support-files"
247263end
248264
249265module Css = struct
@@ -254,7 +270,7 @@ module Css = struct
254270 " DEPRECATED: Use `odoc support-files' to copy the CSS file for the \
255271 default theme."
256272 in
257- Term. info ~doc " css"
273+ Term. info ~docs: section_deprecated ~ doc " css"
258274end
259275
260276module Odoc_link : sig
@@ -295,7 +311,8 @@ end = struct
295311 $ (const link $ odoc_file_directories $ input $ dst $ warnings_options
296312 $ open_modules))
297313
298- let info = Term. info ~doc: " Link odoc files together" " link"
314+ let info =
315+ Term. info ~docs: section_pipeline ~doc: " Link odoc files together" " link"
299316end
300317
301318module type S = sig
@@ -304,6 +321,8 @@ module type S = sig
304321 val renderer : args Odoc_document.Renderer .t
305322
306323 val extra_args : args Cmdliner.Term .t
324+
325+ val generate_docs : string
307326end
308327
309328module Make_renderer (R : S ) : sig
@@ -345,7 +364,7 @@ end = struct
345364 let doc =
346365 Format. sprintf " Render %s files from an odoc one" R. renderer.name
347366 in
348- Term. info ~doc R. renderer.name
367+ Term. info ~docs: section_legacy ~ doc R. renderer.name
349368 end
350369
351370 let process = Process. (cmd, info)
@@ -375,7 +394,7 @@ end = struct
375394 let doc =
376395 Format. sprintf " Generate %s files from an odocl one" R. renderer.name
377396 in
378- Term. info ~doc (R. renderer.name ^ " -generate" )
397+ Term. info ~docs: R. generate_docs ~ doc (R. renderer.name ^ " -generate" )
379398 end
380399
381400 let generate = Generate. (cmd, info)
@@ -407,7 +426,10 @@ end = struct
407426 const handle_error
408427 $ (const list_targets $ dst () $ back_compat $ R. extra_args $ input))
409428
410- let info = Term. info (R. renderer.name ^ " -targets" ) ~doc: " TODO: Fill in."
429+ let info =
430+ Term. info
431+ (R. renderer.name ^ " -targets" )
432+ ~docs: section_support ~doc: " TODO: Fill in."
411433 end
412434
413435 let targets = Targets. (cmd, info)
@@ -430,8 +452,8 @@ end = struct
430452 $ (const reference_to_url $ odoc_file_directories $ reference))
431453
432454 let info =
433- Term. info ~doc: " Resolve a reference and output its corresponding url "
434- " latex-url"
455+ Term. info ~docs: section_support
456+ ~doc: " Resolve a reference and output its corresponding url " " latex-url"
435457end
436458
437459module Odoc_html_args = struct
@@ -540,6 +562,8 @@ module Odoc_html_args = struct
540562 Term. (
541563 const config $ semantic_uris $ closed_details $ indent $ theme_uri
542564 $ support_uri $ flat $ omit_breadcrumbs $ omit_toc $ content_only)
565+
566+ let generate_docs = section_pipeline
543567end
544568
545569module Odoc_html = Make_renderer (Odoc_html_args )
@@ -569,8 +593,8 @@ end = struct
569593 $ odoc_file_directories $ reference))
570594
571595 let info =
572- Term. info ~doc: " Resolve a reference and output its corresponding url "
573- " html-url"
596+ Term. info ~docs: section_support
597+ ~doc: " Resolve a reference and output its corresponding url " " html-url"
574598end
575599
576600module Html_fragment : sig
@@ -618,8 +642,8 @@ end = struct
618642 $ input $ warnings_options))
619643
620644 let info =
621- Term. info ~doc: " Generates an html fragment file from an mld one "
622- " html-fragment"
645+ Term. info ~docs: section_legacy
646+ ~doc: " Generates an html fragment file from an mld one " " html-fragment"
623647end
624648
625649module Odoc_manpage = Make_renderer (struct
@@ -628,6 +652,8 @@ module Odoc_manpage = Make_renderer (struct
628652 let renderer = Man_page. renderer
629653
630654 let extra_args = Term. const ()
655+
656+ let generate_docs = section_generators
631657end )
632658
633659module Odoc_latex = Make_renderer (struct
@@ -642,6 +668,8 @@ module Odoc_latex = Make_renderer (struct
642668 let extra_args =
643669 let f with_children = { Latex. with_children } in
644670 Term. (const f $ with_children)
671+
672+ let generate_docs = section_generators
645673end )
646674
647675module Depends = struct
@@ -666,7 +694,7 @@ module Depends = struct
666694 Term. (const list_dependencies $ input)
667695
668696 let info =
669- Term. info " compile-deps"
697+ Term. info " compile-deps" ~docs: section_legacy
670698 ~doc:
671699 " List units (with their digest) which needs to be compiled in order \
672700 to compile this one. The unit itself and its digest is also \
@@ -712,7 +740,7 @@ module Depends = struct
712740 Term. (const handle_error $ (const list_dependencies $ input))
713741
714742 let info =
715- Term. info " link-deps"
743+ Term. info " link-deps" ~docs: section_legacy
716744 ~doc:
717745 " lists the packages which need to be in odoc's load path to link the \
718746 .odoc files in the given directory"
@@ -734,7 +762,9 @@ module Depends = struct
734762 let cmd _ = Link. list_dependencies in
735763 Term. (const handle_error $ (const cmd $ includes $ input))
736764
737- let info = Term. info " html-deps" ~doc: " DEPRECATED: alias for link-deps"
765+ let info =
766+ Term. info " html-deps" ~docs: section_deprecated
767+ ~doc: " DEPRECATED: alias for link-deps"
738768 end
739769end
740770
@@ -748,7 +778,8 @@ module Targets = struct
748778
749779 let cmd = Term. (const list_targets $ Compile. dst $ Compile. input)
750780
751- let info = Term. info " compile-targets" ~doc: " TODO: Fill in."
781+ let info =
782+ Term. info " compile-targets" ~docs: section_legacy ~doc: " TODO: Fill in."
752783 end
753784
754785 module Support_files = struct
@@ -759,7 +790,7 @@ module Targets = struct
759790 Term. (const list_targets $ Support_files_command. without_theme $ dst () )
760791
761792 let info =
762- Term. info " support-files-targets"
793+ Term. info " support-files-targets" ~docs: section_support
763794 ~doc: " Lists the names of the files that 'odoc support-files' outputs."
764795 end
765796end
@@ -780,7 +811,7 @@ module Odoc_error = struct
780811 let cmd = Term. (const handle_error $ (const errors $ input))
781812
782813 let info =
783- Term. info " errors"
814+ Term. info " errors" ~docs: section_support
784815 ~doc: " Print errors that occurred while an .odoc file was generated."
785816end
786817
@@ -821,8 +852,12 @@ let () =
821852 " Available subcommands: %s\n See --help for more information.\n %!"
822853 (String. concat ~sep: " , " available_subcommands)
823854 in
855+ let man =
856+ (* Show sections in a defined order. *)
857+ List. map ~f: (fun s -> `S s) sections
858+ in
824859 ( Term. (const print_default $ const () ),
825- Term. info ~version: " %%VERSION%%" " odoc" )
860+ Term. info ~man ~ version:" %%VERSION%%" " odoc" )
826861 in
827862 match Term. eval_choice ~err: Format. err_formatter default subcommands with
828863 | `Error _ ->
0 commit comments