Skip to content

Commit

Permalink
Change echo to be variadic
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Jun 5, 2018
1 parent 23beadf commit a2f7e64
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 9 deletions.
20 changes: 13 additions & 7 deletions src/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ struct
; cstr "ignore-stderr" (t @> nil) (fun t -> Ignore (Stderr, t))
; cstr "ignore-outputs" (t @> nil) (fun t -> Ignore (Outputs, t))
; cstr "progn" (rest t) (fun l -> Progn l)
; cstr "echo" (string @> nil) (fun x -> Echo x)
; cstr "echo" (string @> rest string) (fun x xs -> Echo (x::xs))
; cstr "cat" (path @> nil) (fun x -> Cat x)
; cstr "copy" (path @> path @> nil) (fun src dst -> Copy (src, dst))
(*
Expand Down Expand Up @@ -78,7 +78,8 @@ struct
]
| Progn l -> List (Sexp.unsafe_atom_of_string "progn"
:: List.map l ~f:sexp_of_t)
| Echo x -> List [Sexp.unsafe_atom_of_string "echo"; string x]
| Echo xs ->
List (Sexp.unsafe_atom_of_string "echo" :: List.map xs ~f:string)
| Cat x -> List [Sexp.unsafe_atom_of_string "cat"; path x]
| Copy (x, y) ->
List [Sexp.unsafe_atom_of_string "copy"; path x; path y]
Expand Down Expand Up @@ -150,7 +151,7 @@ module Make_mapper
| Ignore (outputs, t) ->
Ignore (outputs, map t ~dir ~f_program ~f_string ~f_path)
| Progn l -> Progn (List.map l ~f:(fun t -> map t ~dir ~f_program ~f_string ~f_path))
| Echo x -> Echo (f_string ~dir x)
| Echo xs -> Echo (List.map xs ~f:(f_string ~dir))
| Cat x -> Cat (f_path ~dir x)
| Copy (x, y) -> Copy (f_path ~dir x, f_path ~dir y)
| Symlink (x, y) ->
Expand Down Expand Up @@ -365,7 +366,7 @@ module Unexpanded = struct
| Ignore (outputs, t) ->
Ignore (outputs, expand t ~dir ~map_exe ~f)
| Progn l -> Progn (List.map l ~f:(fun t -> expand t ~dir ~map_exe ~f))
| Echo x -> Echo (E.string ~dir ~f x)
| Echo xs -> Echo (List.map xs ~f:(E.string ~dir ~f))
| Cat x -> Cat (E.path ~dir ~f x)
| Copy (x, y) ->
Copy (E.path ~dir ~f x, E.path ~dir ~f y)
Expand Down Expand Up @@ -457,7 +458,7 @@ module Unexpanded = struct
| Ignore (outputs, t) ->
Ignore (outputs, partial_expand t ~dir ~map_exe ~f)
| Progn l -> Progn (List.map l ~f:(fun t -> partial_expand t ~dir ~map_exe ~f))
| Echo x -> Echo (E.string ~dir ~f x)
| Echo xs -> Echo (List.map xs ~f:(E.string ~dir ~f))
| Cat x -> Cat (E.path ~dir ~f x)
| Copy (x, y) ->
Copy (E.path ~dir ~f x, E.path ~dir ~f y)
Expand Down Expand Up @@ -674,6 +675,11 @@ let exec_echo stdout_to str =
| None -> print_string str; flush stdout
| Some (_, oc) -> output_string oc str)

let concat = function
| [] -> ""
| [x] -> x
| xs -> String.concat ~sep:"" xs

let rec exec t ~ectx ~dir ~env ~stdout_to ~stderr_to =
match t with
| Run (Error e, _) ->
Expand All @@ -686,7 +692,7 @@ let rec exec t ~ectx ~dir ~env ~stdout_to ~stderr_to =
exec t ~ectx ~dir ~stdout_to ~stderr_to
~env:(Env.add env ~var ~value)
| Redirect (Stdout, fn, Echo s) ->
Io.write_file fn s;
Io.write_file fn (concat s);
Fiber.return ()
| Redirect (outputs, fn, Run (Ok prog, args)) ->
let out = Process.File fn in
Expand All @@ -703,7 +709,7 @@ let rec exec t ~ectx ~dir ~env ~stdout_to ~stderr_to =
redirect ~ectx ~dir outputs Config.dev_null t ~env ~stdout_to ~stderr_to
| Progn l ->
exec_list l ~ectx ~dir ~env ~stdout_to ~stderr_to
| Echo str -> exec_echo stdout_to str
| Echo strs -> exec_echo stdout_to (concat strs)
| Cat fn ->
Io.with_file_in fn ~f:(fun ic ->
let oc =
Expand Down
4 changes: 2 additions & 2 deletions src/action_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ module type Ast = sig
| Redirect of Outputs.t * path * t
| Ignore of Outputs.t * t
| Progn of t list
| Echo of string
| Echo of string list
| Cat of path
| Copy of path * path
| Symlink of path * path
Expand Down Expand Up @@ -61,7 +61,7 @@ module type Helpers = sig
val ignore_stderr : t -> t
val ignore_outputs : t -> t
val progn : t list -> t
val echo : string -> t
val echo : string list -> t
val cat : path -> t
val copy : path -> path -> t
val symlink : path -> path -> t
Expand Down

0 comments on commit a2f7e64

Please sign in to comment.