Skip to content

Commit 6516522

Browse files
committed
Review comments
- Rename `--source-parent-file` into `parent` - Check that source argument is empty in case of rendering source tree - Removed now useless `syntax` argument from `extra_documents` - Check `"src-"`prefix when loading units for counting occurrences to avoid loading for nothing - fixed some typos and made some small refactoring Signed-off-by: Paul-Elliot <[email protected]>
1 parent 4301560 commit 6516522

File tree

10 files changed

+46
-43
lines changed

10 files changed

+46
-43
lines changed

src/document/renderer.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ type input =
2424
type 'a t = {
2525
name : string;
2626
render : 'a -> Types.Document.t -> page list;
27-
extra_documents : 'a -> input -> syntax:syntax -> Types.Document.t list;
27+
extra_documents : 'a -> input -> Types.Document.t list;
2828
}
2929

3030
let document_of_page ~syntax v =

src/odoc/compile.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ let is_module_name n = String.length n > 0 && Char.Ascii.is_upper n.[0]
4040
- [module-Foo] child is a module.
4141
- [module-foo], [Foo] child is a module, for backward compatibility.
4242
- [page-foo] child is a container or leaf page.
43-
- [src-foo] child is a source tree
43+
- [srctree-foo] child is a source tree
4444
4545
Parses [...-"foo"] as [...-foo] for backward compatibility. *)
4646
let parse_parent_child_reference s =
@@ -56,6 +56,7 @@ let parse_parent_child_reference s =
5656
| Some ("asset", n) -> Ok (Asset_child (unquote n))
5757
| Some ("module", n) ->
5858
Ok (Module_child (unquote (String.Ascii.capitalize n)))
59+
| Some ("src", _) -> Error (`Msg "Implementation unexpected")
5960
| Some (k, _) -> Error (`Msg ("Unrecognized kind: " ^ k))
6061
| None -> if is_module_name s then Ok (Module_child s) else Ok (Page_child s)
6162

src/odoc/compile.mli

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,11 @@ val name_of_output : prefix:string -> Fs.File.t -> string
2727
(** Compute the name of the page from the output file. Prefix is the prefix to
2828
remove from the filename. *)
2929

30+
val resolve_imports :
31+
Resolver.t ->
32+
Lang.Compilation_unit.Import.t list ->
33+
Lang.Compilation_unit.Import.t list
34+
3035
val resolve_parent_page :
3136
Resolver.t ->
3237
string ->

src/odoc/depends.ml

Lines changed: 10 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -77,25 +77,23 @@ end = struct
7777
Odoc_model.Root.Hash_table.fold (fun s () acc -> s :: acc) t []
7878
end
7979

80+
let deps_of_imports ~deps imports =
81+
List.iter imports ~f:(fun import ->
82+
match import with
83+
| Odoc_model.Lang.Compilation_unit.Import.Unresolved _ -> ()
84+
| Odoc_model.Lang.Compilation_unit.Import.Resolved (root, _) ->
85+
Hash_set.add deps root);
86+
Ok ()
87+
8088
let deps_of_odoc_file ~deps input =
8189
Odoc_file.load input >>= fun unit ->
8290
match unit.content with
8391
| Page_content _ | Source_tree_content _ ->
8492
Ok () (* XXX something should certainly be done here *)
8593
| Impl_content impl ->
86-
List.iter impl.Odoc_model.Lang.Implementation.imports ~f:(fun import ->
87-
match import with
88-
| Odoc_model.Lang.Compilation_unit.Import.Unresolved _ -> ()
89-
| Odoc_model.Lang.Compilation_unit.Import.Resolved (root, _) ->
90-
Hash_set.add deps root);
91-
Ok ()
94+
deps_of_imports ~deps impl.Odoc_model.Lang.Implementation.imports
9295
| Unit_content unit ->
93-
List.iter unit.Odoc_model.Lang.Compilation_unit.imports ~f:(fun import ->
94-
match import with
95-
| Odoc_model.Lang.Compilation_unit.Import.Unresolved _ -> ()
96-
| Odoc_model.Lang.Compilation_unit.Import.Resolved (root, _) ->
97-
Hash_set.add deps root);
98-
Ok ()
96+
deps_of_imports ~deps unit.Odoc_model.Lang.Compilation_unit.imports
9997

10098
let for_rendering_step pkg_dir =
10199
let deps = Hash_set.create () in

src/odoc/html_page.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,7 @@ let asset_documents parent_id children asset_paths =
6969
Some (Odoc_document.Types.Document.Asset { url; src = path }))
7070
paired_or_missing
7171

