summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_state.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/old/test_state.ml')
-rw-r--r--ocaml/test/old/test_state.ml165
1 files changed, 165 insertions, 0 deletions
diff --git a/ocaml/test/old/test_state.ml b/ocaml/test/old/test_state.ml
new file mode 100644
index 0000000..1c841c8
--- /dev/null
+++ b/ocaml/test/old/test_state.ml
@@ -0,0 +1,165 @@
+(* State Management Tests - Domain-safe state with Eio
+ *
+ * Tests:
+ * 1. Basic state creation and access
+ * 2. Atomic event counter
+ * 3. Save/load snapshots
+ * 4. Concurrent access across domains (future)
+ *)
+
+open Nock_lib
+
+let test_basic_state _env =
+ Printf.printf "Test: Basic state creation and access...\n";
+
+ let state = State.create () in
+
+ (* Check initial values *)
+ let eve = State.event_num state in
+ Printf.printf " Initial event number: %Ld\n" eve;
+ assert (eve = 0L);
+
+ (* Create a simple kernel state *)
+ let kernel = Noun.cell (Noun.atom 1) (Noun.atom 2) in
+ State.boot state kernel;
+
+ let arvo = State.get_arvo state in
+ Printf.printf " Kernel state loaded\n";
+ assert (arvo = kernel);
+
+ Printf.printf " ✓ Basic state operations work!\n\n"
+
+let test_atomic_counter _env =
+ Printf.printf "Test: Atomic event counter...\n";
+
+ let state = State.create () in
+
+ (* Initial counter *)
+ assert (State.event_num state = 0L);
+
+ (* Increment a few times *)
+ for _i = 1 to 10 do
+ let _old = State.inc_event state in
+ ()
+ done;
+
+ let final = State.event_num state in
+ Printf.printf " After 10 increments: %Ld\n" final;
+ assert (final = 10L);
+
+ Printf.printf " ✓ Atomic counter works!\n\n"
+
+let test_snapshot_save_load env =
+ Printf.printf "Test: Snapshot save/load...\n";
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Create state with some data *)
+ let state1 = State.create () in
+ let kernel = Noun.cell
+ (Noun.cell (Noun.atom 42) (Noun.atom 99))
+ (Noun.atom 1000000) in
+ State.boot state1 kernel;
+
+ (* Increment event counter *)
+ for _i = 1 to 5 do
+ let _ = State.inc_event state1 in
+ ()
+ done;
+
+ Printf.printf " State before save: %s\n" (State.summary state1);
+
+ (* Save snapshot *)
+ State.save_snapshot state1 ~fs "tmp/test_state.snapshot";
+ Printf.printf " Snapshot saved\n";
+
+ (* Create new state and load snapshot *)
+ let state2 = State.create () in
+ let result = State.load_snapshot state2 ~fs "tmp/test_state.snapshot" in
+
+ match result with
+ | Ok eve ->
+ Printf.printf " Snapshot loaded, event: %Ld\n" eve;
+ Printf.printf " State after load: %s\n" (State.summary state2);
+
+ (* Verify event number *)
+ assert (State.event_num state2 = 5L);
+
+ (* Verify kernel state *)
+ let loaded_kernel = State.get_arvo state2 in
+ assert (loaded_kernel = kernel);
+
+ Printf.printf " ✓ Snapshot save/load works!\n\n"
+ | Error msg ->
+ failwith ("Snapshot load failed: " ^ msg)
+
+let test_poke env =
+ Printf.printf "Test: Poke (event processing)...\n";
+ Eio.Switch.run @@ fun _sw ->
+ let _fs = Eio.Stdenv.fs env in
+
+ let state = State.create () in
+
+ (* Boot with a simple kernel *)
+ State.boot state (Noun.atom 0);
+ assert (State.event_num state = 0L);
+
+ (* Poke with an event *)
+ let event = Noun.cell (Noun.atom 1) (Noun.atom 2) in
+ let _effects = State.poke state event in
+
+ (* Event number should have incremented *)
+ assert (State.event_num state = 1L);
+ Printf.printf " Event processed, new event number: %Ld\n" (State.event_num state);
+
+ (* Poke again *)
+ let _effects = State.poke state event in
+ assert (State.event_num state = 2L);
+
+ Printf.printf " ✓ Poke increments event counter!\n\n"
+
+let test_peek _env =
+ Printf.printf "Test: Peek (read-only queries)...\n";
+
+ let state = State.create () in
+ let kernel = Noun.atom 42 in
+ State.boot state kernel;
+
+ (* Peek should return something (formula returns [path kernel]) *)
+ let result = State.peek state (Noun.atom 0) in
+ match result with
+ | Some _noun ->
+ (* Peek succeeded *)
+ Printf.printf " ✓ Peek works!\n\n"
+ | None ->
+ failwith "Peek returned None"
+
+let test_cache _env =
+ Printf.printf "Test: Wish cache...\n";
+
+ let state = State.create () in
+
+ (* Check initial cache is empty *)
+ assert (String.contains (State.summary state) '0');
+
+ (* Clear cache (should be safe to call) *)
+ State.clear_cache state;
+
+ Printf.printf " ✓ Cache operations work!\n\n"
+
+let () =
+ Eio_main.run @@ fun env ->
+ Printf.printf "\n=== State Management Tests (Domain-safe with Eio) ===\n\n";
+
+ (* Clean up old test files *)
+ (try Unix.system "rm -rf tmp/test_state*" |> ignore with _ -> ());
+
+ test_basic_state env;
+ test_atomic_counter env;
+ test_snapshot_save_load env;
+ test_poke env;
+ test_peek env;
+ test_cache env;
+
+ Printf.printf "=== All state tests passed! ✓ ===\n";
+ Printf.printf "\nNext: Test concurrent access across domains...\n"