Skip to content

Commit 4838ed0

Browse files
committed
Return a status type instead of a plain bool
Signed-off-by: Etienne Millon <me@emillon.org>
1 parent df11db1 commit 4838ed0

File tree

4 files changed

+30
-19
lines changed

4 files changed

+30
-19
lines changed

bin/install_uninstall.ml

+6-3
Original file line numberDiff line numberDiff line change
@@ -696,9 +696,12 @@ let install_uninstall ~what =
696696
match special_file with
697697
| _ when not create_install_files ->
698698
Fiber.return true
699-
| None ->
700-
Dune_rules.Artifact_substitution.test_file
701-
~src:entry.src ()
699+
| None -> (
700+
let open Dune_rules.Artifact_substitution in
701+
let+ status = test_file ~src:entry.src () in
702+
match status with
703+
| Some_substitution -> true
704+
| No_substitution -> false)
702705
| Some Special_file.META
703706
| Some Special_file.Dune_package ->
704707
Fiber.return true

src/dune_rules/artifact_substitution.ml

+17-13
Original file line numberDiff line numberDiff line change
@@ -425,6 +425,10 @@ type mode =
425425
; conf : conf
426426
}
427427

428+
type status =
429+
| Some_substitution
430+
| No_substitution
431+
428432
(** The copy algorithm works as follow:
429433
430434
{v
@@ -465,8 +469,7 @@ output the replacement | |
465469
v} *)
466470
let parse ~input ~mode =
467471
let open Fiber.O in
468-
let rec loop scanner_state ~beginning_of_data ~pos ~end_of_data ~has_seen_subs
469-
=
472+
let rec loop scanner_state ~beginning_of_data ~pos ~end_of_data ~status =
470473
let scanner_state = Scanner.run scanner_state ~buf ~pos ~end_of_data in
471474
let placeholder_start =
472475
match scanner_state with
@@ -492,7 +495,7 @@ let parse ~input ~mode =
492495
match decode placeholder with
493496
| Some t -> (
494497
match mode with
495-
| Test -> Fiber.return true
498+
| Test -> Fiber.return Some_substitution
496499
| Copy { output; input_file; conf } ->
497500
let* s = eval t ~conf in
498501
(if !Clflags.debug_artifact_substitution then
@@ -509,13 +512,13 @@ let parse ~input ~mode =
509512
output (Bytes.unsafe_of_string s) 0 len;
510513
let pos = placeholder_start + len in
511514
loop Scan0 ~beginning_of_data:pos ~pos ~end_of_data
512-
~has_seen_subs:true)
515+
~status:Some_substitution)
513516
| None ->
514517
(* Restart just after [prefix] since we know for sure that a placeholder
515518
cannot start before that. *)
516519
loop Scan0 ~beginning_of_data:placeholder_start
517520
~pos:(placeholder_start + prefix_len)
518-
~end_of_data ~has_seen_subs)
521+
~end_of_data ~status)
519522
| scanner_state -> (
520523
(* We reached the end of the buffer: move the leftover data back to the
521524
beginning of [buf] and refill the buffer *)
@@ -538,23 +541,24 @@ let parse ~input ~mode =
538541
(* There might still be another placeholder after this invalid one
539542
with a length that is too long *)
540543
loop Scan0 ~beginning_of_data:0 ~pos:prefix_len ~end_of_data:leftover
541-
~has_seen_subs
544+
~status
542545
| _ -> (
543546
match mode with
544-
| Test -> Fiber.return false
547+
| Test -> Fiber.return No_substitution
545548
| Copy { output; _ } ->
546549
(* Nothing more to read; [leftover] is definitely not the beginning
547550
of a placeholder, send it and end the copy *)
548551
output buf 0 leftover;
549-
Fiber.return has_seen_subs))
552+
Fiber.return status))
550553
| n ->
551554
loop scanner_state ~beginning_of_data:0 ~pos:leftover
552-
~end_of_data:(leftover + n) ~has_seen_subs)
555+
~end_of_data:(leftover + n) ~status)
553556
in
554557
match input buf 0 buf_len with
555-
| 0 -> Fiber.return false
558+
| 0 -> Fiber.return No_substitution
556559
| n ->
557-
loop Scan0 ~beginning_of_data:0 ~pos:0 ~end_of_data:n ~has_seen_subs:false
560+
loop Scan0 ~beginning_of_data:0 ~pos:0 ~end_of_data:n
561+
~status:No_substitution
558562

559563
let copy ~conf ~input_file ~input ~output =
560564
parse ~input ~mode:(Copy { conf; input_file; output })
@@ -570,8 +574,8 @@ let copy_file_non_atomic ~conf ?chmod ~src ~dst () =
570574

571575
let run_sign_hook conf ~has_subst file =
572576
match has_subst with
573-
| false -> Fiber.return ()
574-
| true -> (
577+
| No_substitution -> Fiber.return ()
578+
| Some_substitution -> (
575579
match Lazy.force conf.sign_hook with
576580
| Some hook -> hook file
577581
| None -> Fiber.return ())

src/dune_rules/artifact_substitution.mli

+6-2
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,10 @@ val copy_file :
6767
-> unit
6868
-> unit Fiber.t
6969

70+
type status =
71+
| Some_substitution
72+
| No_substitution
73+
7074
(** Generic version of [copy_file]. Rather than filenames, it takes an input and
7175
output functions. Their semantic must match the ones of the [input] and
7276
[output] functions from the OCaml standard library.
@@ -80,10 +84,10 @@ val copy :
8084
-> input_file:Path.t
8185
-> input:(Bytes.t -> int -> int -> int)
8286
-> output:(Bytes.t -> int -> int -> unit)
83-
-> bool Fiber.t
87+
-> status Fiber.t
8488

8589
(** Produce the string that would replace the placeholder with the given value .*)
8690
val encode_replacement : len:int -> repl:string -> string
8791

8892
(** Test if a file contains a substitution placeholder. *)
89-
val test_file : src:Path.t -> unit -> bool Fiber.t
93+
val test_file : src:Path.t -> unit -> status Fiber.t

test/unit-tests/artifact_substitution/artifact_substitution.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -145,7 +145,7 @@ let test input =
145145
to_copy
146146
in
147147
let output = Buffer.add_subbytes buf in
148-
let+ (_ : bool) =
148+
let+ (_ : Artifact_substitution.status) =
149149
Artifact_substitution.copy ~conf:Artifact_substitution.conf_dummy
150150
~input_file:(Path.of_string "<memory>")
151151
~input ~output

0 commit comments

Comments
 (0)