@@ -33,17 +33,6 @@ let map_result
3333type std_output_to =
3434 | Terminal
3535 | File of Path .t
36- | Opened_file of opened_file
37-
38- and opened_file =
39- { filename : Path .t
40- ; desc : opened_file_desc
41- ; tail : bool
42- }
43-
44- and opened_file_desc =
45- | Fd of Unix. file_descr
46- | Channel of out_channel
4736
4837type purpose =
4938 | Internal_job
@@ -125,19 +114,18 @@ module Fancy = struct
125114 | Some dir -> sprintf " (cd %s && %s)" (Path. to_string dir) s
126115 in
127116 match stdout_to, stderr_to with
128- | (File fn1 | Opened_file { filename = fn1; _ }),
129- (File fn2 | Opened_file { filename = fn2 ; _ } ) when Path. equal fn1 fn2 ->
117+ | File fn1 , File fn2 when Path. equal fn1 fn2 ->
130118 sprintf " %s &> %s" s (Path. to_string fn1)
131119 | _ ->
132120 let s =
133121 match stdout_to with
134122 | Terminal -> s
135- | File fn | Opened_file { filename = fn ; _ } ->
123+ | File fn ->
136124 sprintf " %s > %s" s (Path. to_string fn)
137125 in
138126 match stderr_to with
139127 | Terminal -> s
140- | File fn | Opened_file { filename = fn ; _ } ->
128+ | File fn ->
141129 sprintf " %s 2> %s" s (Path. to_string fn)
142130
143131 let pp_purpose ppf = function
@@ -196,19 +184,11 @@ let get_std_output ~default = function
196184 | File fn ->
197185 let fd = Unix. openfile (Path. to_string fn)
198186 [O_WRONLY ; O_CREAT ; O_TRUNC ; O_SHARE_DELETE ] 0o666 in
199- (fd, Some (Fd fd))
200- | Opened_file { desc; tail; _ } ->
201- let fd =
202- match desc with
203- | Fd fd -> fd
204- | Channel oc -> flush oc; Unix. descr_of_out_channel oc
205- in
206- (fd, Option. some_if tail desc)
187+ (fd, Some fd)
207188
208189let close_std_output = function
209190 | None -> ()
210- | Some (Fd fd ) -> Unix. close fd
211- | Some (Channel oc ) -> close_out oc
191+ | Some fd -> Unix. close fd
212192
213193let gen_id =
214194 let next = ref (- 1 ) in
0 commit comments