Skip to content

Commit

Permalink
Add the ability to remap identifiers during HTML generation
Browse files Browse the repository at this point in the history
This is to allow the publishing of 'partial docsets' - the idea being
that the driver proceeds as usual up until HTML generation, and at that
point only generates HTML pages for the packages you wish to publish on
your site, and remap links to other packages to ocaml.org or other site.
  • Loading branch information
jonludlam committed Aug 21, 2024
1 parent a28b179 commit 1583374
Show file tree
Hide file tree
Showing 13 changed files with 137 additions and 63 deletions.
6 changes: 5 additions & 1 deletion src/html/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ type t = {
theme_uri : Types.uri option;
support_uri : Types.uri option;
search_uris : Types.file_uri list;
remap : (string * string) list;
semantic_uris : bool;
search_result : bool;
(* Used to not render links, for summary in search results *)
Expand All @@ -14,7 +15,7 @@ type t = {
}

let v ?(search_result = false) ?theme_uri ?support_uri ?(search_uris = [])
~semantic_uris ~indent ~flat ~open_details ~as_json () =
~semantic_uris ~indent ~flat ~open_details ~as_json ~remap () =
{
semantic_uris;
indent;
Expand All @@ -25,6 +26,7 @@ let v ?(search_result = false) ?theme_uri ?support_uri ?(search_uris = [])
search_uris;
as_json;
search_result;
remap;
}

let theme_uri config : Types.uri =
Expand All @@ -46,3 +48,5 @@ let open_details config = config.open_details
let as_json config = config.as_json

let search_result config = config.search_result

let remap config = config.remap
3 changes: 3 additions & 0 deletions src/html/config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ val v :
flat:bool ->
open_details:bool ->
as_json:bool ->
remap:(string * string) list ->
unit ->
t
(** [search_result] indicates whether this is a summary for a search result. In
Expand All @@ -34,3 +35,5 @@ val open_details : t -> bool
val as_json : t -> bool

val search_result : t -> bool

val remap : t -> (string * string) list
2 changes: 1 addition & 1 deletion src/html/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -537,7 +537,7 @@ module Page = struct
else Html_page.make_src ~breadcrumbs ~header ~config ~url title [ doc ]

let asset ~config { Asset.url; src } =
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
let filename = Link.Path.as_filename ~config url in
let content ppf =
let ic = open_in_bin (Fpath.to_string src) in
let len = 1024 in
Expand Down
4 changes: 2 additions & 2 deletions src/html/html_fragment_json.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ let json_of_toc (toc : Types.toc list) : Utils.Json.json =

let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
~source_anchor content children =
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
let filename = Link.Path.as_filename ~config url in
let filename = Fpath.add_ext ".json" filename in
let json_to_string json = Utils.Json.to_string json in
let source_anchor =
Expand Down Expand Up @@ -65,7 +65,7 @@ let make ~config ~preamble ~url ~breadcrumbs ~sidebar ~toc ~uses_katex
{ Odoc_document.Renderer.filename; content; children }

let make_src ~config ~url ~breadcrumbs content =
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
let filename = Link.Path.as_filename ~config url in
let filename = Fpath.add_ext ".json" filename in
let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in
let json_to_string json = Utils.Json.to_string json in
Expand Down
4 changes: 2 additions & 2 deletions src/html/html_page.ml
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ let search_urls = %s;

let make ~config ~url ~header ~breadcrumbs ~sidebar ~toc ~uses_katex content
children =
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
let filename = Link.Path.as_filename ~config url in
let content =
page_creator ~config ~url ~uses_katex ~global_toc:sidebar header breadcrumbs
toc content
Expand Down Expand Up @@ -285,7 +285,7 @@ let src_page_creator ~breadcrumbs ~config ~url ~header name content =
content

let make_src ~config ~url ~breadcrumbs ~header title content =
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
let filename = Link.Path.as_filename ~config url in
let content =
src_page_creator ~breadcrumbs ~config ~url ~header title content
in
Expand Down
123 changes: 75 additions & 48 deletions src/html/link.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
module Url = Odoc_document.Url

type link = Relative of string list * string | Absolute of string

(* Translation from Url.Path *)
module Path = struct
let for_printing url = List.map snd @@ Url.Path.to_list url
Expand All @@ -11,10 +13,23 @@ module Path = struct

let is_leaf_page url = url.Url.Path.kind = `LeafPage

let get_dir_and_file is_flat url =
let remap config f =
let l = String.concat "/" f in
match
List.find_opt
(fun (prefix, _replacement) -> Astring.String.is_prefix ~affix:prefix l)
(Config.remap config)
with
| None -> None
| Some (prefix, replacement) ->
let len = String.length prefix in
let l = String.sub l len (String.length l - len) in
Some (replacement ^ l)

let get_dir_and_file ~config url =
let l = Url.Path.to_list url in
let is_dir =
if is_flat then function `Page -> `Always | _ -> `Never
if Config.flat config then function `Page -> `Always | _ -> `Never
else function `LeafPage | `File | `SourcePage -> `Never | _ -> `Always
in
let dir, file = Url.Path.split ~is_dir l in
Expand All @@ -26,17 +41,20 @@ module Path = struct
| [ (`File, name) ] -> name
| [ (`SourcePage, name) ] -> name ^ ".html"
| xs ->
assert is_flat;
assert (Config.flat config);
String.concat "-" (List.map segment_to_string xs) ^ ".html"
in
(dir, file)

let for_linking ~is_flat url =
let dir, file = get_dir_and_file is_flat url in
dir @ [ file ]
let for_linking ~config url =
let dir, file = get_dir_and_file ~config url in
match remap config dir with
| None -> Relative (dir, file)
| Some x -> Absolute (x ^ "/" ^ file)

let as_filename ~is_flat (url : Url.Path.t) =
Fpath.(v @@ String.concat Fpath.dir_sep @@ for_linking ~is_flat url)
let as_filename ~config (url : Url.Path.t) =
let dir, file = get_dir_and_file ~config url in
Fpath.(v @@ String.concat Fpath.dir_sep (dir @ [ file ]))
end

type resolve = Current of Url.Path.t | Base of string
Expand All @@ -48,46 +66,55 @@ let rec drop_shared_prefix l1 l2 =

let href ~config ~resolve t =
let { Url.Anchor.page; anchor; _ } = t in
let add_anchor y = match anchor with "" -> y | anchor -> y ^ "#" ^ anchor in
let target_loc = Path.for_linking ~config page in

let target_loc = Path.for_linking ~is_flat:(Config.flat config) page in

(* If xref_base_uri is defined, do not perform relative URI resolution. *)
match resolve with
| Base xref_base_uri -> (
let page = xref_base_uri ^ String.concat "/" target_loc in
match anchor with "" -> page | anchor -> page ^ "#" ^ anchor)
| Current path -> (
let current_loc = Path.for_linking ~is_flat:(Config.flat config) path in
match target_loc with
| Absolute y -> add_anchor y
| Relative (dir, file) -> (
let target_loc = dir @ [ file ] in
(* If xref_base_uri is defined, do not perform relative URI resolution. *)
match resolve with
| Base xref_base_uri ->
let page = xref_base_uri ^ String.concat "/" target_loc in
add_anchor page
| Current path -> (
let current_loc =
let dir, file = Path.get_dir_and_file ~config path in
dir @ [ file ]
in

let current_from_common_ancestor, target_from_common_ancestor =
drop_shared_prefix current_loc target_loc
in
let current_from_common_ancestor, target_from_common_ancestor =
drop_shared_prefix current_loc target_loc
in

let relative_target =
match current_from_common_ancestor with
| [] ->
(* We're already on the right page *)
(* If we're already on the right page, the target from our common
ancestor can't be anything other than the empty list *)
assert (target_from_common_ancestor = []);
[]
| [ _ ] ->
(* We're already in the right dir *)
target_from_common_ancestor
| l ->
(* We need to go up some dirs *)
List.map (fun _ -> "..") (List.tl l) @ target_from_common_ancestor
in
let remove_index_html l =
match List.rev l with
| "index.html" :: rest -> List.rev ("" :: rest)
| _ -> l
in
let relative_target =
if Config.semantic_uris config then remove_index_html relative_target
else relative_target
in
match (relative_target, anchor) with
| [], "" -> "#"
| page, "" -> String.concat "/" page
| page, anchor -> String.concat "/" page ^ "#" ^ anchor)
let relative_target =
match current_from_common_ancestor with
| [] ->
(* We're already on the right page *)
(* If we're already on the right page, the target from our common
ancestor can't be anything other than the empty list *)
assert (target_from_common_ancestor = []);
[]
| [ _ ] ->
(* We're already in the right dir *)
target_from_common_ancestor
| l ->
(* We need to go up some dirs *)
List.map (fun _ -> "..") (List.tl l)
@ target_from_common_ancestor
in
let remove_index_html l =
match List.rev l with
| "index.html" :: rest -> List.rev ("" :: rest)
| _ -> l
in
let relative_target =
if Config.semantic_uris config then
remove_index_html relative_target
else relative_target
in
match (relative_target, anchor) with
| [], "" -> "#"
| page, "" -> String.concat "/" page
| page, anchor -> String.concat "/" page ^ "#" ^ anchor))
4 changes: 1 addition & 3 deletions src/html/link.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,5 @@ module Path : sig

val for_printing : Url.Path.t -> string list

val for_linking : is_flat:bool -> Url.Path.t -> string list

val as_filename : is_flat:bool -> Url.Path.t -> Fpath.t
val as_filename : config:Config.t -> Url.Path.t -> Fpath.t
end
18 changes: 15 additions & 3 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1204,19 +1204,31 @@ module Odoc_html_args = struct
Arg.(
value & opt_all convert_fpath [] & info [ "asset" ] ~doc ~docv:"file.ext")

let remap =
let convert_remap =
let parse inp =
match Astring.String.cut ~sep:":" inp with
| Some (orig, mapped) -> Ok (orig, mapped)
| _ -> Error (`Msg "Map must be of the form '<orig>:https://...'")
and print fmt (orig, mapped) = Format.fprintf fmt "%s:%s" orig mapped in
Arg.conv (parse, print)
in
let doc = "Remap an identifier to an external URL." in
Arg.(value & opt_all convert_remap [] & info [ "R" ] ~doc)

let extra_args =
let config semantic_uris closed_details indent theme_uri support_uri
search_uris flat as_json assets =
search_uris flat as_json assets remap =
let open_details = not closed_details in
let html_config =
Odoc_html.Config.v ~theme_uri ~support_uri ~search_uris ~semantic_uris
~indent ~flat ~open_details ~as_json ()
~indent ~flat ~open_details ~as_json ~remap ()
in
{ Html_page.html_config; assets }
in
Term.(
const config $ semantic_uris $ closed_details $ indent $ theme_uri
$ support_uri $ search_uri $ flat $ as_json $ assets)
$ support_uri $ search_uri $ flat $ as_json $ assets $ remap)
end

module Odoc_html = Make_renderer (Odoc_html_args)
Expand Down
2 changes: 1 addition & 1 deletion src/odoc/html_fragment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input =
let page = Odoc_document.Comment.to_ir resolved.content in
let config =
Odoc_html.Config.v ~semantic_uris:false ~indent:false ~flat:false
~open_details:false ~as_json:false ()
~open_details:false ~as_json:false ~remap:[] ()
in
let html = Odoc_html.Generator.doc ~config ~xref_base_uri page in
let oc = open_out (Fs.File.to_string output) in
Expand Down
5 changes: 3 additions & 2 deletions src/search/html.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ let url { Entry.id; kind; doc = _ } =
| Ok url ->
let config =
Odoc_html.Config.v ~search_result:true ~semantic_uris:false
~indent:false ~flat:false ~open_details:false ~as_json:false ()
~indent:false ~flat:false ~open_details:false ~as_json:false ~remap:[]
()
in
let url = Odoc_html.Link.href ~config ~resolve:(Base "") url in
Result.Ok url
Expand Down Expand Up @@ -201,7 +202,7 @@ let names_of_id id =
let of_doc doc =
let config =
Odoc_html.Config.v ~search_result:true ~semantic_uris:false ~indent:false
~flat:false ~open_details:false ~as_json:false ()
~flat:false ~open_details:false ~as_json:false ~remap:[] ()
in
Tyxml.Html.div ~a:[]
@@ Odoc_html.Generator.doc ~config ~xref_base_uri:""
Expand Down
2 changes: 2 additions & 0 deletions test/integration/remap.t/otherlib.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
type t = Foo | Bar

25 changes: 25 additions & 0 deletions test/integration/remap.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
$ ocamlc -c -bin-annot otherlib.mli
$ ocamlc -c -bin-annot test.mli
$ odoc compile --parent-id prefix/otherpkg/doc --output-dir _odoc otherlib.cmti
$ odoc compile --parent-id prefix/mypkg/doc --output-dir _odoc test.cmti
$ odoc link _odoc/prefix/otherpkg/doc/otherlib.odoc
$ odoc link -I _odoc/prefix/otherpkg/doc _odoc/prefix/mypkg/doc/test.odoc

We should be able to remap the links to one of the packages:

$ odoc html-generate -o _html --indent _odoc/prefix/mypkg/doc/test.odocl
$ odoc html-generate -o _html2 --indent _odoc/prefix/mypkg/doc/test.odocl -R prefix/otherpkg/:https://mysite.org/p/otherpkg/1.2.3/

$ diff _html/prefix/mypkg/doc/Test/index.html _html2/prefix/mypkg/doc/Test/index.html
25c25,27
< <a href="../../../otherpkg/doc/Otherlib/index.html#type-t">Otherlib.t
---
> <a
> href="https://mysite.org/p/otherpkg/1.2.3/doc/Otherlib/index.html#type-t"
> >Otherlib.t
[1]

This shouldn't stop us from outputting the remapped package though, and the following should complete without error

$ odoc html-generate -o _html3 _odoc/prefix/otherpkg/doc/otherlib.odocl -R prefix/otherpkg/:https://mysite.org/p/otherpkg/1.2.3/

2 changes: 2 additions & 0 deletions test/integration/remap.t/test.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
type t = Otherlib.t

0 comments on commit 1583374

Please sign in to comment.