Skip to content

Commit 0d211ce

Browse files
panglesdjonludlam
authored andcommitted
Search: Pass search scripts at html generation
Signed-off-by: Paul-Elliot <[email protected]>
1 parent a1aa23c commit 0d211ce

File tree

21 files changed

+252
-254
lines changed

21 files changed

+252
-254
lines changed

src/document/generator.ml

Lines changed: 3 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1777,14 +1777,6 @@ module Make (Syntax : SYNTAX) = struct
17771777

17781778
let compilation_unit (t : Odoc_model.Lang.Compilation_unit.t) =
17791779
let url = Url.Path.from_identifier t.id in
1780-
let search_assets =
1781-
Utils.filter_map
1782-
(function
1783-
| `Resolved (`Identifier id) ->
1784-
Some Url.(from_path @@ Path.from_identifier id)
1785-
| _ -> None)
1786-
t.search_assets
1787-
in
17881780
let unit_doc, items =
17891781
match t.content with
17901782
| Module sign -> signature sign
@@ -1796,7 +1788,7 @@ module Make (Syntax : SYNTAX) = struct
17961788
| None -> None
17971789
in
17981790
let page = make_expansion_page ~source_anchor url [ unit_doc ] items in
1799-
Document.Page (page, search_assets)
1791+
Document.Page page
18001792

18011793
let page (t : Odoc_model.Lang.Page.t) =
18021794
(*let name =
@@ -1806,15 +1798,7 @@ module Make (Syntax : SYNTAX) = struct
18061798
let url = Url.Path.from_identifier t.name in
18071799
let preamble, items = Sectioning.docs t.content in
18081800
let source_anchor = None in
1809-
let search_assets =
1810-
Utils.filter_map
1811-
(function
1812-
| `Resolved (`Identifier id) ->
1813-
Some (Url.from_path @@ Url.Path.from_identifier id)
1814-
| _ -> None)
1815-
t.search_assets
1816-
in
1817-
Document.Page ({ Page.preamble; items; url; source_anchor }, search_assets)
1801+
Document.Page { Page.preamble; items; url; source_anchor }
18181802

18191803
let source_tree t =
18201804
let dir_pages = t.Odoc_model.Lang.SourceTree.source_children in
@@ -1899,7 +1883,7 @@ module Make (Syntax : SYNTAX) = struct
18991883
:: [ text ~attr:[ "odoc-folder-list" ] @@ list list_of_children ]
19001884
in
19011885
Document.Page
1902-
({ Types.Page.preamble = []; items; url; source_anchor = None }, [])
1886+
{ Types.Page.preamble = []; items; url; source_anchor = None }
19031887
in
19041888
M.fold (fun dir children acc -> page_of_dir dir children :: acc) mmap []
19051889
end

src/document/types.ml

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -198,10 +198,7 @@ end =
198198
Asset
199199

200200
module Document = struct
201-
type t =
202-
| Page of Page.t * Url.t list
203-
| Source_page of Source_page.t
204-
| Asset of Asset.t
201+
type t = Page of Page.t | Source_page of Source_page.t | Asset of Asset.t
205202
end
206203

207204
let inline ?(attr = []) desc = Inline.{ attr; desc }

src/html/config.ml

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
type t = {
44
theme_uri : Types.uri option;
55
support_uri : Types.uri option;
6+
search_uris : Types.file_uri list;
67
semantic_uris : bool;
78
search_result : bool;
89
(* Used to not render links, for summary in search results *)
@@ -12,25 +13,28 @@ type t = {
1213
as_json : bool;
1314
}
1415

15-
let v ?(search_result = false) ?theme_uri ?support_uri ~semantic_uris ~indent
16-
~flat ~open_details ~as_json () =
16+
let v ?(search_result = false) ?theme_uri ?support_uri ?(search_uris = [])
17+
~semantic_uris ~indent ~flat ~open_details ~as_json () =
1718
{
1819
semantic_uris;
1920
indent;
2021
flat;
2122
open_details;
2223
theme_uri;
2324
support_uri;
25+
search_uris;
2426
as_json;
2527
search_result;
2628
}
2729

28-
let theme_uri config =
30+
let theme_uri config : Types.uri =
2931
match config.theme_uri with None -> Types.Relative None | Some uri -> uri
3032

31-
let support_uri config =
33+
let support_uri config : Types.uri =
3234
match config.support_uri with None -> Types.Relative None | Some uri -> uri
3335

36+
let search_uris config = config.search_uris
37+
3438
let semantic_uris config = config.semantic_uris
3539

3640
let indent config = config.indent

src/html/config.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ val v :
88
In that case, the links will be printed as regular text. *) ->
99
?theme_uri:Types.uri ->
1010
?support_uri:Types.uri ->
11+
?search_uris:Types.file_uri list ->
1112
semantic_uris:bool ->
1213
indent:bool ->
1314
flat:bool ->
@@ -20,6 +21,8 @@ val theme_uri : t -> Types.uri
2021

