Skip to content

Commit

Permalink
Remove ppx_jane from preprocessor list and remove sexp
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Sep 26, 2021
1 parent c4712fb commit 069b214
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 23 deletions.
2 changes: 1 addition & 1 deletion test/expect-tests/dune_file_watcher/dune
Original file line number Diff line number Diff line change
Expand Up @@ -19,4 +19,4 @@
stdio
spawn)
(preprocess
(pps ppx_expect ppx_sexp_conv ppx_jane)))
(pps ppx_expect ppx_sexp_conv)))
40 changes: 18 additions & 22 deletions test/expect-tests/dune_file_watcher/dune_file_watcher_tests.ml
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
let printf = Printf.printf

open Stdune
open Base
open Stdune

let tmp_dir = Stdlib.Filename.concat (Unix.getcwd ()) "working-dir"

Expand All @@ -24,18 +24,14 @@ let retry_loop (type a) ~period ~timeout ~(f : unit -> a option) : a option =
| Some res -> Some res
| None ->
let t1 = now () in
if Float.( < ) (t1 -. t0) timeout then (
if Base.Float.( < ) (t1 -. t0) timeout then (
Thread.delay period;
loop ()
) else
None
in
loop ()

let print_s sexp = printf "%s\n" (Sexp.to_string_hum sexp)

let sexp_of_path path = sexp_of_string (Path.to_string path)

let get_events ~try_to_get_events ~expected =
let collected = ref [] in
let done_collecting =
Expand All @@ -44,14 +40,13 @@ let get_events ~try_to_get_events ~expected =
| n ->
assert (n > 0);
retry_loop ~period:0.01 ~timeout:3.0 ~f:(fun () ->
match try_to_get_events () with
| None -> None
| Some events ->
collected := !collected @ events;
if List.length !collected >= expected then
Some `Enough
else
None)
let open Option.O in
try_to_get_events () >>= fun events ->
collected := !collected @ events;
if List.length !collected >= expected then
Some `Enough
else
None)
in
match done_collecting with
| None -> (!collected, `Not_enough)
Expand All @@ -60,14 +55,15 @@ let get_events ~try_to_get_events ~expected =
(match try_to_get_events () with
| Some events -> collected := !collected @ events
| None -> ());
if List.length !collected > expected then
(!collected, `Too_many)
else
(!collected, `Ok)
( !collected
, if List.length !collected > expected then
`Too_many
else
`Ok )

let print_events ~try_to_get_events ~expected =
let events, status = get_events ~try_to_get_events ~expected in
List.iter events ~f:(fun event -> print_s ([%sexp_of: path] event));
List.iter events ~f:(fun event -> Stdio.print_endline (Path.to_string event));
match status with
| `Ok -> ()
| `Not_enough ->
Expand Down Expand Up @@ -106,9 +102,9 @@ let%expect_test _ =
Some
(List.map list ~f:(function
| Dune_file_watcher.Event.Sync -> assert false
| Dune_file_watcher.Event.Queue_overflow -> assert false
| Dune_file_watcher.Event.Fs_memo_event { path; kind = _ } -> path
| Dune_file_watcher.Event.Watcher_terminated -> assert false)))
| Queue_overflow -> assert false
| Fs_memo_event { path; kind = _ } -> path
| Watcher_terminated -> assert false)))
in
let print_events n = print_events ~try_to_get_events ~expected:n in
Dune_file_watcher.wait_for_initial_watches_established_blocking watcher;
Expand Down

0 comments on commit 069b214

Please sign in to comment.