diff --git a/src/markdown/generator.ml b/src/markdown/generator.ml index e6605c3c2b..04d3629d39 100644 --- a/src/markdown/generator.ml +++ b/src/markdown/generator.ml @@ -94,6 +94,8 @@ let style (style : style) content = | `Superscript -> command "" content | `Subscript -> command "" content +let generate_links = ref true + let rec source_code (s : Source.t) = match s with | [] -> noop @@ -122,7 +124,7 @@ and inline (l : Inline.t) = | Styled (sty, content) -> style sty (inline content) ++ inline rest | Linebreak -> break ++ inline rest | Link (href, content) -> - if !Link.no_link then + if !generate_links then (let rec f (content : Inline.t) = match content with | [] -> noop @@ -136,7 +138,7 @@ and inline (l : Inline.t) = ++ inline rest else inline content ++ inline rest | InternalLink (Resolved (link, content)) -> - if !Link.no_link then + if !generate_links then match link.page.parent with | Some _ -> inline content ++ inline rest | None -> @@ -306,30 +308,32 @@ let on_sub subp = | `Page p -> if Link.should_inline p.Subpage.content.url then Some 1 else None | `Include incl -> if inline_subpage incl.Include.status then Some 0 else None -(** TODO: Rename the function. *) -let rec calc_subpages (no_link : bool) { Subpage.content; _ } = - [ page no_link content ] +let rec calc_subpages (generate_links : bool) { Subpage.content; _ } = + [ page generate_links content ] -and subpages (no_link : bool) i = - list_concat_map ~f:(calc_subpages no_link) @@ Doctree.Subpages.compute i +and subpages generate_links i = + list_concat_map ~f:(calc_subpages generate_links) + @@ Doctree.Subpages.compute i -and page (no_link : bool) ({ Page.header; items; url; _ } as p) = +and page generate_links ({ Page.header; items; url; _ } as p) = let header = Shift.compute ~on_sub header in let items = Shift.compute ~on_sub items in - let subpages = subpages no_link p in + let subpages = subpages generate_links p in Block ([ Inline (Link.for_printing url) ] @ [ item "  " header ++ item "  " items ] @ subpages) -let rec subpage subp ~no_link = +let rec subpage subp = let p = subp.Subpage.content in - if Link.should_inline p.url then [] else [ render p ~no_link ] + if Link.should_inline p.url then [] else [ render p ] -and render (p : Page.t) ~no_link = - let content fmt = Format.fprintf fmt "%a" Markup.pp (page no_link p) in +and render (p : Page.t) = + let content fmt = + Format.fprintf fmt "%a" Markup.pp (page !generate_links p) + in let children = - Utils.flatmap ~f:(fun subp -> subpage subp ~no_link) (Subpages.compute p) + Utils.flatmap ~f:(fun subp -> subpage subp) (Subpages.compute p) in let filename = Link.as_filename p.url in { Odoc_document.Renderer.filename; content; children } diff --git a/src/markdown/generator.mli b/src/markdown/generator.mli index 115965f773..3d87bdb3f1 100644 --- a/src/markdown/generator.mli +++ b/src/markdown/generator.mli @@ -1,2 +1 @@ -val render : - Odoc_document.Types.Page.t -> no_link:bool -> Odoc_document.Renderer.page +val render : Odoc_document.Types.Page.t -> Odoc_document.Renderer.page diff --git a/src/markdown/link.ml b/src/markdown/link.ml index a8f13c2213..6f16f54138 100644 --- a/src/markdown/link.ml +++ b/src/markdown/link.ml @@ -1,7 +1,5 @@ open Odoc_document -let no_link = ref true - let for_printing url = List.map snd @@ Url.Path.to_list url let segment_to_string (kind, name) = diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 488eeef50c..4db4add0f5 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -577,16 +577,16 @@ module Odoc_markdown = Make_renderer (struct let renderer = Markdown.renderer - let no_link = + let generate_links = let doc = - "If no-link flag is passed, the rendered markdown\n\ + "If generate_links flag is passed, the rendered markdown\n\ \ output should not contain links, rather plain text." in - Arg.(value & flag (info ~doc [ "no-link" ])) + Arg.(value & flag (info ~doc [ "generate-links" ])) let extra_args = - let f no_link = { Markdown.no_link } in - Term.(const f $ no_link) + let f generate_links = { Markdown.generate_links } in + Term.(const f $ generate_links) end) module Depends = struct diff --git a/src/odoc/markdown.ml b/src/odoc/markdown.ml index b2db8cbdc2..3592f1a62e 100644 --- a/src/odoc/markdown.ml +++ b/src/odoc/markdown.ml @@ -1,9 +1,9 @@ open Odoc_document -type args = { no_link : bool } +type args = { generate_links : bool } -let render args (page : Odoc_document.Types.Page.t) = - Odoc_markdown.Generator.render ~no_link:args.no_link page +let render _ (page : Odoc_document.Types.Page.t) : Odoc_document.Renderer.page = + Odoc_markdown.Generator.render page let files_of_url url = Odoc_markdown.Link.files_of_url url