Skip to content

Commit

Permalink
Artifact_substitution.copy: return a boolean
Browse files Browse the repository at this point in the history
Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Oct 14, 2022
1 parent bc0a0c3 commit b02b6f6
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 22 deletions.
35 changes: 18 additions & 17 deletions src/dune_rules/artifact_substitution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -417,14 +417,13 @@ let buf_len = max_len

let buf = Bytes.create buf_len

type _ mode =
| Test : bool mode
| Copy :
type mode =
| Test
| Copy of
{ input_file : Path.t
; output : bytes -> int -> int -> unit
; conf : conf
}
-> unit mode

(** The copy algorithm works as follow:
Expand Down Expand Up @@ -464,10 +463,10 @@ output the replacement | |
| |
\--------------------------------------------------------------------------/
v} *)
let parse : type a. input:_ -> mode:a mode -> a Fiber.t =
fun ~input ~mode ->
let parse ~input ~mode =
let open Fiber.O in
let rec loop scanner_state ~beginning_of_data ~pos ~end_of_data : a Fiber.t =
let rec loop scanner_state ~beginning_of_data ~pos ~end_of_data ~has_seen_subs
=
let scanner_state = Scanner.run scanner_state ~buf ~pos ~end_of_data in
let placeholder_start =
match scanner_state with
Expand Down Expand Up @@ -509,13 +508,14 @@ let parse : type a. input:_ -> mode:a mode -> a Fiber.t =
let s = encode_replacement ~len ~repl:s in
output (Bytes.unsafe_of_string s) 0 len;
let pos = placeholder_start + len in
loop Scan0 ~beginning_of_data:pos ~pos ~end_of_data)
loop Scan0 ~beginning_of_data:pos ~pos ~end_of_data
~has_seen_subs:true)
| None ->
(* Restart just after [prefix] since we know for sure that a placeholder
cannot start before that. *)
loop Scan0 ~beginning_of_data:placeholder_start
~pos:(placeholder_start + prefix_len)
~end_of_data)
~end_of_data ~has_seen_subs)
| scanner_state -> (
(* We reached the end of the buffer: move the leftover data back to the
beginning of [buf] and refill the buffer *)
Expand All @@ -538,24 +538,23 @@ let parse : type a. input:_ -> mode:a mode -> a Fiber.t =
(* There might still be another placeholder after this invalid one
with a length that is too long *)
loop Scan0 ~beginning_of_data:0 ~pos:prefix_len ~end_of_data:leftover
~has_seen_subs
| _ -> (
match mode with
| Test -> Fiber.return false
| Copy { output; _ } ->
(* Nothing more to read; [leftover] is definitely not the beginning
of a placeholder, send it and end the copy *)
output buf 0 leftover;
Fiber.return ()))
Fiber.return has_seen_subs))
| n ->
loop scanner_state ~beginning_of_data:0 ~pos:leftover
~end_of_data:(leftover + n))
~end_of_data:(leftover + n) ~has_seen_subs)
in
match input buf 0 buf_len with
| 0 -> (
match mode with
| Test -> Fiber.return false
| Copy _ -> Fiber.return ())
| n -> loop Scan0 ~beginning_of_data:0 ~pos:0 ~end_of_data:n
| 0 -> Fiber.return false
| n ->
loop Scan0 ~beginning_of_data:0 ~pos:0 ~end_of_data:n ~has_seen_subs:false

let copy ~conf ~input_file ~input ~output =
parse ~input ~mode:(Copy { conf; input_file; output })
Expand Down Expand Up @@ -612,7 +611,9 @@ let copy_file ~conf ?chmod ?(delete_dst_if_it_is_a_directory = false) ~src ~dst
Fiber.finalize
(fun () ->
let open Fiber.O in
let* () = copy_file_non_atomic ~conf ?chmod ~src ~dst:temp_file () in
let* (_ : bool) =
copy_file_non_atomic ~conf ?chmod ~src ~dst:temp_file ()
in
let+ () = run_sign_hook conf temp_file in
replace_if_different ~delete_dst_if_it_is_a_directory ~src:temp_file ~dst)
~finally:(fun () ->
Expand Down
6 changes: 4 additions & 2 deletions src/dune_rules/artifact_substitution.mli
Original file line number Diff line number Diff line change
Expand Up @@ -72,13 +72,15 @@ val copy_file :
[output] functions from the OCaml standard library.
[input_file] is used only for debugging purposes. It must be the name of the
source file. *)
source file.
Return whether a substitution happened. *)
val copy :
conf:conf
-> input_file:Path.t
-> input:(Bytes.t -> int -> int -> int)
-> output:(Bytes.t -> int -> int -> unit)
-> unit Fiber.t
-> bool Fiber.t

(** Produce the string that would replace the placeholder with the given value .*)
val encode_replacement : len:int -> repl:string -> string
Expand Down
10 changes: 7 additions & 3 deletions test/unit-tests/artifact_substitution/artifact_substitution.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ let test input =
Fiber.run
~iter:(fun () -> assert false)
(let ofs = ref 0 in
let open Fiber.O in
let input buf pos len =
let to_copy = min len (String.length input - !ofs) in
Bytes.blit_string ~src:input ~dst:buf ~src_pos:!ofs ~dst_pos:pos
Expand All @@ -144,9 +145,12 @@ let test input =
to_copy
in
let output = Buffer.add_subbytes buf in
Artifact_substitution.copy ~conf:Artifact_substitution.conf_dummy
~input_file:(Path.of_string "<memory>")
~input ~output);
let+ (_ : bool) =
Artifact_substitution.copy ~conf:Artifact_substitution.conf_dummy
~input_file:(Path.of_string "<memory>")
~input ~output
in
());
let result = Buffer.contents buf in
if result <> expected then
fail
Expand Down

0 comments on commit b02b6f6

Please sign in to comment.