Skip to content

Commit 9059f17

Browse files
committed
draft
1 parent 1704036 commit 9059f17

File tree

5 files changed

+27
-26
lines changed

5 files changed

+27
-26
lines changed

src/markdown/generator.ml

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,8 @@ let style (style : style) content =
9494
| `Superscript -> command "<sup>" content
9595
| `Subscript -> command "<sub>" content
9696

97+
let generate_links = ref true
98+
9799
let rec source_code (s : Source.t) =
98100
match s with
99101
| [] -> noop
@@ -122,7 +124,7 @@ and inline (l : Inline.t) =
122124
| Styled (sty, content) -> style sty (inline content) ++ inline rest
123125
| Linebreak -> break ++ inline rest
124126
| Link (href, content) ->
125-
if !Link.no_link then
127+
if !generate_links then
126128
(let rec f (content : Inline.t) =
127129
match content with
128130
| [] -> noop
@@ -136,7 +138,7 @@ and inline (l : Inline.t) =
136138
++ inline rest
137139
else inline content ++ inline rest
138140
| InternalLink (Resolved (link, content)) ->
139-
if !Link.no_link then
141+
if !generate_links then
140142
match link.page.parent with
141143
| Some _ -> inline content ++ inline rest
142144
| None ->
@@ -306,30 +308,32 @@ let on_sub subp =
306308
| `Page p -> if Link.should_inline p.Subpage.content.url then Some 1 else None
307309
| `Include incl -> if inline_subpage incl.Include.status then Some 0 else None
308310

309-
(** TODO: Rename the function. *)
310-
let rec calc_subpages (no_link : bool) { Subpage.content; _ } =
311-
[ page no_link content ]
311+
let rec calc_subpages (generate_links : bool) { Subpage.content; _ } =
312+
[ page generate_links content ]
312313

313-
and subpages (no_link : bool) i =
314-
list_concat_map ~f:(calc_subpages no_link) @@ Doctree.Subpages.compute i
314+
and subpages generate_links i =
315+
list_concat_map ~f:(calc_subpages generate_links)
316+
@@ Doctree.Subpages.compute i
315317

316-
and page (no_link : bool) ({ Page.header; items; url; _ } as p) =
318+
and page generate_links ({ Page.header; items; url; _ } as p) =
317319
let header = Shift.compute ~on_sub header in
318320
let items = Shift.compute ~on_sub items in
319-
let subpages = subpages no_link p in
321+
let subpages = subpages generate_links p in
320322
Block
321323
([ Inline (Link.for_printing url) ]
322324
@ [ item "&nbsp; " header ++ item "&nbsp; " items ]
323325
@ subpages)
324326

325-
let rec subpage subp ~no_link =
327+
let rec subpage subp =
326328
let p = subp.Subpage.content in
327-
if Link.should_inline p.url then [] else [ render p ~no_link ]
329+
if Link.should_inline p.url then [] else [ render p ]
328330

329-
and render (p : Page.t) ~no_link =
330-
let content fmt = Format.fprintf fmt "%a" Markup.pp (page no_link p) in
331+
and render (p : Page.t) =
332+
let content fmt =
333+
Format.fprintf fmt "%a" Markup.pp (page !generate_links p)
334+
in
331335
let children =
332-
Utils.flatmap ~f:(fun subp -> subpage subp ~no_link) (Subpages.compute p)
336+
Utils.flatmap ~f:(fun subp -> subpage subp) (Subpages.compute p)
333337
in
334338
let filename = Link.as_filename p.url in
335339
{ Odoc_document.Renderer.filename; content; children }

src/markdown/generator.mli

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,2 +1 @@
1-
val render :
2-
Odoc_document.Types.Page.t -> no_link:bool -> Odoc_document.Renderer.page
1+
val render : Odoc_document.Types.Page.t -> Odoc_document.Renderer.page

src/markdown/link.ml

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,5 @@
11
open Odoc_document
22

3-
let no_link = ref true
4-
53
let for_printing url = List.map snd @@ Url.Path.to_list url
64

75
let segment_to_string (kind, name) =

src/odoc/bin/main.ml

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -577,16 +577,16 @@ module Odoc_markdown = Make_renderer (struct
577577

578578
let renderer = Markdown.renderer
579579

580-
let no_link =
580+
let generate_links =
581581
let doc =
582-
"If no-link flag is passed, the rendered markdown\n\
582+
"If generate_links flag is passed, the rendered markdown\n\
583583
\ output should not contain links, rather plain text."
584584
in
585-
Arg.(value & flag (info ~doc [ "no-link" ]))
585+
Arg.(value & flag (info ~doc [ "generate-links" ]))
586586

587587
let extra_args =
588-
let f no_link = { Markdown.no_link } in
589-
Term.(const f $ no_link)
588+
let f generate_links = { Markdown.generate_links } in
589+
Term.(const f $ generate_links)
590590
end)
591591

592592
module Depends = struct

src/odoc/markdown.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
open Odoc_document
22

3-
type args = { no_link : bool }
3+
type args = { generate_links : bool }
44

5-
let render args (page : Odoc_document.Types.Page.t) =
6-
Odoc_markdown.Generator.render ~no_link:args.no_link page
5+
let render _ (page : Odoc_document.Types.Page.t) : Odoc_document.Renderer.page =
6+
Odoc_markdown.Generator.render page
77

88
let files_of_url url = Odoc_markdown.Link.files_of_url url
99

0 commit comments

Comments
 (0)