Skip to content

Commit f34ed8a

Browse files
committed
Adding an html-generate-impl command
1 parent ffd9ec7 commit f34ed8a

File tree

14 files changed

+135
-56
lines changed

14 files changed

+135
-56
lines changed

src/odoc/bin/main.ml

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -775,6 +775,8 @@ module Make_renderer (R : S) : sig
775775
val targets : docs:string -> unit Term.t * Term.info
776776

777777
val generate : docs:string -> unit Term.t * Term.info
778+
779+
val generate_impl : docs:string -> unit Term.t * Term.info
778780
end = struct
779781
let input_odoc =
780782
let doc = "Input file." in
@@ -858,6 +860,43 @@ end = struct
858860

859861
let generate ~docs = Generate.(cmd, info ~docs)
860862

863+
module Generate_impl = struct
864+
let generate extra _hidden output_dir syntax extra_suffix input_file
865+
warnings_options source_file =
866+
let file = Fs.File.of_string input_file in
867+
Rendering.generate_impl_odoc ~renderer:R.renderer ~warnings_options
868+
~syntax ~output:output_dir ~extra_suffix ~source_file extra file
869+
870+
let source_file =
871+
let doc = "Source code for the implementation unit." in
872+
Arg.(
873+
value
874+
& opt (some convert_fpath) None
875+
& info [ "source" ] ~doc ~docv:"file.ml")
876+
877+
let cmd =
878+
let syntax =
879+
let doc = "Available options: ml | re" in
880+
let env = Arg.env_var "ODOC_SYNTAX" in
881+
Arg.(
882+
value
883+
& opt (pconv convert_syntax) Odoc_document.Renderer.OCaml
884+
@@ info ~docv:"SYNTAX" ~doc ~env [ "syntax" ])
885+
in
886+
Term.(
887+
const handle_error
888+
$ (const generate $ R.extra_args $ hidden $ dst ~create:true () $ syntax
889+
$ extra_suffix $ input_odocl $ warnings_options $ source_file))
890+
891+
let info ~docs =
892+
let doc =
893+
Format.sprintf "Generate %s files from a $(i,.odocl)." R.renderer.name
894+
in
895+
Term.info ~docs ~doc (R.renderer.name ^ "-generate-impl")
896+
end
897+
898+
let generate_impl ~docs = Generate_impl.(cmd, info ~docs)
899+
861900
module Targets = struct
862901
let list_targets output_dir directories extra odoc_file =
863902
let odoc_file = Fs.File.of_string odoc_file in
@@ -1458,6 +1497,7 @@ let () =
14581497
Compile_asset.(cmd, info ~docs:section_pipeline);
14591498
Odoc_link.(cmd, info ~docs:section_pipeline);
14601499
Odoc_html.generate ~docs:section_pipeline;
1500+
Odoc_html.generate_impl ~docs:section_pipeline;
14611501
Support_files_command.(cmd, info ~docs:section_pipeline);
14621502
Compile_impl.(cmd, info ~docs:section_pipeline);
14631503
Indexing.(cmd, info ~docs:section_pipeline);

src/odoc/rendering.ml

Lines changed: 45 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -15,37 +15,17 @@ let documents_of_page ~warnings_options ~syntax ~renderer ~extra page =
1515
|> Error.handle_warnings ~warnings_options
1616
>>= fun extra_docs -> Ok (Renderer.document_of_page ~syntax page :: extra_docs)
1717