2122
val support_uri : t -> Types.uri
2223

24+
val search_uris : t -> Types.file_uri list
25+
2326
val semantic_uris : t -> bool
2427

2528
val indent : t -> bool

src/html/generator.ml

Lines changed: 7 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -482,26 +482,20 @@ module Page = struct
482482
| `Closed | `Open | `Default -> None
483483
| `Inline -> Some 0)
484484

485-
let rec include_ ~config search_assets { Subpage.content; _ } =
486-
page ~config search_assets content
485+
let rec include_ ~config { Subpage.content; _ } = page ~config content
487486

488-
and subpages ~config search_assets subpages =
489-
List.map (include_ ~config search_assets) subpages
487+
and subpages ~config subpages = List.map (include_ ~config) subpages
490488

491-
and page ~config (search_assets : Odoc_document.Url.t list) p :
492-
Odoc_document.Renderer.page =
489+
and page ~config p : Odoc_document.Renderer.page =
493490
let { Page.preamble; items = i; url; source_anchor } =
494491
Doctree.Labels.disambiguate_page ~enter_subpages:false p
495492
in
496-
let subpages =
497-
subpages ~config search_assets @@ Doctree.Subpages.compute p
498-
in
493+
let subpages = subpages ~config @@ Doctree.Subpages.compute p in
499494
let resolve = Link.Current url in
500495
let i = Doctree.Shift.compute ~on_sub i in
501496
let uses_katex = Doctree.Math.has_math_elements p in
502497
let toc = Toc.gen_toc ~config ~resolve ~path:url i in
503498
let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~url in
504-
let search_urls = List.map (Link.href ~config ~resolve) search_assets in
505499
let content = (items ~config ~resolve i :> any Html.elt list) in
506500
if Config.as_json config then
507501
let source_anchor =
@@ -517,8 +511,8 @@ module Page = struct
517511
items ~config ~resolve
518512
(Doctree.PageTitle.render_title ?source_anchor p @ preamble)
519513
in
520-
Html_page.make ~config ~header ~toc ~breadcrumbs ~url ~uses_katex
521-
~search_urls content subpages
514+
Html_page.make ~config ~header ~toc ~breadcrumbs ~url ~uses_katex content
515+
subpages
522516

523517
and source_page ~config sp =
524518
let { Source_page.url; contents } = sp in
@@ -555,8 +549,7 @@ module Page = struct
555549
end
556550

557551
let render ~config = function
558-
| Document.Page (page, search_assets) ->
559-
[ Page.page ~config search_assets page ]
552+
| Document.Page page -> [ Page.page ~config page ]
560553
| Source_page src -> [ Page.source_page ~config src ]
561554
| Asset asset -> [ Page.asset ~config asset ]
562555

src/html/html_page.ml

Lines changed: 20 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -86,30 +86,37 @@ let html_of_breadcrumbs (breadcrumbs : Types.breadcrumb list) =
8686
make_navigation ~up_url:up.href
8787
(List.rev html @ sep @ [ Html.txt current.name ])
8888

89-
let page_creator ~config ~url ~uses_katex ~search_urls header breadcrumbs toc
90-
content =
89+
let page_creator ~config ~url ~uses_katex header breadcrumbs toc content =
9190
let theme_uri = Config.theme_uri config in
9291
let support_uri = Config.support_uri config in
92+
let search_uris = Config.search_uris config in
9393
let path = Link.Path.for_printing url in
9494

9595
let head : Html_types.head Html.elt =
9696
let title_string =
9797
Printf.sprintf "%s (%s)" url.name (String.concat "." path)
9898
in
9999

