Skip to content

Commit f04cce9

Browse files
committed
Remove the old asset pipeline
This removes a deprecated-before-use pipeline, and allows to finally remove the extra_documents in renderers
1 parent 1e9cf37 commit f04cce9

File tree

14 files changed

+35
-238
lines changed

14 files changed

+35
-238
lines changed

src/document/renderer.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,6 @@ type input =
2424
type 'a t = {
2525
name : string;
2626
render : 'a -> Types.Block.t option -> Types.Document.t -> page list;
27-
extra_documents : 'a -> input -> Types.Document.t list;
2827
}
2928

3029
let document_of_page ~syntax v =

src/model/lang.ml

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -525,11 +525,7 @@ end =
525525
Implementation
526526

527527
module rec Page : sig
528-
type child =
529-
| Page_child of string
530-
| Module_child of string
531-
| Source_tree_child of string
532-
| Asset_child of string
528+
type child = Page_child of string | Module_child of string
533529

534530
type t = {
535531
name : Identifier.Page.t;

src/odoc/bin/main.ml

Lines changed: 3 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1174,27 +1174,19 @@ module Odoc_html_args = struct
11741174
in
11751175
Arg.(value & flag & info ~doc [ "as-json" ])
11761176

1177-
let assets =
1178-
let doc =
1179-
"Assets files. These must match the assets listed as children during the \
1180-
compile phase."
1181-
in
1182-
Arg.(
1183-
value & opt_all convert_fpath [] & info [ "asset" ] ~doc ~docv:"file.ext")
1184-
11851177
let extra_args =
11861178
let config semantic_uris closed_details indent theme_uri support_uri
1187-
search_uris flat as_json assets =
1179+
search_uris flat as_json =
11881180
let open_details = not closed_details in
11891181
let html_config =
11901182
Odoc_html.Config.v ~theme_uri ~support_uri ~search_uris ~semantic_uris
11911183
~indent ~flat ~open_details ~as_json ()
11921184
in
1193-
{ Html_page.html_config; assets }
1185+
{ Html_page.html_config }
11941186
in
11951187
Term.(
11961188
const config $ semantic_uris $ closed_details $ indent $ theme_uri
1197-
$ support_uri $ search_uri $ flat $ as_json $ assets)
1189+
$ support_uri $ search_uri $ flat $ as_json)
11981190
end
11991191

12001192
module Odoc_html = Make_renderer (Odoc_html_args)