72-
let extra_documents args input ~syntax:_ =
72+
let extra_documents args input =
7373
match input with
7474
| Odoc_document.Renderer.CU _unit ->
7575
(* Remove assets from [Document.t] and move their rendering in the main

src/odoc/latex.ml

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

8-
let extra_documents _args _unit ~syntax:_ = []
8+
let extra_documents _args _unit = []
99

1010
let renderer = { Renderer.name = "latex"; render; extra_documents }

src/odoc/man_page.ml

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

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

5-
let extra_documents _args _unit ~syntax:_ = []
5+
let extra_documents _args _unit = []
66

77
let renderer = { Renderer.name = "man"; render; extra_documents }

src/odoc/occurrences.ml

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,14 @@
11
open Or_error
22

33
let handle_file file ~f =
4-
Odoc_file.load file |> function
5-
| Error _ as e -> e
6-
| Ok unit' -> (
7-
match unit' with
8-
| { Odoc_file.content = Impl_content impl; _ } -> Ok (Some (f impl))
9-
| _ -> Ok None)
4+
if String.starts_with ~prefix:"src-" (Fpath.filename file) then
5+
Odoc_file.load file |> function
6+
| Error _ as e -> e
7+
| Ok unit' -> (
8+
match unit' with
9+
| { Odoc_file.content = Impl_content impl; _ } -> Ok (Some (f impl))
10+
| _ -> Ok None)
11+
else Ok None
1012

1113
let fold_dirs ~dirs ~f ~init =
1214
dirs

src/odoc/rendering.ml

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ let documents_of_unit ~warnings_options ~syntax ~source ~renderer ~extra
2525
~filename unit =
2626
Odoc_model.Error.catch_warnings (fun () ->
2727
check_empty_source_arg source filename;
28-
renderer.Renderer.extra_documents ~syntax extra (CU unit))
28+
renderer.Renderer.extra_documents extra (CU unit))
2929
|> Odoc_model.Error.handle_warnings ~warnings_options
3030
>>= fun extra_docs ->
3131
Ok
@@ -36,7 +36,7 @@ let documents_of_page ~warnings_options ~syntax ~source ~renderer ~extra
3636
~filename page =
3737
Odoc_model.Error.catch_warnings (fun () ->
3838
check_empty_source_arg source filename;
39-
renderer.Renderer.extra_documents ~syntax extra (Page page))
39+
renderer.Renderer.extra_documents extra (Page page))
4040
|> Odoc_model.Error.handle_warnings ~warnings_options
4141
>>= fun extra_docs -> Ok (Renderer.document_of_page ~syntax page :: extra_docs)
4242

@@ -75,6 +75,13 @@ let documents_of_implementation ~warnings_options:_ ~syntax impl source =
7575
"--source or --source-root should be passed when generating \
7676
documents for an implementation.")
7777

78+
let documents_of_source_tree ~warnings_options ~syntax ~source ~filename srctree
79+
=
80+
Odoc_model.Error.catch_warnings (fun () ->
81+
check_empty_source_arg source filename)
82+
|> Odoc_model.Error.handle_warnings ~warnings_options
83+
>>= fun () -> Ok (Renderer.documents_of_source_tree ~syntax srctree)
84+
7885
let documents_of_odocl ~warnings_options ~renderer ~extra ~source ~syntax input
7986
=
8087
Odoc_file.load input >>= fun unit ->
@@ -84,7 +91,8 @@ let documents_of_odocl ~warnings_options ~renderer ~extra ~source ~syntax input
8491
documents_of_page ~warnings_options ~syntax ~source ~renderer ~extra
8592
~filename odoctree
8693
| Source_tree_content srctree ->
87-
Ok (Renderer.documents_of_source_tree ~syntax srctree)
94+
documents_of_source_tree ~warnings_options ~syntax ~source ~filename
95+
srctree
8896
| Impl_content impl ->
8997
documents_of_implementation ~warnings_options ~syntax impl source
9098
| Unit_content odoctree ->

src/odoc/source.ml

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,34 +1,23 @@
11
open Odoc_model
22
open Or_error
33

4-
let resolve_imports resolver imports =
5-
List.map
6-
(function
7-
| Lang.Compilation_unit.Import.Resolved _ as resolved -> resolved
8-
| Unresolved (name, _) as unresolved -> (
9-
match Resolver.resolve_import resolver name with
10-
| Some root -> Resolved (root, Names.ModuleName.make_std name)
11-
| None -> unresolved))
12-
imports
13-
144
let resolve_and_substitute ~resolver ~make_root ~source_id input_file =
155
let filename = Fs.File.to_string input_file in
166
let impl =
177
Odoc_loader.read_impl ~make_root ~filename ~source_id
188
|> Error.raise_errors_and_warnings
199
in
20-
let impl = { impl with imports = resolve_imports resolver impl.imports } in
10+
let impl =
11+
{ impl with imports = Compile.resolve_imports resolver impl.imports }
12+
in
2113
let env = Resolver.build_compile_env_for_impl resolver impl in
2214
Odoc_xref2.Compile.compile_impl ~filename env impl |> Error.raise_warnings
2315

2416
let root_of_implementation ~source_id ~module_name ~digest =
2517
let open Root in
26-
let result =
27-
let file = Odoc_file.create_impl module_name in
28-
let id :> Paths.Identifier.OdocId.t = source_id in
29-
Ok { id; file; digest }
30-
in
31-
result
18+
let file = Odoc_file.create_impl module_name in
19+
let id :> Paths.Identifier.OdocId.t = source_id in
20+
Ok { id; file; digest }
3221

3322
let compile ~resolver ~output ~warnings_options ~source_path ~source_parent_file
3423
input =

0 commit comments

Comments
 (0)