100-
let file_uri base file =
100+
let file_uri (base : Types.uri) file =
101101
match base with
102102
| Types.Absolute uri -> uri ^ "/" ^ file
103103
| Relative uri ->
104104
let page = Url.Path.{ kind = `File; parent = uri; name = file } in
105105
Link.href ~config ~resolve:(Current url) (Url.from_path page)
106106
in
107+
let search_uri uri =
108+
match uri with
109+
| Types.Absolute uri -> uri
110+
| Relative uri ->
111+
Link.href ~config ~resolve:(Current url) (Url.from_path uri)
112+
in
107113
let odoc_css_uri = file_uri theme_uri "odoc.css" in
108114
let highlight_js_uri = file_uri support_uri "highlight.pack.js" in
109115
let search_scripts =
110-
match search_urls with
116+
match search_uris with
111117
| [] -> []
112-
| search_urls ->
118+
| _ ->
119+
let search_urls = List.map search_uri search_uris in
113120
let search_urls =
114121
let search_url name = Printf.sprintf "'%s'" name in
115122
let search_urls = List.map search_url search_urls in
@@ -120,7 +127,10 @@ let page_creator ~config ~url ~uses_katex ~search_urls header breadcrumbs toc
120127
[
121128
Html.script ~a:[]
122129
(Html.txt
123-
(Format.asprintf "let base_url = '%s'; let search_urls = %s;"
130+
(Format.asprintf
131+
{|let base_url = '%s';
132+
let search_urls = %s;
133+
|}
124134
(let page =
125135
Url.Path.{ kind = `File; parent = None; name = "" }
126136
in
@@ -185,7 +195,7 @@ let page_creator ~config ~url ~uses_katex ~search_urls header breadcrumbs toc
185195
Html.head (Html.title (Html.txt title_string)) meta_elements
186196
in
187197
let search_bar =
188-
match search_urls with
198+
match search_uris with
189199
| [] -> []
190200
| _ ->
191201
[ Html.div ~a:[ Html.a_class [ "odoc-search" ] ] [ html_of_search () ] ]
@@ -208,12 +218,10 @@ let page_creator ~config ~url ~uses_katex ~search_urls header breadcrumbs toc
208218
in
209219
content
210220

211-
let make ~config ~url ~header ~breadcrumbs ~toc ~uses_katex ~search_urls content
212-
children =
221+
let make ~config ~url ~header ~breadcrumbs ~toc ~uses_katex content children =
213222
let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in
214223
let content =
215-
page_creator ~config ~url ~uses_katex ~search_urls header breadcrumbs toc
216-
content
224+
page_creator ~config ~url ~uses_katex header breadcrumbs toc content
217225
in
218226
{ Odoc_document.Renderer.filename; content; children }
219227

@@ -230,7 +238,7 @@ let src_page_creator ~breadcrumbs ~config ~url ~header name content =
230238
let title_string =
231239
Format.asprintf "Source: %s%a" name path_of_module_of_source url
232240
in
233-
let file_uri base file =
241+
let file_uri (base : Types.uri) file =
234242
match base with
235243
| Types.Absolute uri -> uri ^ "/" ^ file
236244
| Relative uri ->

src/html/html_page.mli

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@ val make :
2727
breadcrumbs:Types.breadcrumb list ->
2828
toc:Types.toc list ->
2929
uses_katex:bool ->
30-
search_urls:string list ->
3130
Html_types.div_content Html.elt list ->
3231
Odoc_document.Renderer.page list ->
3332
Odoc_document.Renderer.page

src/html/types.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@
22

33
type uri = Absolute of string | Relative of Odoc_document.Url.Path.t option
44

5+
type file_uri = Absolute of string | Relative of Odoc_document.Url.Path.t
6+
57
type toc = {
68
title : Html_types.flow5_without_interactive Tyxml.Html.elt list;
79
title_str : string;

src/latex/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -488,5 +488,5 @@ module Page = struct
488488
end
489489

490490
let render ~with_children = function
491-
| Document.Page (page, _) -> [ Page.page ~with_children page ]
491+
| Document.Page page -> [ Page.page ~with_children page ]
492492
| Source_page _ | Asset _ -> []

src/loader/odoc_loader.ml

Lines changed: 12 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ let read_cmt_infos source_id_opt id ~filename () =
5252

5353

5454
let make_compilation_unit ~make_root ~imports ~interface ?sourcefile ~name ~id
55-
?canonical ?shape_info ~source_info ~search_assets content =
55+
?canonical ?shape_info ~source_info content =
5656
let open Odoc_model.Lang.Compilation_unit in
5757
let interface, digest =
5858
match interface with
@@ -90,7 +90,6 @@ let make_compilation_unit ~make_root ~imports ~interface ?sourcefile ~name ~id
9090
canonical;
9191
source_info;
9292
shape_info;
93-
search_assets;
9493
}
9594

