Skip to content

Commit ffd9ec7

Browse files
committed
Remove generation of implementation using html-generate
1 parent 1ec6b2c commit ffd9ec7

File tree

3 files changed

+45
-86
lines changed

3 files changed

+45
-86
lines changed

src/odoc/bin/main.ml

Lines changed: 7 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -38,14 +38,6 @@ let convert_fpath =
3838
and print = Fpath.pp in
3939
Arg.conv (parse, print)
4040

41-
let convert_src_fpath =
42-
let parse inp =
43-
match Arg.(conv_parser file) inp with
44-
| Ok s -> Result.Ok (Fs.File.of_string s)
45-
| Error _ as e -> e
46-
and print = Fpath.pp in
47-
Arg.conv (parse, print)
48-
4941
let convert_named_root =
5042
let parse inp =
5143
match Astring.String.cuts inp ~sep:":" with
@@ -831,20 +823,10 @@ end = struct
831823

832824
module Generate = struct
833825
let generate extra _hidden output_dir syntax extra_suffix input_file
834-
warnings_options source_file sidebar =
826+
warnings_options sidebar =
835827
let file = Fs.File.of_string input_file in
836828
Rendering.generate_odoc ~renderer:R.renderer ~warnings_options ~syntax
837-
~output:output_dir ~extra_suffix ~source_file ~sidebar extra file
838-
839-
let source_file =
840-
let doc =
841-
"(EXPERIMENTAL) Source code for the compilation unit. It must have \
842-
been compiled with --source-parent passed."
843-
in
844-
Arg.(
845-
value
846-
& opt (some convert_src_fpath) None
847-
& info [ "source" ] ~doc ~docv:"file.ml")
829+
~output:output_dir ~extra_suffix ~sidebar extra file
848830

849831
let sidebar =
850832
let doc = "A .odoc-index file, used eg to generate the sidebar." in
@@ -865,8 +847,7 @@ end = struct
865847
Term.(
866848
const handle_error
867849
$ (const generate $ R.extra_args $ hidden $ dst ~create:true () $ syntax
868-
$ extra_suffix $ input_odocl $ warnings_options $ source_file $ sidebar
869-
))
850+
$ extra_suffix $ input_odocl $ warnings_options $ sidebar))
870851

871852
let info ~docs =
872853
let doc =
@@ -878,7 +859,7 @@ end = struct
878859
let generate ~docs = Generate.(cmd, info ~docs)
879860

880861
module Targets = struct
881-
let list_targets output_dir directories source_file extra odoc_file =
862+
let list_targets output_dir directories extra odoc_file =
882863
let odoc_file = Fs.File.of_string odoc_file in
883864
let resolver =
884865
Resolver.create ~important_digests:false ~directories ~open_modules:[]
@@ -888,7 +869,7 @@ end = struct
888869
{ Odoc_model.Error.warn_error = false; print_warnings = false }
889870
in
890871
Rendering.targets_odoc ~resolver ~warnings_options ~syntax:OCaml
891-
~renderer:R.renderer ~output:output_dir ~extra ~source_file odoc_file
872+
~renderer:R.renderer ~output:output_dir ~extra odoc_file
892873

893874
let back_compat =
894875
let doc =
@@ -900,13 +881,11 @@ end = struct
900881
& opt_all (convert_directory ()) []
901882
& info ~docs ~docv:"DIR" ~doc [ "I" ])
902883

903-
let source_file = Generate.source_file
904-
905884
let cmd =
906885
Term.(
907886
const handle_error
908-
$ (const list_targets $ dst () $ back_compat $ source_file
909-
$ R.extra_args $ input_odocl))
887+
$ (const list_targets $ dst () $ back_compat $ R.extra_args
888+
$ input_odocl))
910889

911890
let info ~docs =
912891
let doc =

src/odoc/rendering.ml

Lines changed: 38 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -2,78 +2,63 @@ open Odoc_document
22
open Or_error
33
open Odoc_model
44

5-
let check_empty_source_arg source filename =
6-
if source <> None then
7-
Error.raise_warning
8-
@@ Error.filename_only
9-
"--source and --source-root only have an effect when generating from \
10-
an implementation"
11-
filename
12-
13-
let documents_of_unit ~warnings_options ~syntax ~source ~renderer ~extra
14-
~filename unit =
5+
let documents_of_unit ~warnings_options ~syntax ~renderer ~extra unit =
156
Error.catch_warnings (fun () ->
16-
check_empty_source_arg source filename;
177
renderer.Renderer.extra_documents extra (CU unit))
188
|> Error.handle_warnings ~warnings_options
199
>>= fun extra_docs ->
2010
Ok (Renderer.document_of_compilation_unit ~syntax unit :: extra_docs)
2111

22-
let documents_of_page ~warnings_options ~syntax ~source ~renderer ~extra
23-
~filename page =
12+
let documents_of_page ~warnings_options ~syntax ~renderer ~extra page =
2413
Error.catch_warnings (fun () ->
25-
check_empty_source_arg source filename;
2614
renderer.Renderer.extra_documents extra (Page page))
2715
|> Error.handle_warnings ~warnings_options
2816
>>= fun extra_docs -> Ok (Renderer.document_of_page ~syntax page :: extra_docs)
2917

