Skip to content

Commit b7a7d67

Browse files
Remove tyxml from odoc_html_frontend (#1072)
* Remove tyxml from odoc_html_frontend Also include a bugfix : name with no prefix are not displayed with a `.` in front. Co-authored-by: Emile Trotignon <[email protected]> Co-authored-by: panglesd <[email protected]>
1 parent dd4bf1c commit b7a7d67

File tree

6 files changed

+128
-44
lines changed

6 files changed

+128
-44
lines changed

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,13 +14,19 @@
1414
- Updated colors for code fragments (@EmileTrotignon, #1023)
1515
- Fixed complexity of looking up `.odoc` files (@panglesd, #1075)
1616

17+
### Changed
18+
19+
- `Odoc_html_frontend` does not use tyxml, for smaller javascript sizes.
20+
(@EmileTrotignon, #1072)
21+
1722
# Fixed
1823

1924
- Revert to outputing a file (without content) when rendering a hidden
2025
compilation unit. This fixes cases where the dune rules would
2126
fail. (@panglesd, #1069)
2227
- Fix issue #1066 with extended opens (@jonludlam, #1082)
2328

29+
2430
# 2.4.0
2531

2632
### Added

src/search/html.ml

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -159,7 +159,12 @@ let string_of_kind =
159159

160160
let value_rhs (t : Entry.value_entry) = " : " ^ Text.of_type t.type_
161161

162-
let of_strings = Odoc_html_frontend.of_strings
162+
let of_strings ~kind ~prefix_name ~name ~rhs ~typedecl_params ~doc =
163+
[
164+
Tyxml.Html.Unsafe.data
165+
(Odoc_html_frontend.of_strings ~kind ~prefix_name ~name ~rhs
166+
~typedecl_params ~doc);
167+
]
163168
let rhs_of_kind (entry : Entry.kind) =
164169
match entry with
165170
| TypeDecl td -> typedecl_rhs td
@@ -175,7 +180,9 @@ let names_of_id id =
175180
let fullname = Paths.Identifier.fullname id in
176181
let prefix_name, name =
177182
let rev_fullname = List.rev fullname in
178-
( rev_fullname |> List.tl |> List.rev |> String.concat ".",
183+
( rev_fullname |> List.tl |> List.rev
184+
|> List.map (fun str -> str ^ ".")
185+
|> String.concat "",
179186
List.hd rev_fullname )
180187
in
181188
(prefix_name, name)

src/search/html.mli

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -9,9 +9,9 @@ val url :
99
(string, Odoc_document.Url.Error.t) Result.result
1010

1111
(** The below is intended for search engine that do not use the Json output but
12-
Odoc as a library. Most search engine will use their own representation
13-
instead of {!Entry.t}, and may not want to store the whole HTML in their
14-
database. The following functions help give correct values to store in a
12+
Odoc as a library. Most search engine will use their own representation
13+
instead of {!Entry.t}, and may not want to store the whole HTML in their
14+
database. The following functions help give correct values to store in a
1515
search database. *)
1616

1717
val of_strings :
@@ -24,22 +24,22 @@ val of_strings :
2424
html list
2525

2626
val names_of_id : Paths.Identifier.t -> string * string
27-
(** [names_of_id id] is [("X.Y", "foo")] if [id] corresponds to [X.Y.foo].
28-
The tuple is intended to be given respectively to the [prefix_name] and
27+
(** [names_of_id id] is [("X.Y", "foo")] if [id] corresponds to [X.Y.foo].
28+
The tuple is intended to be given respectively to the [prefix_name] and
2929
[name] arguments of {!Odoc_html_frontend.of_strings}. *)
3030

3131
val of_doc : Comment.docs -> html
3232
(** [of_doc d] returns the HTML associated of the documentation comment [d],
3333
generated correctly for search (no links or anchors). *)
3434

3535
val html_string_of_doc : Comment.docs -> string
36-
(** [html_string_of_doc d] is the same as {!of_doc} converted to a
36+
(** [html_string_of_doc d] is the same as {!of_doc} converted to a
3737
string. *)
3838

3939
(** Right-hand sides *)
4040

4141
val rhs_of_kind : Entry.kind -> string option
42-
(** [rhs_of_kind k] is the right-hand-side string associated with the metadata
42+
(** [rhs_of_kind k] is the right-hand-side string associated with the metadata
4343
included in the kind [k]. If [k] is [Value _], it may be [": int"] *)
4444

4545
val typedecl_params_of_entry : Entry.t -> string option

src/search/odoc_html_frontend.ml

Lines changed: 92 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,85 @@
1+
module Html : sig
2+
type t
3+
4+
val string_of_list : t list -> string
5+
6+
type attr
7+
8+
val a_class : string list -> attr
9+
val code : a:attr list -> t list -> t
10+
val span : a:attr list -> t list -> t
11+
val div : a:attr list -> t list -> t
12+
val txt : string -> t
13+
14+
module Unsafe : sig
15+
val data : string -> t
16+
end
17+
end = struct
18+
type t = Raw of string | Txt of string | Concat of t list
19+
20+
let add_escape_string buf s =
21+
(* https://discuss.ocaml.org/t/html-encoding-of-string/4289/4 *)
22+
let add = Buffer.add_string buf in
23+
let len = String.length s in
24+
let max_idx = len - 1 in
25+
let flush start i =
26+
if start < len then Buffer.add_substring buf s start (i - start)
27+
in
28+
let rec loop start i =
29+
if i > max_idx then flush start i
30+
else
31+
match String.get s i with
32+
| '&' -> escape "&amp;" start i
33+
| '<' -> escape "&lt;" start i
34+
| '>' -> escape "&gt;" start i
35+
| '\'' -> escape "&apos;" start i
36+
| '"' -> escape "&quot;" start i
37+
| '@' -> escape "&commat;" start i
38+
| _ -> loop start (i + 1)
39+
and escape amperstr start i =
40+
flush start i;
41+
add amperstr;
42+
let next = i + 1 in
43+
loop next next
44+
in
45+
loop 0 0
46+
47+
let to_string t =
48+
let buf = Buffer.create 16 in
49+
let rec go = function
50+
| Raw s -> Buffer.add_string buf s
51+
| Txt s -> add_escape_string buf s
52+
| Concat xs -> List.iter go xs
53+
in
54+
go t;
55+
Buffer.contents buf
56+
57+
let string_of_list lst = to_string (Concat lst)
58+
59+
type attr = t
60+
61+
let a_class lst =
62+
Concat [ Raw "class=\""; Txt (String.concat " " lst); Raw "\"" ]
63+
64+
let attrs = function [] -> Concat [] | xs -> Concat (Raw " " :: xs)
65+
66+
let block name ~a body =
67+
let name = Raw name in
68+
Concat
69+
[ Raw "<"; name; attrs a; Raw ">"; Concat body; Raw "</"; name; Raw ">" ]
70+
71+
let code = block "code"
72+
let span = block "span"
73+
let div = block "div"
74+
let txt s = Txt s
75+
76+
module Unsafe = struct
77+
let data s = Raw s
78+
end
79+
end
80+
181
let of_strings ~kind ~prefix_name ~name ~rhs ~typedecl_params ~doc =
2-
let open Tyxml.Html in
82+
let open Html in
383
let kind = code ~a:[ a_class [ "entry-kind" ] ] [ txt kind ]
484
and typedecl_params =
585
match typedecl_params with
@@ -19,9 +99,10 @@ let of_strings ~kind ~prefix_name ~name ~rhs ~typedecl_params ~doc =
1999
]
20100
and prefix_name =
21101
match prefix_name with
22-
| Some prefix_name ->
23-
[ span ~a:[ a_class [ "prefix-name" ] ] [ txt (prefix_name ^ ".") ] ]
24102
| None -> []
103+
| Some "" -> []
104+
| Some prefix_name ->
105+
[ span ~a:[ a_class [ "prefix-name" ] ] [ txt prefix_name ] ]
25106
and name =
26107
match name with
27108
| Some name -> [ span ~a:[ a_class [ "entry-name" ] ] [ txt name ] ]
@@ -31,35 +112,25 @@ let of_strings ~kind ~prefix_name ~name ~rhs ~typedecl_params ~doc =
31112
| None -> []
32113
| Some rhs -> [ code ~a:[ a_class [ "entry-rhs" ] ] [ txt rhs ] ]
33114
in
34-
[
35-
kind;
36-
code
37-
~a:[ a_class [ "entry-title" ] ]
38-
(typedecl_params @ prefix_name @ name @ rhs);
39-
div ~a:[ a_class [ "entry-comment" ] ] [ Unsafe.data doc ];
40-
]
115+
Html.string_of_list
116+
[
117+
kind;
118+
code
119+
~a:[ a_class [ "entry-title" ] ]
120+
(typedecl_params @ prefix_name @ name @ rhs);
121+
div ~a:[ a_class [ "entry-comment" ] ] [ Unsafe.data doc ];
122+
]
41123

42124
let kind_doc = "doc"
43-
44125
let kind_typedecl = "type"
45-
46126
let kind_module = "mod"
47-
48127
let kind_exception = "exn"
49-
50128
let kind_class_type = "class"
51129
let kind_class = "class"
52-
53130
let kind_method = "meth"
54-
55131
let kind_extension_constructor = "cons"
56-
57132
let kind_module_type = "sig"
58-
59133
let kind_constructor = "cons"
60-
61134
let kind_field = "field"
62-
63135
let kind_value = "val"
64-
65136
let kind_extension = "ext"

src/search/odoc_html_frontend.mli

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
(** This library is intended for search engine that do not use the Json output
2-
but Odoc as a library. Most search engine will use their own representation
3-
instead of {!Entry.t}, and may not want to store the whole HTML in their
2+
but Odoc as a library. Most search engine will use their own representation
3+
instead of {!Entry.t}, and may not want to store the whole HTML in their
44
database.
5-
This library contains functions that are useful for the frontend of such
6-
search engines.
5+
This library contains functions that are useful for the frontend of such
6+
search engines.
77
These functions would have their place in Odoc_searc.html, but putting them
88
there means that you need to link to a lot of dependencies to use them, and
99
js-of-ocaml is unable to detect when these dependencies are unused. *)
@@ -15,8 +15,8 @@ val of_strings :
1515
rhs:string option ->
1616
typedecl_params:string option ->
1717
doc:string ->
18-
[> `Code | `Div ] Tyxml_html.elt list
19-
(** [of_string] generates the html of an entry using strings associated to
18+
string
19+
(** [of_string] generates the html of an entry using strings associated to
2020
the relevant parts of the entry. If the strings have the correct values,
2121
it will return the same HTML as {!Odoc_search.Html.of_entry}. Correct values
2222
are given by {!Odoc_search.Html}, and for kinds, bellow. *)

test/search/html_search.t/run.t

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -86,12 +86,12 @@ The index file, one entry per line:
8686
$ cat index.json | jq sort | jq '.[]' -c
8787
{"id":[{"kind":"Root","name":"Main"},{"kind":"Type","name":"tdzdz"},{"kind":"Constructor","name":"A"}],"doc":"","kind":{"kind":"Constructor","args":{"kind":"Tuple","vals":["int","int"]},"res":"tdzdz"},"display":{"url":"page/Main/index.html#type-tdzdz.A","html":"<code class=\"entry-kind\">cons</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.tdzdz.</span><span class=\"entry-name\">A</span><code class=\"entry-rhs\"> : int * int -&gt; tdzdz</code></code><div class=\"entry-comment\"><div></div></div>"}}
8888
{"id":[{"kind":"Root","name":"Main"},{"kind":"Type","name":"tdzdz"},{"kind":"Constructor","name":"B"}],"doc":"Bliiiiiiiiiii","kind":{"kind":"Constructor","args":{"kind":"Tuple","vals":["int list","int"]},"res":"tdzdz"},"display":{"url":"page/Main/index.html#type-tdzdz.B","html":"<code class=\"entry-kind\">cons</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.tdzdz.</span><span class=\"entry-name\">B</span><code class=\"entry-rhs\"> : int list * int -&gt; tdzdz</code></code><div class=\"entry-comment\"><div><p>Bliiiiiiiiiii</p></div></div>"}}
89-
{"id":[{"kind":"Root","name":"J"}],"doc":"a paragraph two","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/J/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">J</span></code><div class=\"entry-comment\"><div><p>a paragraph two</p></div></div>"}}
90-
{"id":[{"kind":"Page","name":"page"}],"doc":"A paragraph","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><p>A paragraph</p></div></div>"}}
91-
{"id":[{"kind":"Page","name":"page"}],"doc":"a list of things","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><p>a list <em>of</em> things</p></div></div>"}}
92-
{"id":[{"kind":"Page","name":"page"}],"doc":"bliblib","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><p>bliblib</p></div></div>"}}
93-
{"id":[{"kind":"Page","name":"page"}],"doc":"and code","kind":{"kind":"Doc","subkind":"CodeBlock"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><pre class=\"language-ocaml\"><code>and code</code></pre></div></div>"}}
94-
{"id":[{"kind":"Page","name":"page"}],"doc":"some verbatim","kind":{"kind":"Doc","subkind":"Verbatim"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><pre>some verbatim</pre></div></div>"}}
89+
{"id":[{"kind":"Root","name":"J"}],"doc":"a paragraph two","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/J/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"entry-name\">J</span></code><div class=\"entry-comment\"><div><p>a paragraph two</p></div></div>"}}
90+
{"id":[{"kind":"Page","name":"page"}],"doc":"A paragraph","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><p>A paragraph</p></div></div>"}}
91+
{"id":[{"kind":"Page","name":"page"}],"doc":"a list of things","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><p>a list <em>of</em> things</p></div></div>"}}
92+
{"id":[{"kind":"Page","name":"page"}],"doc":"bliblib","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><p>bliblib</p></div></div>"}}
93+
{"id":[{"kind":"Page","name":"page"}],"doc":"and code","kind":{"kind":"Doc","subkind":"CodeBlock"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><pre class=\"language-ocaml\"><code>and code</code></pre></div></div>"}}
94+
{"id":[{"kind":"Page","name":"page"}],"doc":"some verbatim","kind":{"kind":"Doc","subkind":"Verbatim"},"display":{"url":"page/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"entry-name\">page</span></code><div class=\"entry-comment\"><div><pre>some verbatim</pre></div></div>"}}
9595
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"I"}],"doc":"x + 1","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/Main/I/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">I</span></code><div class=\"entry-comment\"><div><p><code class=\"odoc-katex-math\">x + 1</code></p></div></div>"}}
9696
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"I"}],"doc":"x + 1","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/Main/I/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">I</span></code><div class=\"entry-comment\"><div><p><code class=\"odoc-katex-math\">x + 1</code></p></div></div>"}}
9797
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"I"}],"doc":"a paragraph two","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/Main/I/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">I</span></code><div class=\"entry-comment\"><div><p>a paragraph two</p></div></div>"}}
@@ -106,8 +106,8 @@ The index file, one entry per line:
106106
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"X"}],"doc":"and this is a paragraph","kind":{"kind":"Doc","subkind":"Paragraph"},"display":{"url":"page/Main/X/index.html","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">X</span></code><div class=\"entry-comment\"><div><p>and this is a paragraph</p></div></div>"}}
107107
{"id":[{"kind":"Root","name":"Main"},{"kind":"Label","name":"this-is-a-title"}],"doc":"this is a title","kind":{"kind":"Doc","subkind":"Heading"},"display":{"url":"page/Main/index.html#this-is-a-title","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">this-is-a-title</span></code><div class=\"entry-comment\"><div><p>this is a title</p></div></div>"}}
108108
{"id":[{"kind":"Page","name":"page"},{"kind":"Label","name":"a-title"}],"doc":"A title","kind":{"kind":"Doc","subkind":"Heading"},"display":{"url":"page/index.html#a-title","html":"<code class=\"entry-kind\">doc</code><code class=\"entry-title\"><span class=\"prefix-name\">page.</span><span class=\"entry-name\">a-title</span></code><div class=\"entry-comment\"><div><p>A title</p></div></div>"}}
109-
{"id":[{"kind":"Root","name":"J"}],"doc":"a paragraph one","kind":{"kind":"Module"},"display":{"url":"page/J/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">J</span></code><div class=\"entry-comment\"><div><p>a paragraph one</p></div></div>"}}
110-
{"id":[{"kind":"Root","name":"Main"}],"doc":"","kind":{"kind":"Module"},"display":{"url":"page/Main/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"prefix-name\">.</span><span class=\"entry-name\">Main</span></code><div class=\"entry-comment\"><div></div></div>"}}
109+
{"id":[{"kind":"Root","name":"J"}],"doc":"a paragraph one","kind":{"kind":"Module"},"display":{"url":"page/J/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"entry-name\">J</span></code><div class=\"entry-comment\"><div><p>a paragraph one</p></div></div>"}}
110+
{"id":[{"kind":"Root","name":"Main"}],"doc":"","kind":{"kind":"Module"},"display":{"url":"page/Main/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"entry-name\">Main</span></code><div class=\"entry-comment\"><div></div></div>"}}
111111
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"I"}],"doc":"","kind":{"kind":"Module"},"display":{"url":"page/Main/I/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">I</span></code><div class=\"entry-comment\"><div></div></div>"}}
112112
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"M"}],"doc":"","kind":{"kind":"Module"},"display":{"url":"page/Main/M/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">M</span></code><div class=\"entry-comment\"><div></div></div>"}}
113113
{"id":[{"kind":"Root","name":"Main"},{"kind":"Module","name":"X"}],"doc":"","kind":{"kind":"Module"},"display":{"url":"page/Main/X/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"prefix-name\">Main.</span><span class=\"entry-name\">X</span></code><div class=\"entry-comment\"><div></div></div>"}}

0 commit comments

Comments
 (0)