File tree Expand file tree Collapse file tree 7 files changed +22
-25
lines changed Expand file tree Collapse file tree 7 files changed +22
-25
lines changed Original file line number Diff line number Diff line change
1
+ open Odoc_utils
1
2
open Or_error
2
3
3
4
let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input =
@@ -47,11 +48,8 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input =
47
48
Odoc_html.Generator. items ~config ~resolve: (Base xref_base_uri)
48
49
(page.Odoc_document.Types.Page. preamble @ page.items)
49
50
in
50
- let oc = open_out (Fs.File. to_string output) in
51
- let fmt = Format. formatter_of_out_channel oc in
52
-
51
+ Io_utils. with_formatter_out (Fs.File. to_string output) @@ fun fmt ->
53
52
Format. fprintf fmt " %a@." (Format. pp_print_list (Tyxml.Html. pp_elt () )) html;
54
- close_out oc;
55
53
Ok ()
56
54
in
57
55
match Fs.File. read input with
Original file line number Diff line number Diff line change @@ -24,11 +24,8 @@ let parse_input_files input =
24
24
>> = fun files -> Ok (List. concat files)
25
25
26
26
let compile_to_json ~output ~occurrences ~wrap ~simplified hierarchies =
27
- let output_channel =
28
- Fs.Directory. mkdir_p (Fs.File. dirname output);
29
- open_out_bin (Fs.File. to_string output)
30
- in
31
- let output = Format. formatter_of_out_channel output_channel in
27
+ Fs.Directory. mkdir_p (Fs.File. dirname output);
28
+ Io_utils. with_formatter_out (Fs.File. to_string output) @@ fun output ->
32
29
if wrap then Format. fprintf output " let documents = " ;
33
30
let all =
34
31
List. fold_left
Original file line number Diff line number Diff line change @@ -34,9 +34,9 @@ let magic = "odoc-%%VERSION%%"
34
34
(* * Exceptions while saving are allowed to leak. *)
35
35
let save_ file f =
36
36
Fs.Directory. mkdir_p (Fs.File. dirname file);
37
- let oc = open_out_bin (Fs.File. to_string file) in
38
- output_string oc magic;
39
- Fun. protect ~finally: ( fun () -> close_out oc) ( fun () -> f oc)
37
+ Io_utils. with_open_out_bin (Fs.File. to_string file) ( fun oc ->
38
+ output_string oc magic;
39
+ f oc)
40
40
41
41
let save_unit file (root : Root.t ) (t : t ) =
42
42
save_ file (fun oc ->
Original file line number Diff line number Diff line change
1
+ open Odoc_utils
1
2
open Odoc_document
2
3
open Or_error
3
4
open Odoc_model
@@ -53,10 +54,8 @@ let render_document renderer ~sidebar ~output:root_dir ~extra_suffix ~extra doc
53
54
let pages = renderer.Renderer. render extra sidebar doc in
54
55
Renderer. traverse pages ~f: (fun filename content ->
55
56
let filename = prepare ~extra_suffix ~output_dir: root_dir filename in
56
- let oc = open_out (Fs.File. to_string filename) in
57
- let fmt = Format. formatter_of_out_channel oc in
58
- Format. fprintf fmt " %t@?" content;
59
- close_out oc)
57
+ Io_utils. with_formatter_out (Fs.File. to_string filename) @@ fun fmt ->
58
+ Format. fprintf fmt " %t@?" content)
60
59
61
60
let render_odoc ~resolver ~warnings_options ~syntax ~renderer ~output extra file
62
61
=
Original file line number Diff line number Diff line change @@ -4,12 +4,9 @@ open Odoc_utils
4
4
let compile_to_json ~output sidebar =
5
5
let json = Odoc_html.Sidebar. to_json sidebar in
6
6
let text = Json. to_string json in
7
- let output_channel =
8
- Fs.Directory. mkdir_p (Fs.File. dirname output);
9
- open_out_bin (Fs.File. to_string output)
10
- in
11
- Fun. protect ~finally: (fun () -> close_out output_channel) @@ fun () ->
12
- Printf. fprintf output_channel " %s" text
7
+ Fs.Directory. mkdir_p (Fs.File. dirname output);
8
+ Io_utils. with_open_out_bin (Fs.File. to_string output) @@ fun oc ->
9
+ Printf. fprintf oc " %s" text
13
10
14
11
let generate ~marshall ~output ~warnings_options :_ ~index =
15
12
Odoc_file. load_index index >> = fun index ->
Original file line number Diff line number Diff line change
1
+ open Odoc_utils
2
+
1
3
let should_include ~without_theme file =
2
4
if without_theme then
3
5
match file with
@@ -25,9 +27,7 @@ let write =
25
27
let dir = Fs.File. dirname name in
26
28
Fs.Directory. mkdir_p dir;
27
29
let name = Fs.File. to_string name in
28
- let channel = open_out name in
29
- output_string channel content;
30
- close_out channel)
30
+ Io_utils. with_open_out name (fun oc -> output_string oc content))
31
31
32
32
let print_filenames =
33
33
iter_files (fun name _content -> print_endline (Fs.File. to_string name))
Original file line number Diff line number Diff line change @@ -101,9 +101,15 @@ module Io_utils = struct
101
101
let read_lines fname =
102
102
List. rev (fold_lines fname (fun line acc -> line :: acc) [] )
103
103
104
+ let with_open_out fname f =
105
+ _with_resource (open_out fname) ~close: close_out_noerr f
106
+
104
107
let with_open_out_bin fname f =
105
108
_with_resource (open_out_bin fname) ~close: close_out_noerr f
106
109
110
+ let with_formatter_out fname f =
111
+ with_open_out fname (fun oc -> f (Format. formatter_of_out_channel oc))
112
+
107
113
let marshal fname v =
108
114
_with_resource (open_out_bin fname) ~close: close_out_noerr (fun oc ->
109
115
Marshal. to_channel oc v [] )
You can’t perform that action at this time.
0 commit comments