@@ -2,78 +2,63 @@ open Odoc_document
2
2
open Or_error
3
3
open Odoc_model
4
4
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 =
15
6
Error. catch_warnings (fun () ->
16
- check_empty_source_arg source filename;
17
7
renderer.Renderer. extra_documents extra (CU unit ))
18
8
|> Error. handle_warnings ~warnings_options
19
9
>> = fun extra_docs ->
20
10
Ok (Renderer. document_of_compilation_unit ~syntax unit :: extra_docs)
21
11
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 =
24
13
Error. catch_warnings (fun () ->
25
- check_empty_source_arg source filename;
26
14
renderer.Renderer. extra_documents extra (Page page))
27
15
|> Error. handle_warnings ~warnings_options
28
16
>> = fun extra_docs -> Ok (Renderer. document_of_page ~syntax page :: extra_docs)
29
17
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.") * )
52
40
53
- let documents_of_odocl ~warnings_options ~renderer ~extra ~source ~syntax input
54
- =
41
+ let documents_of_odocl ~warnings_options ~renderer ~extra ~syntax input =
55
42
Odoc_file. load input >> = fun unit ->
56
- let filename = Fpath. to_string input in
57
43
match unit .content with
58
44
| 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 "
63
49
| 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
66
51
| Asset_content _ -> Ok [] (* TODO *)
67
52
68
53
let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
69
54
input =
70
55
let output = Fs.File. (set_ext " .odocl" input) in
71
56
Odoc_link. from_odoc ~resolver ~warnings_options input output >> = function
72
57
| `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
77
62
| `Asset _ -> Ok [] (* TODO *)
78
63
79
64
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
115
100
Ok ()
116
101
117
102
let generate_odoc ~syntax ~warnings_options ~renderer ~output ~extra_suffix
118
- ~source_file ~ sidebar extra file =
103
+ ~sidebar extra file =
119
104
(match sidebar with
120
105
| None -> Ok None
121
106
| Some x ->
122
107
Odoc_file. load_index x >> = fun (sidebar , _ ) ->
123
108
Ok (Some (Odoc_document.Sidebar. of_lang sidebar)))
124
109
>> = 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
127
111
>> = fun docs ->
128
112
List. iter
129
113
(render_document renderer ~output ~sidebar ~extra_suffix ~extra )
130
114
docs;
131
115
Ok ()
132
116
133
117
let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output :root_dir
134
- ~extra ~ source_file odoctree =
118
+ ~extra odoctree =
135
119
let docs =
136
120
if Fpath. get_ext odoctree = " .odoc" then
137
121
documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax
138
122
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
142
124
in
143
125
docs >> = fun docs ->
144
126
List. iter
0 commit comments