summaryrefslogtreecommitdiff
path: root/ocaml/test/test_eventlog.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/test_eventlog.ml')
-rw-r--r--ocaml/test/test_eventlog.ml155
1 files changed, 155 insertions, 0 deletions
diff --git a/ocaml/test/test_eventlog.ml b/ocaml/test/test_eventlog.ml
new file mode 100644
index 0000000..fd0e496
--- /dev/null
+++ b/ocaml/test/test_eventlog.ml
@@ -0,0 +1,155 @@
+(* Event Log Tests - Eio-based event persistence testing
+ *
+ * Tests:
+ * 1. Basic append and read
+ * 2. Jam/cue roundtrip through event log
+ * 3. Replay functionality
+ * 4. Multiple events in sequence
+ *)
+
+open Nock_lib
+
+let test_basic_append env =
+ Printf.printf "Test: Basic append and read...\n";
+ Eio.Switch.run @@ fun sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Create event log in tmp directory *)
+ let log = Eventlog.create ~sw ~fs "tmp/test_eventlog" in
+
+ (* Create a simple noun *)
+ let noun1 = Noun.atom 42 in
+
+ (* Append event *)
+ let event_num = Eventlog.append log ~sw noun1 in
+ Printf.printf " Appended event %Ld\n" event_num;
+
+ (* Read it back *)
+ let noun2 = Eventlog.read_event log event_num in
+ Printf.printf " Read back event %Ld\n" event_num;
+
+ (* Verify they match *)
+ if noun1 = noun2 then
+ Printf.printf " ✓ Basic append/read works!\n\n"
+ else
+ failwith "Noun mismatch!"
+
+let test_jam_cue_roundtrip env =
+ Printf.printf "Test: Jam/cue roundtrip through event log...\n";
+ Eio.Switch.run @@ fun sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Create event log *)
+ let log = Eventlog.create ~sw ~fs "tmp/test_eventlog_jam" in
+
+ (* Create various nouns *)
+ let test_cases = [
+ ("atom 0", Noun.atom 0);
+ ("atom 42", Noun.atom 42);
+ ("atom 1000000", Noun.atom 1000000);
+ ("cell [1 2]", Noun.cell (Noun.atom 1) (Noun.atom 2));
+ ("nested [[1 2] [3 4]]",
+ Noun.cell
+ (Noun.cell (Noun.atom 1) (Noun.atom 2))
+ (Noun.cell (Noun.atom 3) (Noun.atom 4)));
+ ] in
+
+ List.iter (fun (name, noun) ->
+ let event_num = Eventlog.append log ~sw noun in
+ let recovered = Eventlog.read_event log event_num in
+ if noun = recovered then
+ Printf.printf " ✓ %s: roundtrip OK (event %Ld)\n" name event_num
+ else
+ failwith (Printf.sprintf "%s: roundtrip FAILED" name)
+ ) test_cases;
+
+ Printf.printf "\n"
+
+let test_replay env =
+ Printf.printf "Test: Event replay...\n";
+ Eio.Switch.run @@ fun sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Create event log *)
+ let log = Eventlog.create ~sw ~fs "tmp/test_eventlog_replay" in
+
+ (* Append several events *)
+ let nouns = [
+ Noun.atom 1;
+ Noun.atom 2;
+ Noun.atom 3;
+ Noun.cell (Noun.atom 4) (Noun.atom 5);
+ ] in
+
+ List.iter (fun noun ->
+ let _ = Eventlog.append log ~sw noun in
+ ()
+ ) nouns;
+
+ Printf.printf " Appended %d events\n" (List.length nouns);
+
+ (* Create new log instance to test replay *)
+ let log2 = Eventlog.create ~sw ~fs "tmp/test_eventlog_replay" in
+
+ (* Replay events *)
+ let replayed = ref [] in
+ Eventlog.replay log2 ~sw (fun num noun ->
+ Printf.printf " Replayed event %Ld\n" num;
+ replayed := noun :: !replayed
+ );
+
+ let replayed_list = List.rev !replayed in
+
+ (* Verify all events were replayed correctly *)
+ if List.length replayed_list = List.length nouns then
+ Printf.printf " ✓ Replayed %d events correctly\n" (List.length nouns)
+ else
+ failwith (Printf.sprintf "Expected %d events, got %d"
+ (List.length nouns) (List.length replayed_list));
+
+ (* Verify content matches *)
+ List.iter2 (fun original replayed ->
+ if original <> replayed then
+ failwith "Replayed noun doesn't match original"
+ ) nouns replayed_list;
+
+ Printf.printf " ✓ All replayed events match originals\n\n"
+
+let test_event_count env =
+ Printf.printf "Test: Event counting...\n";
+ Eio.Switch.run @@ fun sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ let log = Eventlog.create ~sw ~fs "tmp/test_eventlog_count" in
+
+ (* Initially should have 0 events *)
+ let count0 = Eventlog.event_count log in
+ Printf.printf " Initial count: %d\n" count0;
+
+ (* Append 5 events *)
+ for i = 1 to 5 do
+ let _ = Eventlog.append log ~sw (Noun.atom i) in
+ ()
+ done;
+
+ let count5 = Eventlog.event_count log in
+ Printf.printf " After 5 appends: %d\n" count5;
+
+ if count5 = 5 then
+ Printf.printf " ✓ Event count correct\n\n"
+ else
+ failwith (Printf.sprintf "Expected 5 events, got %d" count5)
+
+let () =
+ Eio_main.run @@ fun env ->
+ Printf.printf "\n=== Event Log Tests (Eio-based) ===\n\n";
+
+ (* Clean up old test directories *)
+ (try Unix.system "rm -rf tmp/test_eventlog*" |> ignore with _ -> ());
+
+ test_basic_append env;
+ test_jam_cue_roundtrip env;
+ test_replay env;
+ test_event_count env;
+
+ Printf.printf "=== All tests passed! ✓ ===\n"