18-
(* let documents_of_implementation ~warnings_options:_ ~syntax impl source = *)
19-
(* match (source, impl.Lang.Implementation.id) with *)
20-
(* | Some source_file, Some _ -> ( *)
21-
(* match Fs.File.read source_file with *)
22-
(* | Error (`Msg msg) -> *)
23-
(* Error (`Msg (Format.sprintf "Couldn't load source file: %s" msg)) *)
24-
(* | Ok source_code -> *)
25-
(* let syntax_info = *)
26-
(* Syntax_highlighter.syntax_highlighting_locs source_code *)
27-
(* in *)
28-
(* let rendered = *)
29-
(* Odoc_document.Renderer.documents_of_implementation ~syntax impl *)
30-
(* syntax_info source_code *)
31-
(* in *)
32-
(* Ok rendered) *)
33-
(* | _, None -> *)
34-
(* Error (`Msg "The implementation unit was not compiled with --source-id.") *)
35-
(* | None, _ -> *)
36-
(* Error *)
37-
(* (`Msg *)
38-
(* "--source or --source-root should be passed when generating \ *)
39-
(* documents for an implementation.") *)
40-
4118
let documents_of_odocl ~warnings_options ~renderer ~extra ~syntax input =
4219
Odoc_file.load input >>= fun unit ->
4320
match unit.content with
4421
| Odoc_file.Page_content odoctree ->
4522
documents_of_page ~warnings_options ~syntax ~renderer ~extra odoctree
4623
| Impl_content _impl ->
4724
(* documents_of_implementation ~warnings_options ~syntax impl source *)
48-
failwith "TODO ERROR"
25+
Error
26+
(`Msg
27+
"Wrong kind of unit: Expected a page or module unit, got an \
28+
implementation. Use the dedicated command for implementation.")
4929
| Unit_content odoctree ->
5030
documents_of_unit ~warnings_options ~syntax ~renderer ~extra odoctree
5131
| Asset_content _ -> Ok [] (* TODO *)
@@ -56,8 +36,10 @@ let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
5636
Odoc_link.from_odoc ~resolver ~warnings_options input output >>= function
5737
| `Page page -> Ok [ Renderer.document_of_page ~syntax page ]
5838
| `Impl _impl ->
59-
(* Ok (Renderer.documents_of_implementation ~syntax impl [] "") *)
60-
failwith "TODO ERROR"
39+
Error
40+
(`Msg
41+
"Wrong kind of unit: Expected a page or module unit, got an \
42+
implementation. Use the dedicated command for implementation.")
6143
| `Module m -> documents_of_unit ~warnings_options ~syntax ~renderer ~extra m
6244
| `Asset _ -> Ok [] (* TODO *)
6345

@@ -114,6 +96,43 @@ let generate_odoc ~syntax ~warnings_options ~renderer ~output ~extra_suffix
11496
docs;
11597
Ok ()
11698

99+
let documents_of_implementation ~warnings_options:_ ~syntax impl source =
100+
match (source, impl.Lang.Implementation.id) with
101+
| Some source_file, Some _ -> (
102+
match Fs.File.read source_file with
103+
| Error (`Msg msg) ->
104+
Error (`Msg (Format.sprintf "Couldn't load source file: %s" msg))
105+
| Ok source_code ->
106+
let syntax_info =
107+
Syntax_highlighter.syntax_highlighting_locs source_code
108+
in
109+
let rendered =
110+
Odoc_document.Renderer.documents_of_implementation ~syntax impl
111+
syntax_info source_code
112+
in
113+
Ok rendered)
114+
| _, None ->
115+
Error (`Msg "The implementation unit was not compiled with --source-id.")
116+
| None, _ ->
117+
Error
118+
(`Msg
119+
"--source should be passed when generating documents for an \
120+
implementation.")
121+
122+
let generate_impl_odoc ~syntax ~warnings_options ~renderer ~output ~source_file
123+
~extra_suffix extra file =
124+
Odoc_file.load file >>= fun unit ->
125+
match unit.content with
126+
| Odoc_file.Impl_content impl ->
127+
documents_of_implementation ~warnings_options ~syntax impl source_file
128+
>>= fun docs ->
129+
List.iter
130+
(render_document renderer ~output ~sidebar:None ~extra_suffix ~extra)
131+
docs;
132+
Ok ()
133+
| Page_content _ | Unit_content _ | Asset_content _ ->
134+
Error (`Msg "Expected an implementation unit")
135+
117136
let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir
118137
~extra odoctree =
119138
let docs =

src/odoc/rendering.mli

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,17 @@ val generate_odoc :
2222
Fpath.t ->
2323
(unit, [> msg ]) result
2424

25+
val generate_impl_odoc :
26+
syntax:Renderer.syntax ->
27+
warnings_options:Odoc_model.Error.warnings_options ->
28+
renderer:'a Renderer.t ->
29+
output:Fs.directory ->
30+
source_file:Fpath.t option ->
31+
extra_suffix:string option ->
32+
'a ->
33+
Fpath.t ->
34+
(unit, [> msg ]) result
35+
2536
val targets_odoc :
2637
resolver:Resolver.t ->
2738
warnings_options:Odoc_model.Error.warnings_options ->

test/integration/json_expansion_with_sources.t/run.t

Lines changed: 18 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -24,17 +24,29 @@ Test the JSON output in the presence of expanded modules.
2424
html/Main/A/index.html.json
2525
html/Main/A/B/index.html.json
2626
$ odoc html-targets --source a.ml -o html impl-main__A.odocl
27-
html/src/a.ml.html
27+
odoc: unknown option '--source'.
28+
Usage: odoc html-targets [OPTION]… FILE.odocl
29+
Try 'odoc html-targets --help' or 'odoc --help' for more information.
30+
[2]
2831
$ odoc html-targets --source main.ml -o html impl-main.odocl
29-
html/src/main.ml.html
32+
odoc: unknown option '--source'.
33+
Usage: odoc html-targets [OPTION]… FILE.odocl
34+
Try 'odoc html-targets --help' or 'odoc --help' for more information.
35+
[2]
3036
$ odoc html-targets --source a.ml --as-json -o html impl-main__A.odocl
31-
html/src/a.ml.html.json
37+
odoc: unknown option '--source'.
38+
Usage: odoc html-targets [OPTION]… FILE.odocl
39+
Try 'odoc html-targets --help' or 'odoc --help' for more information.
40+
[2]
3241
$ odoc html-targets --source main.ml --as-json -o html impl-main.odocl
33-
html/src/main.ml.html.json
42+
odoc: unknown option '--source'.
43+
Usage: odoc html-targets [OPTION]… FILE.odocl
44+
Try 'odoc html-targets --help' or 'odoc --help' for more information.
45+
[2]
3446

35-
$ odoc html-generate --source a.ml --as-json -o html impl-main__A.odocl
47+
$ odoc html-generate-impl --source a.ml --as-json -o html impl-main__A.odocl
3648
$ odoc html-generate --as-json -o html main__A.odocl
37-
$ odoc html-generate --source main.ml --as-json -o html impl-main.odocl
49+
$ odoc html-generate-impl --source main.ml --as-json -o html impl-main.odocl
3850
$ odoc html-generate --as-json -o html main.odocl
3951

4052
$ cat html/Main/index.html.json

test/odoc_print/odoc_print.ml

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -222,9 +222,6 @@ let run inp short long_paths show_canonical show_expansions
222222
in
223223
Odoc_file.load inp >>= fun unit ->
224224
match unit.content with
225-
| Odoc_file.Source_tree_content tree ->
226-
print_json_desc Lang_desc.source_tree_page_t tree;
227-
Ok ()
228225
| Odoc_file.Page_content page ->
229226
print_json_desc Lang_desc.page_t page;
230227
Ok ()

test/sources/double_wrapped.t/run.t

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,8 @@ Similar to the lookup_def_wrapped test.
2020
$ odoc link -I . main__.odoc
2121

2222
$ odoc html-generate --indent -o html main.odocl
23-
$ odoc html-generate --source main.ml --indent -o html impl-main.odocl
24-
$ odoc html-generate --source a.ml --indent -o html impl-main__A.odocl
23+
$ odoc html-generate-impl --source main.ml --indent -o html impl-main.odocl
24+
$ odoc html-generate-impl --source a.ml --indent -o html impl-main__A.odocl
2525

2626
Look if all the source files are generated:
2727

test/sources/functor.t/run.t

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -15,11 +15,11 @@ Verify the behavior on functors.
1515
$ odoc link -I . impl-s.odoc
1616
$ odoc link -I . impl-a.odoc
1717
$ odoc link -I . impl-b.odoc
18-
$ odoc html-generate --source s.ml --indent -o html impl-s.odocl
18+
$ odoc html-generate-impl --source s.ml --indent -o html impl-s.odocl
1919
$ odoc html-generate --indent -o html s.odocl
20-
$ odoc html-generate --source a.ml --indent -o html impl-a.odocl
20+
$ odoc html-generate-impl --source a.ml --indent -o html impl-a.odocl
2121
$ odoc html-generate --indent -o html a.odocl
22-
$ odoc html-generate --source b.ml --indent -o html impl-b.odocl
22+
$ odoc html-generate-impl --source b.ml --indent -o html impl-b.odocl
2323
$ odoc html-generate --indent -o html b.odocl
2424

2525
$ find html | sort

test/sources/include_in_expansion.t/run.t

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,9 @@ Checking that source parents are kept, using include.
1818
$ odoc link -I . impl-main.odoc
1919
$ odoc link -I . impl-main__A.odoc
2020

21-
$ odoc html-generate --source main.ml --indent -o html impl-main.odocl
21+
$ odoc html-generate-impl --source main.ml --indent -o html impl-main.odocl
2222
$ odoc html-generate --indent -o html main.odocl
23-
$ odoc html-generate --source a.ml --hidden --indent -o html impl-main__A.odocl
23+
$ odoc html-generate-impl --source a.ml --hidden --indent -o html impl-main__A.odocl
2424
$ odoc html-generate --hidden --indent -o html main__A.odocl
2525

2626
In Main.A, the source parent of value x should be to Main__A, while the

test/sources/lookup_def_wrapped.t/run.t

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -21,11 +21,11 @@ It's a simpler case than Dune's wrapping.
2121
$ odoc link -I . impl-main.odoc
2222
$ odoc link -I . main.odoc
2323

24-
$ odoc html-generate --source main.ml --indent -o html impl-main.odocl
24+
$ odoc html-generate-impl --source main.ml --indent -o html impl-main.odocl
2525
$ odoc html-generate --indent -o html main.odocl
26-
$ odoc html-generate --source a.ml --indent -o html impl-main__A.odocl
26+
$ odoc html-generate-impl --source a.ml --indent -o html impl-main__A.odocl
2727
$ odoc html-generate --hidden --indent -o html main__A.odocl
28-
$ odoc html-generate --source b.ml --indent -o html impl-main__B.odocl
28+
$ odoc html-generate-impl --source b.ml --indent -o html impl-main__B.odocl
2929
$ odoc html-generate --hidden --indent -o html main__B.odocl
3030

3131
Look if all the source files are generated:

test/sources/recursive_module.t/run.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ Checking that source links exists inside recursive modules.
66
$ odoc link -I . impl-main.odoc
77
$ odoc link -I . main.odoc
88
$ odoc html-generate --indent -o html main.odocl
9-
$ odoc html-generate --source main.ml --indent -o html impl-main.odocl
9+
$ odoc html-generate-impl --source main.ml --indent -o html impl-main.odocl
1010

1111
Both modules should contain source links
1212

0 commit comments

Comments
 (0)