(* Test Arvo poke with CORRECT interface from docs *) open Nock_lib let extract_arvo () = Printf.printf "Loading Arvo from solid pill...\n"; let in_channel = open_in_bin "solid.noun" in let pill = (Marshal.from_channel in_channel : Noun.noun) in close_in in_channel; (* Extract event 1 - the initial kernel *) match pill with | Noun.Cell (_tag, events) -> let rec nth n noun = match noun with | Noun.Atom _ -> None | Noun.Cell (item, rest) -> if n = 0 then Some item else nth (n - 1) rest in begin match nth 1 events with | Some (Noun.Cell (_wire, card)) -> Some card | _ -> None end | _ -> None let test_poke _env = Printf.printf "🎯 Testing Arvo Poke (Correct Interface)\n\n"; Printf.printf "Based on docs/runtime/api.md:\n"; Printf.printf " ++ poke |/ {now/@da ovo/ovum} :: 42\n"; Printf.printf " ++ ovum {p/wire q/card}\n"; Printf.printf " ++ card {p/@tas q/*}\n\n"; match extract_arvo () with | None -> Printf.printf "✗ Failed to extract Arvo\n" | Some arvo -> try (* The poke gate is at AXIS 42, not 23! *) Printf.printf "Looking for poke gate at axis 42...\n"; let poke_gate = Noun.slot (Z.of_int 42) arvo in Printf.printf "✓ Found poke gate at axis 42!\n\n"; (* Build proper ovum: [wire card] *) (* wire = / (empty path, represented as 0) *) (* card = [term data] = [%test 42] *) Printf.printf "Building ovum: [wire card]\n"; Printf.printf " wire: / (atom 0)\n"; Printf.printf " card: [%%test 42]\n"; let wire = Noun.atom 0 in (* / path *) let term_test = Noun.Atom (Z.of_string "1953719668") in (* 'test' as atom *) let data = Noun.atom 42 in let card = Noun.cell term_test data in let ovum = Noun.cell wire card in Printf.printf "\nBuilding poke arguments: [now ovum]\n"; (* now = current time as @da (atom) - use a fake timestamp *) let now = Noun.atom 0 in (* epoch *) let poke_arg = Noun.cell now ovum in Printf.printf " now: 0 (epoch)\n"; Printf.printf " ovum: [0 [1953719668 42]]\n\n"; (* Build subject for gate call: [sample gate] *) (* Standard gate call: [9 2 [0 2] [0 3]] *) Printf.printf "Calling poke gate...\n"; let subject = Noun.cell poke_arg poke_gate in let formula = Noun.cell (Noun.atom 9) (Noun.cell (Noun.atom 2) (Noun.cell (Noun.cell (Noun.atom 0) (Noun.atom 2)) (Noun.cell (Noun.atom 0) (Noun.atom 3)))) in let start = Unix.gettimeofday () in let result = Nock.nock_on subject formula in let elapsed = Unix.gettimeofday () -. start in Printf.printf "✓ Poke succeeded in %.4fs!\n\n" elapsed; (* Parse result: [effects new-kernel] *) begin match result with | Noun.Cell (effects, new_kernel) -> Printf.printf "Result: [effects new-kernel]\n"; Printf.printf " Effects: %s\n" (match effects with Noun.Atom _ -> "atom/nil" | Noun.Cell _ -> "cell/list"); Printf.printf " New kernel: %s\n\n" (match new_kernel with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell"); (* Verify new kernel still has poke gate *) begin try let _new_poke = Noun.slot (Z.of_int 42) new_kernel in Printf.printf "✓ New kernel has poke gate at axis 42\n\n"; Printf.printf "🎉 ARVO POKE IS FULLY WORKING!\n\n"; Printf.printf "This means we can:\n"; Printf.printf " ✅ Send events to Arvo\n"; Printf.printf " ✅ Receive effects (output events)\n"; Printf.printf " ✅ Get updated kernel state\n"; Printf.printf " ✅ Build a complete Urbit runtime!\n" with _ -> Printf.printf "⚠️ New kernel missing poke gate\n" end | Noun.Atom _ -> Printf.printf "Result is an atom (unexpected)\n"; Printf.printf "This might mean the gate signature doesn't match\n" end with | Noun.Exit -> Printf.printf "✗ Nock failed (Exit)\n\n"; Printf.printf "Possible issues:\n"; Printf.printf " - Event format still wrong\n"; Printf.printf " - Gate formula incorrect\n"; Printf.printf " - Arvo kernel not fully initialized\n" | Not_found -> Printf.printf "✗ No gate at axis 42\n"; Printf.printf "This kernel might not be Arvo\n" let () = Printf.printf "\n"; Printf.printf "═══════════════════════════════════════════════════════════\n"; Printf.printf " Test Arvo Poke (Correct Interface from Docs)\n"; Printf.printf "═══════════════════════════════════════════════════════════\n"; Printf.printf "\n"; Eio_main.run test_poke