Skip to content

Commit

Permalink
Add an option to not link children
Browse files Browse the repository at this point in the history
  • Loading branch information
Octachron committed Jul 1, 2020
1 parent edab964 commit 2b33511
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 4 deletions.
9 changes: 7 additions & 2 deletions src/odoc/bin/main.ml
Expand Up @@ -340,10 +340,10 @@ module Odoc_latex : sig
val info: Term.info
end = struct

let latex directories output_dir syntax input_file =
let latex directories output_dir syntax with_children input_file =
let env = Env.create ~important_digests:false ~directories in
let file = Fs.File.of_string input_file in
Latex.from_odoc ~env ~syntax ~output:output_dir file
Latex.from_odoc ~env ~syntax ~output:output_dir ~with_children file

let cmd =
let input =
Expand All @@ -356,9 +356,14 @@ end = struct
in
Arg.(value & opt (pconv convert_syntax) (Odoc_document.Renderer.OCaml) @@ info ~docv:"SYNTAX" ~doc ~env ["syntax"])
in
let with_children =
let doc = "Include children at the end of the page" in
Arg.(value & opt bool true & info ~docv:"BOOL" ~doc ["with-children"])
in
Term.(const handle_error $ (const latex $
odoc_file_directories $ dst ~create:true () $
syntax $
with_children $
input))

let info =
Expand Down
4 changes: 2 additions & 2 deletions src/odoc/latex.ml
Expand Up @@ -64,7 +64,7 @@ let traverse ~f t =
aux [] t


let from_odoc ~env ?(syntax=Renderer.OCaml) ~output:root_dir input =
let from_odoc ~env ?(syntax=Renderer.OCaml) ?(with_children=true) ~output:root_dir input =
Root.read input >>= fun root ->
match root.file with
| Page page_name ->
Expand All @@ -88,7 +88,7 @@ let from_odoc ~env ?(syntax=Renderer.OCaml) ~output:root_dir input =
let page_name = String.concat ~sep:"." (List.rev @@ name :: parents) in
with_tex_file ~pkg_dir ~page_name (fun ppf ->
content ppf;
link_children pkg_dir parents name children_names ppf
if with_children then link_children pkg_dir parents name children_names ppf
)
);
Ok ()

0 comments on commit 2b33511

Please sign in to comment.