Skip to content

Commit

Permalink
draft
Browse files Browse the repository at this point in the history
  • Loading branch information
lubegasimon committed Sep 15, 2021
1 parent 1704036 commit bcd67fb
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 16 deletions.
21 changes: 11 additions & 10 deletions src/markdown/generator.ml
Expand Up @@ -94,6 +94,8 @@ let style (style : style) content =
| `Superscript -> command "<sup>" content
| `Subscript -> command "<sub>" content

let no_link = ref true

let rec source_code (s : Source.t) =
match s with
| [] -> noop
Expand Down Expand Up @@ -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 !no_link then
(let rec f (content : Inline.t) =
match content with
| [] -> noop
Expand All @@ -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 !no_link then
match link.page.parent with
| Some _ -> inline content ++ inline rest
| None ->
Expand Down Expand Up @@ -306,14 +308,13 @@ 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 ]

and subpages (no_link : bool) i =
and subpages no_link i =
list_concat_map ~f:(calc_subpages no_link) @@ Doctree.Subpages.compute i

and page (no_link : bool) ({ Page.header; items; url; _ } as p) =
and page no_link ({ 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
Expand All @@ -322,14 +323,14 @@ and page (no_link : bool) ({ Page.header; items; url; _ } as p) =
@ [ item "&nbsp; " header ++ item "&nbsp; " 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 !no_link 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 }
3 changes: 1 addition & 2 deletions 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
2 changes: 0 additions & 2 deletions 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) =
Expand Down
4 changes: 2 additions & 2 deletions src/odoc/markdown.ml
Expand Up @@ -2,8 +2,8 @@ open Odoc_document

type args = { no_link : 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

Expand Down

0 comments on commit bcd67fb

Please sign in to comment.