@@ -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
@@ -534,6 +556,8 @@ module Odoc_html_args = struct
534556 Term. (
535557 const config $ semantic_uris $ closed_details $ indent $ theme_uri
536558 $ support_uri $ flat $ as_json)
559+
560+ let generate_docs = section_pipeline
537561end
538562
539563module Odoc_html = Make_renderer (Odoc_html_args )
@@ -563,8 +587,8 @@ end = struct
563587 $ odoc_file_directories $ reference))
564588
565589 let info =
566- Term. info ~doc: " Resolve a reference and output its corresponding url "
567- " html-url"
590+ Term. info ~docs: section_support
591+ ~doc: " Resolve a reference and output its corresponding url " " html-url"
568592end
569593
570594module Html_fragment : sig
@@ -612,8 +636,8 @@ end = struct
612636 $ input $ warnings_options))
613637
614638 let info =
615- Term. info ~doc: " Generates an html fragment file from an mld one "
616- " html-fragment"
639+ Term. info ~docs: section_legacy
640+ ~doc: " Generates an html fragment file from an mld one " " html-fragment"
617641end
618642
619643module Odoc_manpage = Make_renderer (struct
@@ -622,6 +646,8 @@ module Odoc_manpage = Make_renderer (struct
622646 let renderer = Man_page. renderer
623647
624648 let extra_args = Term. const ()
649+
650+ let generate_docs = section_generators
625651end )
626652
627653module Odoc_latex = Make_renderer (struct
@@ -636,6 +662,8 @@ module Odoc_latex = Make_renderer (struct
636662 let extra_args =
637663 let f with_children = { Latex. with_children } in
638664 Term. (const f $ with_children)
665+
666+ let generate_docs = section_generators
639667end )
640668
641669module Depends = struct
@@ -660,7 +688,7 @@ module Depends = struct
660688 Term. (const list_dependencies $ input)
661689
662690 let info =
663- Term. info " compile-deps"
691+ Term. info " compile-deps" ~docs: section_legacy
664692 ~doc:
665693 " List units (with their digest) which needs to be compiled in order \
666694 to compile this one. The unit itself and its digest is also \
@@ -706,7 +734,7 @@ module Depends = struct
706734 Term. (const handle_error $ (const list_dependencies $ input))
707735
708736 let info =
709- Term. info " link-deps"
737+ Term. info " link-deps" ~docs: section_legacy
710738 ~doc:
711739 " lists the packages which need to be in odoc's load path to link the \
712740 .odoc files in the given directory"
@@ -728,7 +756,9 @@ module Depends = struct
728756 let cmd _ = Link. list_dependencies in
729757 Term. (const handle_error $ (const cmd $ includes $ input))
730758
731- let info = Term. info " html-deps" ~doc: " DEPRECATED: alias for link-deps"
759+ let info =
760+ Term. info " html-deps" ~docs: section_deprecated
761+ ~doc: " DEPRECATED: alias for link-deps"
732762 end
733763end
734764
@@ -742,7 +772,8 @@ module Targets = struct
742772
743773 let cmd = Term. (const list_targets $ Compile. dst $ Compile. input)
744774
745- let info = Term. info " compile-targets" ~doc: " TODO: Fill in."
775+ let info =
776+ Term. info " compile-targets" ~docs: section_legacy ~doc: " TODO: Fill in."
746777 end
747778
748779 module Support_files = struct
@@ -753,7 +784,7 @@ module Targets = struct
753784 Term. (const list_targets $ Support_files_command. without_theme $ dst () )
754785
755786 let info =
756- Term. info " support-files-targets"
787+ Term. info " support-files-targets" ~docs: section_support
757788 ~doc: " Lists the names of the files that 'odoc support-files' outputs."
758789 end
759790end
@@ -774,7 +805,7 @@ module Odoc_error = struct
774805 let cmd = Term. (const handle_error $ (const errors $ input))
775806
776807 let info =
777- Term. info " errors"
808+ Term. info " errors" ~docs: section_support
778809 ~doc: " Print errors that occurred while an .odoc file was generated."
779810end
780811
@@ -815,8 +846,12 @@ let () =
815846 " Available subcommands: %s\n See --help for more information.\n %!"
816847 (String. concat ~sep: " , " available_subcommands)
817848 in
849+ let man =
850+ (* Show sections in a defined order. *)
851+ List. map ~f: (fun s -> `S s) sections
852+ in
818853 ( Term. (const print_default $ const () ),
819- Term. info ~version: " %%VERSION%%" " odoc" )
854+ Term. info ~man ~ version:" %%VERSION%%" " odoc" )
820855 in
821856 match Term. eval_choice ~err: Format. err_formatter default subcommands with
822857 | `Error _ ->
0 commit comments