Skip to content

Commit f41e27b

Browse files
committed
Open files lazily + close them ASAP (#1643)
Revert #1635 + implement another fix for #1633. When executing actions: - open files as late as possible - close them as soon as possible This ensures that fds stay open for the least amount of time and helps reduce the maximum number of fds opened by Dune. Signed-off-by: Rudi Grinberg <[email protected]> Signed-off-by: Jeremie Dimino <[email protected]>
1 parent bc26efc commit f41e27b

File tree

12 files changed

+166
-81
lines changed

12 files changed

+166
-81
lines changed

CHANGES.md

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,9 +7,13 @@
77
- Fix preprocessing for libraries with `(include_subdirs ..)` (#1624, fix #1626,
88
@nojb, @rgrinberg)
99

10-
- Delay opening redirected output files until executing commands in
11-
order to reduce the number of maximum number of open file
12-
descriptors (#1635, fixes #1633, @jonludlam)
10+
- Do not generate targets for archive that don't match the `modes` field.
11+
(#1632, fix #1617, @rgrinberg)
12+
13+
- When executing actions, open files lazily and close them as soon as
14+
possible in order to reduce the maximum number of file descriptors
15+
opened by Dune (#1635, #1643, fixes #1633, @jonludlam, @rgrinberg,
16+
@diml)
1317

1418
1.6.2 (05/12/2018)
1519
------------------

src/action_exec.ml

Lines changed: 12 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,7 @@ type exec_context =
77
; purpose : Process.purpose
88
}
99

10-
let get_std_output : _ -> Process.std_output_to = function
11-
| None -> Terminal
12-
| Some fn -> File fn
13-
14-
let exec_run_direct ~ectx ~dir ~env ~stdout_to ~stderr_to prog args =
10+
let exec_run ~ectx ~dir ~env ~stdout_to ~stderr_to prog args =
1511
begin match ectx.context with
1612
| None
1713
| Some { Context.for_host = None; _ } -> ()
@@ -31,16 +27,8 @@ let exec_run_direct ~ectx ~dir ~env ~stdout_to ~stderr_to prog args =
3127
~purpose:ectx.purpose
3228
prog args
3329

34-
let exec_run ~stdout_to ~stderr_to =
35-
let stdout_to = get_std_output stdout_to in
36-
let stderr_to = get_std_output stderr_to in
37-
exec_run_direct ~stdout_to ~stderr_to
38-
3930
let exec_echo stdout_to str =
40-
Fiber.return
41-
(match stdout_to with
42-
| None -> print_string str; flush stdout
43-
| Some fn -> Io.write_file fn str)
31+
Fiber.return (output_string (Process.Output.channel stdout_to) str)
4432

4533
let rec exec t ~ectx ~dir ~env ~stdout_to ~stderr_to =
4634
match (t : Action.t) with
@@ -65,9 +53,7 @@ let rec exec t ~ectx ~dir ~env ~stdout_to ~stderr_to =
6553
| Echo strs -> exec_echo stdout_to (String.concat strs ~sep:" ")
6654
| Cat fn ->
6755
Io.with_file_in fn ~f:(fun ic ->
68-
match stdout_to with
69-
| None -> Io.copy_channels ic stdout
70-
| Some fn -> Io.with_file_out fn ~f:(fun oc -> Io.copy_channels ic oc));
56+
Io.copy_channels ic (Process.Output.channel stdout_to));
7157
Fiber.return ()
7258
| Copy (src, dst) ->
7359
Io.copy_file ~src ~dst ();
@@ -179,16 +165,15 @@ let rec exec t ~ectx ~dir ~env ~stdout_to ~stderr_to =
179165
Fiber.return ()
180166

181167
and redirect outputs fn t ~ectx ~dir ~env ~stdout_to ~stderr_to =
182-
(* We resolve the path to an absolute one here to ensure no
183-
Chdir actions change the eventual path of the file *)
184-
let out = Some (Path.to_absolute fn) in
168+
let out = Process.Output.file fn in
185169
let stdout_to, stderr_to =
186170
match outputs with
187171
| Stdout -> (out, stderr_to)
188172
| Stderr -> (stdout_to, out)
189173
| Outputs -> (out, out)
190174
in
191-
exec t ~ectx ~dir ~env ~stdout_to ~stderr_to
175+
exec t ~ectx ~dir ~env ~stdout_to ~stderr_to >>| fun () ->
176+
Process.Output.release out
192177

193178
and exec_list l ~ectx ~dir ~env ~stdout_to ~stderr_to =
194179
match l with
@@ -197,7 +182,9 @@ and exec_list l ~ectx ~dir ~env ~stdout_to ~stderr_to =
197182
| [t] ->
198183
exec t ~ectx ~dir ~env ~stdout_to ~stderr_to
199184
| t :: rest ->
200-
exec t ~ectx ~dir ~env ~stdout_to ~stderr_to >>= fun () ->
185+
(let stdout_to = Process.Output.multi_use stdout_to in
186+
let stderr_to = Process.Output.multi_use stderr_to in
187+
exec t ~ectx ~dir ~env ~stdout_to ~stderr_to) >>= fun () ->
201188
exec_list rest ~ectx ~dir ~env ~stdout_to ~stderr_to
202189

203190
let exec ~targets ~context ~env t =
@@ -209,4 +196,6 @@ let exec ~targets ~context ~env t =
209196
in
210197
let purpose = Process.Build_job targets in
211198
let ectx = { purpose; context } in
212-
exec t ~ectx ~dir:Path.root ~env ~stdout_to:None ~stderr_to:None
199+
exec t ~ectx ~dir:Path.root ~env
200+
~stdout_to:Process.Output.stdout
201+
~stderr_to:Process.Output.stderr

src/build.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -249,7 +249,7 @@ let symlink ~src ~dst =
249249
action ~targets:[dst] (Symlink (src, dst))
250250

251251
let create_file fn =
252-
action ~targets:[fn] (Redirect (Stdout, fn, Echo []))
252+
action ~targets:[fn] (Redirect (Stdout, fn, Progn []))
253253

254254
let remove_tree dir =
255255
arr (fun _ -> Action.Remove_tree dir)

src/main.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,7 @@ let auto_concurrency =
144144
| None -> loop rest
145145
| Some prog ->
146146
Process.run_capture (Accept All) prog args ~env:Env.initial
147-
~stderr_to:(File Config.dev_null)
147+
~stderr_to:(Process.Output.file Config.dev_null)
148148
>>= function
149149
| Error _ -> loop rest
150150
| Ok s ->

src/process.ml

Lines changed: 96 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -30,9 +30,67 @@ let map_result
3030
| 0 -> Ok (f ())
3131
| n -> Error n
3232

33-
type std_output_to =
34-
| Terminal
35-
| File of Path.t
33+
module Output = struct
34+
type t =
35+
{ kind : kind
36+
; fd : Unix.file_descr Lazy.t
37+
; channel : out_channel Lazy.t
38+
; mutable status : status
39+
}
40+
41+
and kind =
42+
| File of Path.t
43+
| Terminal
44+
45+
and status =
46+
| Keep_open
47+
| Close_after_exec
48+
| Closed
49+
50+
let terminal oc =
51+
let fd = Unix.descr_of_out_channel oc in
52+
{ kind = Terminal
53+
; fd = lazy fd
54+
; channel = lazy stdout
55+
; status = Keep_open
56+
}
57+
let stdout = terminal stdout
58+
let stderr = terminal stderr
59+
60+
let file fn =
61+
let fd =
62+
lazy (Unix.openfile (Path.to_string fn)
63+
[O_WRONLY; O_CREAT; O_TRUNC; O_SHARE_DELETE] 0o666)
64+
in
65+
{ kind = File fn
66+
; fd
67+
; channel = lazy (Unix.out_channel_of_descr (Lazy.force fd))
68+
; status = Close_after_exec
69+
}
70+
71+
let flush t =
72+
if Lazy.is_val t.channel then flush (Lazy.force t.channel)
73+
74+
let fd t =
75+
flush t;
76+
Lazy.force t.fd
77+
78+
let channel t = Lazy.force t.channel
79+
80+
let release t =
81+
match t.status with
82+
| Closed -> ()
83+
| Keep_open -> flush t
84+
| Close_after_exec ->
85+
t.status <- Closed;
86+
if Lazy.is_val t.channel then
87+
close_out (Lazy.force t.channel)
88+
else
89+
Unix.close (Lazy.force t.fd)
90+
91+
let multi_use t =
92+
{ t with status = Keep_open }
93+
end
3694

3795
type purpose =
3896
| Internal_job
@@ -101,7 +159,8 @@ module Fancy = struct
101159
"-o" :: Colors.(apply_string output_filename) fn :: colorize_args rest
102160
| x :: rest -> x :: colorize_args rest
103161

104-
let command_line ~prog ~args ~dir ~stdout_to ~stderr_to =
162+
let command_line ~prog ~args ~dir
163+
~(stdout_to:Output.t) ~(stderr_to:Output.t) =
105164
let prog = Path.reach_for_running ?from:dir prog in
106165
let quote = quote_for_shell in
107166
let prog = colorize_prog (quote prog) in
@@ -113,17 +172,17 @@ module Fancy = struct
113172
| None -> s
114173
| Some dir -> sprintf "(cd %s && %s)" (Path.to_string dir) s
115174
in
116-
match stdout_to, stderr_to with
175+
match stdout_to.kind, stderr_to.kind with
117176
| File fn1, File fn2 when Path.equal fn1 fn2 ->
118177
sprintf "%s &> %s" s (Path.to_string fn1)
119178
| _ ->
120179
let s =
121-
match stdout_to with
180+
match stdout_to.kind with
122181
| Terminal -> s
123182
| File fn ->
124183
sprintf "%s > %s" s (Path.to_string fn)
125184
in
126-
match stderr_to with
185+
match stderr_to.kind with
127186
| Terminal -> s
128187
| File fn ->
129188
sprintf "%s 2> %s" s (Path.to_string fn)
@@ -179,17 +238,6 @@ module Fancy = struct
179238
contexts;
180239
end
181240

182-
let get_std_output ~default = function
183-
| Terminal -> (default, None)
184-
| File fn ->
185-
let fd = Unix.openfile (Path.to_string fn)
186-
[O_WRONLY; O_CREAT; O_TRUNC; O_SHARE_DELETE] 0o666 in
187-
(fd, Some fd)
188-
189-
let close_std_output = function
190-
| None -> ()
191-
| Some fd -> Unix.close fd
192-
193241
let gen_id =
194242
let next = ref (-1) in
195243
fun () -> incr next; !next
@@ -198,8 +246,8 @@ let cmdline_approximate_length prog args =
198246
List.fold_left args ~init:(String.length prog) ~f:(fun acc arg ->
199247
acc + String.length arg)
200248

201-
let run_internal ?dir ?(stdout_to=Terminal) ?(stderr_to=Terminal) ~env ~purpose
202-
fail_mode prog args =
249+
let run_internal ?dir ?(stdout_to=Output.stdout) ?(stderr_to=Output.stderr)
250+
~env ~purpose fail_mode prog args =
203251
Scheduler.wait_for_available_job ()
204252
>>= fun scheduler ->
205253
let display = Scheduler.display scheduler in
@@ -234,33 +282,43 @@ let run_internal ?dir ?(stdout_to=Terminal) ?(stderr_to=Terminal) ~env ~purpose
234282
(args, None)
235283
in
236284
let argv = prog_str :: args in
237-
let output_filename, stdout_fd, stderr_fd, to_close =
238-
match stdout_to, stderr_to with
285+
let output_filename, stdout_to, stderr_to =
286+
match stdout_to.kind, stderr_to.kind with
239287
| (Terminal, _ | _, Terminal) when !Clflags.capture_outputs ->
240288
let fn = Temp.create "dune" ".output" in
241-
let fd = Unix.openfile (Path.to_string fn) [O_WRONLY; O_SHARE_DELETE] 0 in
242-
(Some fn, fd, fd, Some fd)
289+
let terminal = Output.file fn in
290+
let get (out : Output.t) =
291+
if out.kind = Terminal then begin
292+
Output.flush out;
293+
terminal
294+
end else
295+
out
296+
in
297+
(Some fn, get stdout_to, get stderr_to)
243298
| _ ->
244-
(None, Unix.stdout, Unix.stderr, None)
299+
(None, stdout_to, stderr_to)
245300
in
246-
let stdout, close_stdout = get_std_output stdout_to ~default:stdout_fd in
247-
let stderr, close_stderr = get_std_output stderr_to ~default:stderr_fd in
248-
let run () =
249-
Spawn.spawn ()
250-
~prog:prog_str
251-
~argv
252-
~env:(Spawn.Env.of_array (Env.to_unix env))
253-
~stdout
254-
~stderr
301+
let run =
302+
(* Output.fd might create the file with Unix.openfile. We need to
303+
make sure to call it before doing the chdir as the path might
304+
be relative. *)
305+
let stdout = Output.fd stdout_to in
306+
let stderr = Output.fd stderr_to in
307+
fun () ->
308+
Spawn.spawn ()
309+
~prog:prog_str
310+
~argv
311+
~env:(Spawn.Env.of_array (Env.to_unix env))
312+
~stdout
313+
~stderr
255314
in
256315
let pid =
257316
match dir with
258317
| None -> run ()
259318
| Some dir -> Scheduler.with_chdir scheduler ~dir ~f:run
260319
in
261-
Option.iter to_close ~f:Unix.close;
262-
close_std_output close_stdout;
263-
close_std_output close_stderr;
320+
Output.release stdout_to;
321+
Output.release stderr_to;
264322
Scheduler.wait_for_process pid
265323
>>| fun exit_status ->
266324
Option.iter response_file ~f:Path.unlink;
@@ -334,7 +392,7 @@ let run_capture_gen ?dir ?stderr_to ~env ?(purpose=Internal_job) fail_mode
334392
prog args ~f =
335393
let fn = Temp.create "dune" ".output" in
336394
map_result fail_mode
337-
(run_internal ?dir ~stdout_to:(File fn) ?stderr_to
395+
(run_internal ?dir ~stdout_to:(Output.file fn) ?stderr_to
338396
~env ~purpose fail_mode prog args)
339397
~f:(fun () ->
340398
let x = f fn in

src/process.mli

Lines changed: 27 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,28 @@ type ('a, 'b) failure_mode =
1414
(** Accept the following non-zero exit codes, and return [Error
1515
code] if the process exists with one of these codes. *)
1616

17-
(** Where to redirect standard output *)
18-
type std_output_to =
19-
| Terminal
20-
| File of Path.t
17+
module Output : sig
18+
(** Where to redirect stdout/stderr *)
19+
type t
20+
21+
val stdout : t
22+
val stderr : t
23+
24+
(** Create a [t] representing redirecting the output to a file. The
25+
returned output can only be used by a single call to {!run}. If
26+
you want to use it multiple times, you need to use [clone]. *)
27+
val file : Path.t -> t
28+
29+
(** Call this when you no longer need this output *)
30+
val release : t -> unit
31+
32+
(** Return a buffered channel for this output. The channel is
33+
created lazily. *)
34+
val channel : t -> out_channel
35+
36+
(** [multi_use t] returns a copy for which [release] does nothing *)
37+
val multi_use : t -> t
38+
end
2139

2240
(** Why a Fiber.t was run *)
2341
type purpose =
@@ -27,8 +45,8 @@ type purpose =
2745
(** [run ?dir ?stdout_to prog args] spawns a sub-process and wait for its termination *)
2846
val run
2947
: ?dir:Path.t
30-
-> ?stdout_to:std_output_to
31-
-> ?stderr_to:std_output_to
48+
-> ?stdout_to:Output.t
49+
-> ?stderr_to:Output.t
3250
-> env:Env.t
3351
-> ?purpose:purpose
3452
-> (unit, 'a) failure_mode
@@ -39,7 +57,7 @@ val run
3957
(** Run a command and capture its output *)
4058
val run_capture
4159
: ?dir:Path.t
42-
-> ?stderr_to:std_output_to
60+
-> ?stderr_to:Output.t
4361
-> env:Env.t
4462
-> ?purpose:purpose
4563
-> (string, 'a) failure_mode
@@ -48,7 +66,7 @@ val run_capture
4866
-> 'a Fiber.t
4967
val run_capture_line
5068
: ?dir:Path.t
51-
-> ?stderr_to:std_output_to
69+
-> ?stderr_to:Output.t
5270
-> env:Env.t
5371
-> ?purpose:purpose
5472
-> (string, 'a) failure_mode
@@ -57,11 +75,10 @@ val run_capture_line
5775
-> 'a Fiber.t
5876
val run_capture_lines
5977
: ?dir:Path.t
60-
-> ?stderr_to:std_output_to
78+
-> ?stderr_to:Output.t
6179
-> env:Env.t
6280
-> ?purpose:purpose
6381
-> (string list, 'a) failure_mode
6482
-> Path.t
6583
-> string list
6684
-> 'a Fiber.t
67-

0 commit comments

Comments
 (0)