30-
let documents_of_implementation ~warnings_options:_ ~syntax impl source =
31-
match (source, impl.Lang.Implementation.id) with
32-
| Some source_file, Some _ -> (
33-
match Fs.File.read source_file with
34-
| Error (`Msg msg) ->
35-
Error (`Msg (Format.sprintf "Couldn't load source file: %s" msg))
36-
| Ok source_code ->
37-
let syntax_info =
38-
Syntax_highlighter.syntax_highlighting_locs source_code
39-
in
40-
let rendered =
41-
Odoc_document.Renderer.documents_of_implementation ~syntax impl
42-
syntax_info source_code
43-
in
44-
Ok rendered)
45-
| _, None ->
46-
Error (`Msg "The implementation unit was not compiled with --source-id.")
47-
| None, _ ->
48-
Error
49-
(`Msg
50-
"--source or --source-root should be passed when generating \
51-
documents for an implementation.")
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.") *)
5240

53-
let documents_of_odocl ~warnings_options ~renderer ~extra ~source ~syntax input
54-
=
41+
let documents_of_odocl ~warnings_options ~renderer ~extra ~syntax input =
5542
Odoc_file.load input >>= fun unit ->
56-
let filename = Fpath.to_string input in
5743
match unit.content with
5844
| Odoc_file.Page_content odoctree ->
59-
documents_of_page ~warnings_options ~syntax ~source ~renderer ~extra
60-
~filename odoctree
61-
| Impl_content impl ->
62-
documents_of_implementation ~warnings_options ~syntax impl source
45+
documents_of_page ~warnings_options ~syntax ~renderer ~extra odoctree
46+
| Impl_content _impl ->
47+
(* documents_of_implementation ~warnings_options ~syntax impl source *)
48+
failwith "TODO ERROR"
6349
| Unit_content odoctree ->
64-
documents_of_unit ~warnings_options ~source ~syntax ~renderer ~extra
65-
~filename odoctree
50+
documents_of_unit ~warnings_options ~syntax ~renderer ~extra odoctree
6651
| Asset_content _ -> Ok [] (* TODO *)
6752

6853
let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
6954
input =
7055
let output = Fs.File.(set_ext ".odocl" input) in
7156
Odoc_link.from_odoc ~resolver ~warnings_options input output >>= function
7257
| `Page page -> Ok [ Renderer.document_of_page ~syntax page ]
73-
| `Impl impl -> Ok (Renderer.documents_of_implementation ~syntax impl [] "")
74-
| `Module m ->
75-
documents_of_unit ~warnings_options ~source:None ~filename:"" ~syntax
76-
~renderer ~extra m
58+
| `Impl _impl ->
59+
(* Ok (Renderer.documents_of_implementation ~syntax impl [] "") *)
60+
failwith "TODO ERROR"
61+
| `Module m -> documents_of_unit ~warnings_options ~syntax ~renderer ~extra m
7762
| `Asset _ -> Ok [] (* TODO *)
7863

7964
let render_document renderer ~sidebar ~output:root_dir ~extra_suffix ~extra doc
@@ -115,30 +100,27 @@ let render_odoc ~resolver ~warnings_options ~syntax ~renderer ~output extra file
115100
Ok ()
116101

117102
let generate_odoc ~syntax ~warnings_options ~renderer ~output ~extra_suffix
118-
~source_file ~sidebar extra file =
103+
~sidebar extra file =
119104
(match sidebar with
120105
| None -> Ok None
121106
| Some x ->
122107
Odoc_file.load_index x >>= fun (sidebar, _) ->
123108
Ok (Some (Odoc_document.Sidebar.of_lang sidebar)))
124109
>>= fun sidebar ->
125-
documents_of_odocl ~warnings_options ~renderer ~source:source_file ~extra
126-
~syntax file
110+
documents_of_odocl ~warnings_options ~renderer ~extra ~syntax file
127111
>>= fun docs ->
128112
List.iter
129113
(render_document renderer ~output ~sidebar ~extra_suffix ~extra)
130114
docs;
131115
Ok ()
132116

133117
let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir
134-
~extra ~source_file odoctree =
118+
~extra odoctree =
135119
let docs =
136120
if Fpath.get_ext odoctree = ".odoc" then
137121
documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
138122
odoctree
139-
else
140-
documents_of_odocl ~warnings_options ~renderer ~extra ~syntax
141-
~source:source_file odoctree
123+
else documents_of_odocl ~warnings_options ~renderer ~extra ~syntax odoctree
142124
in
143125
docs >>= fun docs ->
144126
List.iter

src/odoc/rendering.mli

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ val generate_odoc :
1717
renderer:'a Renderer.t ->
1818
output:Fs.directory ->
1919
extra_suffix:string option ->
20-
source_file:Fpath.t option ->
2120
sidebar:Fpath.t option ->
2221
'a ->
2322
Fpath.t ->
@@ -30,6 +29,5 @@ val targets_odoc :
3029
renderer:'a Renderer.t ->
3130
output:Fs.directory ->
3231
extra:'a ->
33-
source_file:Fpath.t option ->
3432
Fpath.t ->
3533
(unit, [> msg ]) result

0 commit comments

Comments
 (0)