Skip to content

Commit a52dd8e

Browse files
gilthojonludlam
authored andcommitted
Handle Math_span and Math_block constructs
1 parent 0e62e03 commit a52dd8e

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

47 files changed

+261
-17
lines changed

.gitignore

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,3 +33,6 @@ ocaml-re/
3333
result/
3434
tyxml/
3535
uutf/
36+
37+
# Mac things
38+
.DS_Store

.ocamlformat

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,2 @@
11
module-item-spacing=preserve
2-
version=0.21.0
2+
version=0.24.1

odoc.opam

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ delimited with `(** ... *)`, and outputs HTML.
2525
"""
2626

2727
depends: [
28-
"odoc-parser" {>= "1.0.0"}
28+
"odoc-parser" {>= "2.0.0"}
2929
"astring"
3030
"cmdliner" {>= "1.0.0"}
3131
"cppo" {build & >= "1.1.0"}

src/document/comment.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,7 @@ let leaf_inline_element : Comment.leaf_inline_element -> Inline.one = function
129129
| `Space -> inline @@ Text " "
130130
| `Word s -> inline @@ Text s
131131
| `Code_span s -> inline @@ Source (source_of_code s)
132+
| `Math_span s -> inline @@ Math s
132133
| `Raw_markup (target, s) -> inline @@ Raw_markup (target, s)
133134

134135
let rec non_link_inline_element : Comment.non_link_inline_element -> Inline.one
@@ -202,6 +203,7 @@ let rec nestable_block_element : Comment.nestable_block_element -> Block.one =
202203
in
203204
block
204205
@@ Source (lang_tag, source_of_code (Odoc_model.Location_.value code))
206+
| `Math_block s -> block @@ Math s
205207
| `Verbatim s -> block @@ Verbatim s
206208
| `Modules ms -> module_references ms
207209
| `List (kind, items) ->

src/document/doctree.ml

Lines changed: 74 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -282,3 +282,77 @@ end = struct
282282
labels page
283283
|> snd
284284
end
285+
286+
module Math : sig
287+
val has_math_elements : Page.t -> bool
288+
end = struct
289+
let rec items x = List.exists item x
290+
291+
and item : Item.t -> bool = function
292+
| Text x -> block x
293+
| Heading x -> heading x
294+
| Declaration { content = x; doc; _ } -> documentedsrc x || block doc
295+
| Include { content = x; doc; _ } -> include_ x || block doc
296+
297+
and documentedsrc : DocumentedSrc.t -> bool =
298+
fun x ->
299+
let documentedsrc_ : DocumentedSrc.one -> bool = function
300+
| Code _ -> false
301+
| Documented { code = x; doc; _ } -> inline x || block doc
302+
| Nested { code = x; doc; _ } -> documentedsrc x || block doc
303+
| Subpage x -> subpage x
304+
| Alternative x -> alternative x
305+
in
306+
List.exists documentedsrc_ x
307+
308+
and subpage : Subpage.t -> bool = fun x -> page x.content
309+
310+
and page : Page.t -> bool = fun x -> items x.items
311+
312+
and alternative : Alternative.t -> bool = function
313+
| Expansion x -> documentedsrc x.expansion
314+
315+
and include_ : Include.t -> bool = fun x -> items x.content
316+
317+
and block : Block.t -> bool =
318+
fun x ->
319+
let block_ : Block.one -> bool =
320+
fun x ->
321+
match x.desc with
322+
| Inline x -> inline x
323+
| Paragraph x -> inline x
324+
| List (_, x) -> List.exists block x
325+
| Description x -> description x
326+
| Math _ -> true
327+
| Source _ | Verbatim _ | Raw_markup _ -> false
328+
in
329+
List.exists block_ x
330+
331+
and heading : Heading.t -> bool = fun x -> inline x.title
332+
333+
and inline : Inline.t -> bool =
334+
fun x ->
335+
let inline_ : Inline.one -> bool =
336+
fun x ->
337+
match x.desc with
338+
| Styled (_, x) -> inline x
339+
| Link (_, x) -> inline x
340+
| InternalLink x -> internallink x
341+
| Math _ -> true
342+
| Text _ | Entity _ | Linebreak | Source _ | Raw_markup _ -> false
343+
in
344+
List.exists inline_ x
345+
346+
and internallink : InternalLink.t -> bool = function
347+
| Resolved (_, x) -> inline x
348+
| Unresolved x -> inline x
349+
350+
and description : Description.t -> bool =
351+
fun x ->
352+
let description_ : Description.one -> bool =
353+
fun x -> inline x.key || block x.definition
354+
in
355+
List.exists description_ x
356+
357+
let has_math_elements = page
358+
end

src/document/types.ml

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,11 @@ and Source : sig
3030
end =
3131
Source
3232

33+
and Math : sig
34+
type t = string
35+
end =
36+
Math
37+
3338
and Inline : sig
3439
type entity = string
3540

@@ -47,6 +52,7 @@ and Inline : sig
4752
| Link of href * t
4853
| InternalLink of InternalLink.t
4954
| Source of Source.t
55+
| Math of Math.t
5056
| Raw_markup of Raw_markup.t
5157
end =
5258
Inline
@@ -76,6 +82,7 @@ and Block : sig
7682
| List of list_type * t list
7783
| Description of Description.t
7884
| Source of lang_tag * Source.t
85+
| Math of Math.t
7986
| Verbatim of string
8087
| Raw_markup of Raw_markup.t
8188

src/document/utils.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ and compute_length_inline (t : Types.Inline.t) : int =
3939
| InternalLink (Unresolved t) ->
4040
acc + compute_length_inline t
4141
| Source s -> acc + compute_length_source s
42+
| Math _ -> assert false
4243
| Raw_markup _ -> assert false
4344
(* TODO *)
4445
in

src/html/generator.ml

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,12 @@ let mk_anchor anchor =
4242

4343
let class_ (l : Class.t) = if l = [] then [] else [ Html.a_class l ]
4444

45+
let inline_math (s : Math.t) =
46+
Html.code ~a:[ Html.a_class [ "odoc-katex-math" ] ] [ Html.txt s ]
47+
48+
let block_math (s : Math.t) =
49+
Html.pre ~a:[ Html.a_class [ "odoc-katex-math"; "display" ] ] [ Html.txt s ]
50+
4551
and raw_markup (t : Raw_markup.t) =
4652
let target, content = t in
4753
match Astring.String.Ascii.lowercase target with
@@ -121,6 +127,7 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) :
121127
[ Html.a ~a:(Html.a_href href :: a) content ]
122128
| InternalLink c -> internallink ~config ~emph_level ~resolve ~a c
123129
| Source c -> source (inline ~config ~emph_level ~resolve) ~a c
130+
| Math s -> [ inline_math s ]
124131
| Raw_markup r -> raw_markup r
125132
in
126133
Utils.list_concat_map ~f:one l
@@ -142,6 +149,7 @@ and inline_nolink ?(emph_level = 0) (l : Inline.t) :
142149
| Link (_, c) -> inline_nolink ~emph_level c
143150
| InternalLink c -> internallink_nolink ~emph_level ~a c
144151
| Source c -> source (inline_nolink ~emph_level) ~a c
152+
| Math s -> [ inline_math s ]
145153
| Raw_markup r -> raw_markup r
146154
in
147155
Utils.list_concat_map ~f:one l
@@ -196,6 +204,7 @@ let rec block ~config ~resolve (l : Block.t) : flow Html.elt list =
196204
| Source (lang_tag, c) ->
197205
let extra_class = [ "language-" ^ lang_tag ] in
198206
mk_block ~extra_class Html.pre (source (inline ~config ~resolve) c)
207+
| Math s -> mk_block Html.div [ block_math s ]
199208
in
200209
Utils.list_concat_map l ~f:one
201210

@@ -389,10 +398,11 @@ module Page = struct
389398
in
390399
let resolve = Link.Current url in
391400
let i = Doctree.Shift.compute ~on_sub i in
401+
let uses_katex = Doctree.Math.has_math_elements p in
392402
let toc = Toc.gen_toc ~config ~resolve ~path:url i in
393403
let header = items ~config ~resolve header in
394404
let content = (items ~config ~resolve i :> any Html.elt list) in
395-
Tree.make ~config ~header ~toc ~url title content subpages
405+
Tree.make ~config ~header ~toc ~url ~uses_katex title content subpages
396406
end
397407

398408
let render ~config page = Page.page ~config page

src/html/tree.ml

Lines changed: 35 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ let html_of_toc toc =
3030
| [] -> []
3131
| _ -> [ Html.nav ~a:[ Html.a_class [ "odoc-toc" ] ] [ sections toc ] ]
3232

33-
let page_creator ~config ~url name header toc content =
33+
let page_creator ~config ~url ~uses_katex name header toc content =
3434
let theme_uri = Config.theme_uri config in
3535
let support_uri = Config.support_uri config in
3636
let path = Link.Path.for_printing url in
@@ -51,9 +51,7 @@ let page_creator ~config ~url name header toc content =
5151

5252
let odoc_css_uri = file_uri theme_uri "odoc.css" in
5353
let highlight_js_uri = file_uri support_uri "highlight.pack.js" in
54-
55-
Html.head
56-
(Html.title (Html.txt title_string))
54+
let default_meta_elements =
5755
[
5856
Html.link ~rel:[ `Stylesheet ] ~href:odoc_css_uri ();
5957
Html.meta ~a:[ Html.a_charset "utf-8" ] ();
@@ -70,6 +68,35 @@ let page_creator ~config ~url name header toc content =
7068
Html.script ~a:[ Html.a_src highlight_js_uri ] (Html.txt "");
7169
Html.script (Html.txt "hljs.initHighlightingOnLoad();");
7270
]
71+
in
72+
let meta_elements =
73+
if uses_katex then
74+
let katex_css_uri = file_uri theme_uri "katex.min.css" in
75+
let katex_js_uri = file_uri support_uri "katex.min.js" in
76+
default_meta_elements
77+
@ [
78+
Html.link ~rel:[ `Stylesheet ] ~href:katex_css_uri ();
79+
Html.script ~a:[ Html.a_src katex_js_uri ] (Html.txt "");
80+
Html.script
81+
(Html.cdata_script
82+
{|
83+
document.addEventListener("DOMContentLoaded", function () {
84+
var elements = Array.from(document.getElementsByClassName("odoc-katex-math"));
85+
for (var i = 0; i < elements.length; i++) {
86+
var el = elements[i];
87+
var content = el.textContent;
88+
var new_el = document.createElement("span");
89+
new_el.setAttribute("class", "odoc-katex-math-rendered");
90+
var display = el.classList.contains("display");
91+
katex.render(content, new_el, { throwOnError: false, displayMode: display });
92+
el.replaceWith(new_el);
93+
}
94+
});
95+
|});
96+
]
97+
else default_meta_elements
98+
in
99+
Html.head (Html.title (Html.txt title_string)) meta_elements
73100
in
74101

75102
let gen_breadcrumbs () =
@@ -152,7 +179,9 @@ let page_creator ~config ~url name header toc content =
152179
let content ppf = htmlpp ppf html in
153180
content
154181

155-
let make ~config ~url ~header ~toc title content children =
182+
let make ~config ~url ~header ~toc ~uses_katex title content children =
156183
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
157-
let content = page_creator ~config ~url title header toc content in
184+
let content =
185+
page_creator ~config ~url ~uses_katex title header toc content
186+
in
158187
[ { Odoc_document.Renderer.filename; content; children } ]

src/html/tree.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ val make :
2525
url:Odoc_document.Url.Path.t ->
2626
header:Html_types.flow5_without_header_footer Html.elt list ->
2727
toc:Types.toc list ->
28+
uses_katex:bool ->
2829
string ->
2930
Html_types.div_content Html.elt list ->
3031
Odoc_document.Renderer.page list ->

0 commit comments

Comments
 (0)