src/odoc/compile.ml

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -71,8 +71,6 @@ let parse_parent_child_reference s =
7171
in
7272
match String.cut ~sep:"-" s with
7373
| Some ("page", n) -> Ok (Lang.Page.Page_child (unquote n))
74-
| Some ("srctree", n) -> Ok (Source_tree_child (unquote n))
75-
| Some ("asset", n) -> Ok (Asset_child (unquote n))
7674
| Some ("module", n) ->
7775
Ok (Module_child (unquote (String.Ascii.capitalize n)))
7876
| Some ("src", _) -> Error (`Msg "Implementation unexpected")
@@ -85,8 +83,7 @@ let resolve_parent_page resolver f =
8583
match Resolver.lookup_page resolver p with
8684
| Some r -> Ok r
8785
| None -> Error (`Msg "Couldn't find specified parent page"))
88-
| Source_tree_child _ | Module_child _ | Asset_child _ ->
89-
Error (`Msg "Expecting page as parent")
86+
| Module_child _ -> Error (`Msg "Expecting page as parent")
9087
in
9188
let extract_parent = function
9289
| { Paths.Identifier.iv = `Page _; _ } as container -> Ok container
@@ -171,7 +168,7 @@ let root_of_compilation_unit ~parent_id ~parents_children ~hidden ~output
171168
Filename.chop_extension Fs.File.(to_string @@ basename output)
172169
in
173170
String.Ascii.(uncapitalize n = uncapitalize filename)
174-
| Asset_child _ | Source_tree_child _ | Page_child _ -> false
171+
| Page_child _ -> false
175172
in
176173
match parents_children with
177174
| Some parents_children ->
@@ -215,7 +212,7 @@ let mld ~parent_id ~parents_children ~output ~children ~warnings_options input =
215212
let page_name = PageName.make_std root_name in
216213
let check_child = function
217214
| Lang.Page.Page_child n -> root_name = n
218-
| Asset_child _ | Source_tree_child _ | Module_child _ -> false
215+
| Module_child _ -> false
219216
in
220217
(if children = [] then
221218
(* No children, this is a leaf page. *)

src/odoc/html_page.ml

Lines changed: 3 additions & 59 deletions
Original file line numberDiff line numberDiff line change
@@ -14,65 +14,9 @@
1414
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
1515
*)
1616

17-
open Odoc_model
17+
type args = { html_config : Odoc_html.Config.t }
1818

19-
type args = { html_config : Odoc_html.Config.t; assets : Fpath.t list }
20-
21-
let render { html_config; assets = _ } sidebar page =
19+
let render { html_config } sidebar page =
2220
Odoc_html.Generator.render ~config:html_config ~sidebar page
2321

24-
let asset_documents parent_id children asset_paths =
25-
let asset_names =
26-
Odoc_utils.List.filter_map
27-
(function Lang.Page.Asset_child name -> Some name | _ -> None)
28-
children
29-
in
30-
let rec extract paths name =
31-
match paths with
32-
| [] -> (paths, (name, None))
33-
| x :: xs when Fpath.basename x = name -> (xs, (name, Some x))
34-
| x :: xs ->
35-
let rest, elt = extract xs name in
36-
(x :: rest, elt)
37-
in
38-
let unmatched, paired_or_missing =
39-
let rec foldmap paths paired = function
40-
| [] -> (paths, paired)
41-
| name :: names ->
42-
let paths, pair = extract paths name in
43-
foldmap paths (pair :: paired) names
44-
in
45-
foldmap asset_paths [] asset_names
46-
in
47-
List.iter
48-
(fun asset ->
49-
Error.raise_warning
50-
(Error.filename_only "this asset was not declared as a child of %s"
51-
(Paths.Identifier.name parent_id)
52-
(Fs.File.to_string asset)))
53-
unmatched;
54-
Odoc_utils.List.filter_map
55-
(fun (name, path) ->
56-
match path with
57-
| None ->
58-
Error.raise_warning (Error.filename_only "asset is missing." name);
59-
None
60-
| Some path ->
61-
let asset_id =
62-
Paths.Identifier.Mk.asset_file
63-
(parent_id, Names.AssetName.make_std name)
64-
in
65-
let url = Odoc_document.Url.Path.from_identifier asset_id in
66-
Some (Odoc_document.Types.Document.Asset { url; src = path }))
67-
paired_or_missing
68-
69-
let extra_documents args input =
70-
match input with
71-
| Odoc_document.Renderer.CU _unit ->
72-
(* Remove assets from [Document.t] and move their rendering in the main
73-
[render] function to allow to remove the [extra_documents]
74-
machinery? *)
75-
[]
76-
| Page page -> asset_documents page.Lang.Page.name page.children args.assets
77-
78-
let renderer = { Odoc_document.Renderer.name = "html"; render; extra_documents }
22+
let renderer = { Odoc_document.Renderer.name = "html"; render }

src/odoc/html_page.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,6 @@
1616

1717
open Odoc_document
1818

19-
type args = { html_config : Odoc_html.Config.t; assets : Fpath.t list }
19+
type args = { html_config : Odoc_html.Config.t }
2020

2121
val renderer : args Renderer.t

src/odoc/latex.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,4 @@ type args = { with_children : bool }
55
let render args _sidebar page =
66
Odoc_latex.Generator.render ~with_children:args.with_children page
77

8-
let extra_documents _args _unit = []
9-
10-
let renderer = { Renderer.name = "latex"; render; extra_documents }
8+
let renderer = { Renderer.name = "latex"; render }

src/odoc/man_page.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,4 @@ open Odoc_document
22

33
let render _ _sidebar page = Odoc_manpage.Generator.render page
44

5-
let extra_documents _args _unit = []
6-
7-
let renderer = { Renderer.name = "man"; render; extra_documents }
5+
let renderer = { Renderer.name = "man"; render }

src/odoc/rendering.ml

Lines changed: 19 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -2,26 +2,13 @@ open Odoc_document
22
open Or_error
33
open Odoc_model
44

5-
let documents_of_unit ~warnings_options ~syntax ~renderer ~extra unit =
6-
Error.catch_warnings (fun () ->
7-
renderer.Renderer.extra_documents extra (CU unit))
8-
|> Error.handle_warnings ~warnings_options
9-
>>= fun extra_docs ->
10-
Ok (Renderer.document_of_compilation_unit ~syntax unit :: extra_docs)
11-
12-
let documents_of_page ~warnings_options ~syntax ~renderer ~extra page =
13-
Error.catch_warnings (fun () ->
14-
renderer.Renderer.extra_documents extra (Page page))
15-
|> Error.handle_warnings ~warnings_options
16-
>>= fun extra_docs -> Ok (Renderer.document_of_page ~syntax page :: extra_docs)
17-
18-
let documents_of_odocl ~warnings_options ~renderer ~extra ~syntax input =
5+
let document_of_odocl ~syntax input =
196
Odoc_file.load input >>= fun unit ->
207
match unit.content with
218
| Odoc_file.Page_content odoctree ->
22-
documents_of_page ~warnings_options ~syntax ~renderer ~extra odoctree
9+
Ok (Renderer.document_of_page ~syntax odoctree)
2310
| Unit_content odoctree ->
24-
documents_of_unit ~warnings_options ~syntax ~renderer ~extra odoctree
11+
Ok (Renderer.document_of_compilation_unit ~syntax odoctree)
2512
| Impl_content _ ->
2613
Error
2714
(`Msg
@@ -33,12 +20,11 @@ let documents_of_odocl ~warnings_options ~renderer ~extra ~syntax input =
3320
"Wrong kind of unit: Expected a page or module unit, got an asset \
3421
unit. Use the dedicated command for assets.")
3522

36-
let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
37-
input =
23+
let document_of_input ~resolver ~warnings_options ~syntax input =
3824
let output = Fs.File.(set_ext ".odocl" input) in
3925
Odoc_link.from_odoc ~resolver ~warnings_options input output >>= function
40-
| `Page page -> Ok [ Renderer.document_of_page ~syntax page ]
41-
| `Module m -> documents_of_unit ~warnings_options ~syntax ~renderer ~extra m
26+
| `Page page -> Ok (Renderer.document_of_page ~syntax page)
27+
| `Module m -> Ok (Renderer.document_of_compilation_unit ~syntax m)
4228
| `Impl _ ->
4329
Error
4430
(`Msg
@@ -81,26 +67,20 @@ let render_document renderer ~sidebar ~output:root_dir ~extra_suffix ~extra doc
8167
let render_odoc ~resolver ~warnings_options ~syntax ~renderer ~output extra file
8268
=
8369
let extra_suffix = None in
84-
documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax file
85-
>>= fun docs ->
86-
List.iter
87-
(render_document renderer ~sidebar:None ~output ~extra_suffix ~extra)
88-
docs;
70+
document_of_input ~resolver ~warnings_options ~syntax file >>= fun doc ->
71+
render_document renderer ~sidebar:None ~output ~extra_suffix ~extra doc;
8972
Ok ()
9073

91-
let generate_odoc ~syntax ~warnings_options ~renderer ~output ~extra_suffix
74+
let generate_odoc ~syntax ~warnings_options:_ ~renderer ~output ~extra_suffix
9275
~sidebar extra file =
9376
(match sidebar with
9477
| None -> Ok None
9578
| Some x ->
9679
Odoc_file.load_index x >>= fun (sidebar, _) ->
9780
Ok (Some (Odoc_document.Sidebar.of_lang sidebar)))
9881
>>= fun sidebar ->
99-
documents_of_odocl ~warnings_options ~renderer ~extra ~syntax file
100-
>>= fun docs ->
101-
List.iter
102-
(render_document renderer ~output ~sidebar ~extra_suffix ~extra)
103-
docs;
82+
document_of_odocl ~syntax file >>= fun doc ->
83+
render_document renderer ~output ~sidebar ~extra_suffix ~extra doc;
10484
Ok ()
10585

10686
let documents_of_implementation ~warnings_options:_ ~syntax impl source_file =
@@ -148,20 +128,16 @@ let generate_asset_odoc ~warnings_options:_ ~renderer ~output ~asset_file
148128

149129
let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir
150130
~extra odoctree =
151-
let docs =
131+
let doc =
152132
if Fpath.get_ext odoctree = ".odoc" then
153-
documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
154-
odoctree
155-
else documents_of_odocl ~warnings_options ~renderer ~extra ~syntax odoctree
133+
document_of_input ~resolver ~warnings_options ~syntax odoctree
134+
else document_of_odocl ~syntax odoctree
156135
in
157-
docs >>= fun docs ->
158-
List.iter
159-
(fun doc ->
160-
let pages = renderer.Renderer.render extra None doc in
161-
Renderer.traverse pages ~f:(fun filename _content ->
162-
let filename = Fpath.normalize @@ Fs.File.append root_dir filename in
163-
Format.printf "%a\n" Fpath.pp filename))
164-
docs;
136+
doc >>= fun doc ->
137+
let pages = renderer.Renderer.render extra None doc in
138+
Renderer.traverse pages ~f:(fun filename _content ->
139+
let filename = Fpath.normalize @@ Fs.File.append root_dir filename in
140+
Format.printf "%a\n" Fpath.pp filename);
165141
Ok ()
166142

167143
let targets_source_odoc ~syntax ~warnings_options ~renderer ~output:root_dir

src/xref2/link.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1109,7 +1109,6 @@ let page env page =
11091109
List.iter
11101110
(fun child ->
11111111
match child with
1112-
| Page.Asset_child _ | Page.Source_tree_child _ -> ()
11131112
| Page.Page_child page -> (
11141113
match Env.lookup_page_by_name page env with
11151114
| Ok _ -> ()

0 commit comments

Comments
 (0)