Skip to content

Commit

Permalink
Remove dead code
Browse files Browse the repository at this point in the history
Signed-off-by: Jon Ludlam <jon@recoil.org>
  • Loading branch information
jonludlam committed Dec 11, 2018
1 parent 990d111 commit f13da85
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 37 deletions.
30 changes: 5 additions & 25 deletions src/process.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,17 +33,6 @@ let map_result
type std_output_to =
| Terminal
| File of Path.t
| Opened_file of opened_file

and opened_file =
{ filename : Path.t
; desc : opened_file_desc
; tail : bool
}

and opened_file_desc =
| Fd of Unix.file_descr
| Channel of out_channel

type purpose =
| Internal_job
Expand Down Expand Up @@ -125,19 +114,18 @@ module Fancy = struct
| Some dir -> sprintf "(cd %s && %s)" (Path.to_string dir) s
in
match stdout_to, stderr_to with
| (File fn1 | Opened_file { filename = fn1; _ }),
(File fn2 | Opened_file { filename = fn2; _ }) when Path.equal fn1 fn2 ->
| File fn1, File fn2 when Path.equal fn1 fn2 ->
sprintf "%s &> %s" s (Path.to_string fn1)
| _ ->
let s =
match stdout_to with
| Terminal -> s
| File fn | Opened_file { filename = fn; _ } ->
| File fn ->
sprintf "%s > %s" s (Path.to_string fn)
in
match stderr_to with
| Terminal -> s
| File fn | Opened_file { filename = fn; _ } ->
| File fn ->
sprintf "%s 2> %s" s (Path.to_string fn)

let pp_purpose ppf = function
Expand Down Expand Up @@ -196,19 +184,11 @@ let get_std_output ~default = function
| File fn ->
let fd = Unix.openfile (Path.to_string fn)
[O_WRONLY; O_CREAT; O_TRUNC; O_SHARE_DELETE] 0o666 in
(fd, Some (Fd fd))
| Opened_file { desc; tail; _ } ->
let fd =
match desc with
| Fd fd -> fd
| Channel oc -> flush oc; Unix.descr_of_out_channel oc
in
(fd, Option.some_if tail desc)
(fd, Some fd)

let close_std_output = function
| None -> ()
| Some (Fd fd) -> Unix.close fd
| Some (Channel oc) -> close_out oc
| Some fd -> Unix.close fd

let gen_id =
let next = ref (-1) in
Expand Down
12 changes: 0 additions & 12 deletions src/process.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,18 +18,6 @@ type ('a, 'b) failure_mode =
type std_output_to =
| Terminal
| File of Path.t
| Opened_file of opened_file

and opened_file =
{ filename : Path.t
; desc : opened_file_desc
; tail : bool
(** If [true], the descriptor is closed after starting the command *)
}

and opened_file_desc =
| Fd of Unix.file_descr
| Channel of out_channel

(** Why a Fiber.t was run *)
type purpose =
Expand Down

0 comments on commit f13da85

Please sign in to comment.