Skip to content

Commit

Permalink
Respond to review comments
Browse files Browse the repository at this point in the history
  • Loading branch information
jonludlam committed Jan 13, 2025
1 parent fc7fb9a commit 84023d6
Show file tree
Hide file tree
Showing 3 changed files with 56 additions and 49 deletions.
3 changes: 1 addition & 2 deletions src/driver/library_names.ml
Original file line number Diff line number Diff line change
Expand Up @@ -110,8 +110,7 @@ let directories v =
List.fold_left
(fun acc x ->
match x.dir with
| None
| Some "" -> Fpath.Set.add meta_dir acc
| None | Some "" -> Fpath.Set.add meta_dir acc
| Some x -> (
let dir = Fpath.(meta_dir // v x) in
(* NB. topkg installs a META file that points to a ../topkg-care directory
Expand Down
96 changes: 52 additions & 44 deletions src/markdown/doc_of_md.ml
Original file line number Diff line number Diff line change
Expand Up @@ -166,8 +166,7 @@ type nestable_ast_acc =
let link_definition defs l =
match Inline.Link.reference_definition defs l with
| Some (Link_definition.Def (ld, _)) -> Some ld
| Some (Block.Footnote.Def (_, _)) ->
None
| Some (Block.Footnote.Def (_, _)) -> None
| Some _ -> assert false
| None -> assert false (* assert [l]'s referenced label is not synthetic *)

Expand Down Expand Up @@ -215,30 +214,39 @@ let image_to_inline_element ~locator defs i m (is, warns) =
let b = Buffer.create 255 in
let ld = link_definition defs i in
match ld with
| None ->
(is, warns)
| None -> (is, warns)
| Some ld ->
let link =
match Link_definition.dest ld with
| None -> ""
| Some (link, _) -> pct_esc b link
in
let title =
match Link_definition.title ld with
| None -> ""
| Some title ->
let title = List.map Block_line.tight_to_string title in
html_esc b (String.concat "\n" title)
in
let alt =
let ls = Inline.to_plain_text ~break_on_soft:false (Inline.Link.text i) in
html_esc b (String.concat "\n" (List.map (String.concat "") ls))
in
let img =
String.concat ""
[ {|<img src="|}; link; {|" alt="|}; alt; {|" title="|}; title; {|" >"|} ]
in
(Loc.at loc (`Raw_markup (Some "html", img)) :: is, warns)
let link =
match Link_definition.dest ld with
| None -> ""
| Some (link, _) -> pct_esc b link
in
let title =
match Link_definition.title ld with
| None -> ""
| Some title ->
let title = List.map Block_line.tight_to_string title in
html_esc b (String.concat "\n" title)
in
let alt =
let ls =
Inline.to_plain_text ~break_on_soft:false (Inline.Link.text i)
in
html_esc b (String.concat "\n" (List.map (String.concat "") ls))
in
let img =
String.concat ""
[
{|<img src="|};
link;
{|" alt="|};
alt;
{|" title="|};
title;
{|" >"|};
]
in
(Loc.at loc (`Raw_markup (Some "html", img)) :: is, warns)
let text_to_inline_elements ~locator s meta ((is, warns) as acc) =
(* [s] is on a single source line (but may have newlines because of
Expand Down Expand Up @@ -266,26 +274,26 @@ let rec link_reference_to_inline_element ~locator defs l m (is, warns) =
let ld = link_definition defs l in
match ld with
| None ->
let text, warns =
inline_to_inline_elements ~locator defs ([], warns) (Inline.Link.text l)
in
(text @ is, warns)
let text, warns =
inline_to_inline_elements ~locator defs ([], warns) (Inline.Link.text l)
in
(text @ is, warns)
| Some ld ->
let link =
match Link_definition.dest ld with None -> "" | Some (l, _) -> l
in
let warns =
match Link_definition.title ld with
| None -> warns
| Some title ->
let textloc = Block_line.tight_list_textloc title in
let loc = textloc_to_loc ~locator textloc in
warn ~loc warn_unsupported_link_title warns
in
let text, warns =
inline_to_inline_elements ~locator defs ([], warns) (Inline.Link.text l)
in
(Loc.at loc (`Link (link, text)) :: is, warns)
let link =
match Link_definition.dest ld with None -> "" | Some (l, _) -> l
in
let warns =
match Link_definition.title ld with
| None -> warns
| Some title ->
let textloc = Block_line.tight_list_textloc title in
let loc = textloc_to_loc ~locator textloc in
warn ~loc warn_unsupported_link_title warns
in
let text, warns =
inline_to_inline_elements ~locator defs ([], warns) (Inline.Link.text l)
in
(Loc.at loc (`Link (link, text)) :: is, warns)
and link_to_inline_element ~locator defs l m acc =
link_reference_to_inline_element ~locator defs l m acc
Expand Down
6 changes: 3 additions & 3 deletions src/markdown/odoc_md.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,10 +57,10 @@ let run input_s parent_id_opt odoc_dir =
let page = mk_page input_s id content in

let output =
let fname = "page-" ^ page_name ^ ".odoc" in
match parent_id_opt with
| None -> Fpath.(v odoc_dir / ("page-" ^ page_name ^ ".odoc"))
| Some parent_id_str ->
Fpath.(v odoc_dir // v parent_id_str / ("page-" ^ page_name ^ ".odoc"))
| None -> Fpath.(v odoc_dir / fname)
| Some parent_id_str -> Fpath.(v odoc_dir // v parent_id_str / fname)
in
Odoc_odoc.Odoc_file.save_page output ~warnings page

Expand Down

0 comments on commit 84023d6

Please sign in to comment.