9695

@@ -100,7 +99,7 @@ let compilation_unit_of_sig ~make_root ~imports ~interface ?sourcefile ~name ~id
10099
make_compilation_unit ~make_root ~imports ~interface ?sourcefile ~name ~id
101100
?canonical ?shape_info content
102101

103-
let read_cmti ~make_root ~parent ~filename ~search_assets ~cmt_filename_opt ~source_id_opt () =
102+
let read_cmti ~make_root ~parent ~filename ~cmt_filename_opt ~source_id_opt () =
104103
let cmt_info = Cmt_format.read_cmt filename in
105104
match cmt_info.cmt_annots with
106105
| Interface intf -> (
@@ -121,11 +120,11 @@ let read_cmti ~make_root ~parent ~filename ~search_assets ~cmt_filename_opt ~sou
121120
| None -> (None, None)
122121
in
123122
compilation_unit_of_sig ~make_root ~imports:cmt_info.cmt_imports
124-
~interface ~sourcefile ~name ~id ?shape_info ~source_info ~search_assets
123+
~interface ~sourcefile ~name ~id ?shape_info ~source_info
125124
?canonical sg)
126125
| _ -> raise Not_an_interface
127126

128-
let read_cmt ~make_root ~parent ~filename ~search_assets ~source_id_opt () =
127+
let read_cmt ~make_root ~parent ~filename ~source_id_opt () =
129128
match Cmt_format.read_cmt filename with
130129
| exception Cmi_format.Error (Not_an_interface _) ->
131130
raise Not_an_implementation
@@ -165,14 +164,14 @@ let read_cmt ~make_root ~parent ~filename ~search_assets ~source_id_opt () =
165164
in
166165
let content = Odoc_model.Lang.Compilation_unit.Pack items in
167166
make_compilation_unit ~make_root ~imports ~interface ~sourcefile ~name
168-
~id ~search_assets ~source_info:None content
167+
~id ~source_info:None content
169168
| Implementation impl ->
170169
let id, sg, canonical = Cmt.read_implementation parent name impl in
171170
let shape_info, source_info =
172171
read_cmt_infos source_id_opt id ~filename ()
173172
in
174173
compilation_unit_of_sig ~make_root ~imports ~interface ~sourcefile
175-
~name ~id ?canonical ?shape_info ~search_assets ~source_info sg
174+
~name ~id ?canonical ?shape_info ~source_info sg
176175
| _ -> raise Not_an_implementation)
177176

178177
let read_cmi ~make_root ~parent ~filename () =
@@ -200,14 +199,14 @@ let wrap_errors ~filename f =
200199
| Not_an_interface -> not_an_interface filename
201200
| Make_root_error m -> error_msg filename m)
202201

203-
let read_cmti ~make_root ~parent ~filename ~source_id_opt ~cmt_filename_opt ~search_assets =
202+
let read_cmti ~make_root ~parent ~filename ~source_id_opt ~cmt_filename_opt =
204203
wrap_errors ~filename
205-
(read_cmti ~make_root ~parent ~filename ~source_id_opt ~cmt_filename_opt ~search_assets)
204+
(read_cmti ~make_root ~parent ~filename ~source_id_opt ~cmt_filename_opt)
206205

207-
let read_cmt ~make_root ~parent ~filename ~source_id_opt ~search_assets =
208-
wrap_errors ~filename (read_cmt ~make_root ~parent ~filename ~source_id_opt ~search_assets)
206+
let read_cmt ~make_root ~parent ~filename ~source_id_opt =
207+
wrap_errors ~filename (read_cmt ~make_root ~parent ~filename ~source_id_opt)
209208

210-
let read_cmi ~make_root ~parent ~filename ~search_assets =
211-
wrap_errors ~filename (read_cmi ~make_root ~parent ~filename ~search_assets)
209+
let read_cmi ~make_root ~parent ~filename =
210+
wrap_errors ~filename (read_cmi ~make_root ~parent ~filename)
212211

213212
let read_location = Doc_attr.read_location

0 commit comments

Comments
 (0)