(* Boot Arvo properly through all 5 solid pill events *) open Nock_lib let boot_arvo _env = Printf.printf "🚀 Booting Arvo Through All 5 Events\n\n"; (* Load solid pill *) Printf.printf "Loading solid pill from cache...\n"; let in_channel = open_in_bin "solid.noun" in let pill = (Marshal.from_channel in_channel : Noun.noun) in close_in in_channel; Printf.printf "✓ Loaded\n\n"; match pill with | Noun.Cell (_tag, events) -> (* Convert to list *) let rec to_list acc noun = match noun with | Noun.Atom _ -> List.rev acc | Noun.Cell (item, rest) -> to_list (item :: acc) rest in let event_list = to_list [] events in Printf.printf "Found %d events\n\n" (List.length event_list); (* Start with no kernel *) let kernel = ref None in (* Process each event *) List.iteri (fun i event -> Printf.printf "=== Event %d ===\n" i; match event with | Noun.Atom a -> Printf.printf "Atom: %s\n" (Z.to_string a); if i = 0 then Printf.printf " (Boot sequence tag)\n" else if i = 2 then Printf.printf " (Separator)\n"; Printf.printf "\n" | Noun.Cell _ -> if i = 1 then begin (* Event 1: The kernel itself (not wrapped in [wire card]) *) Printf.printf "Cell: Initial kernel\n"; Printf.printf " → Setting as kernel\n"; kernel := Some event; (* The whole event IS the kernel *) (* Verify it has poke gate at axis 42 *) begin try let _gate = Noun.slot (Z.of_int 42) event in Printf.printf " ✓ Has poke gate at axis 42\n" with _ -> Printf.printf " ✗ No poke gate found\n" end; Printf.printf "\n" end else if i > 1 then begin (* Events 3 and 4: Boot events as [wire card] *) Printf.printf "Cell: [wire card]\n"; match !kernel with | None -> Printf.printf " ✗ No kernel to poke yet\n\n" | Some k -> Printf.printf " → Poking kernel with event\n"; try (* Get poke gate at axis 42 *) let poke_gate = Noun.slot (Z.of_int 42) k in Printf.printf " Found poke gate at axis 42\n"; (* Build poke arguments: [now ovum] *) (* ovum is the event itself: [wire card] *) let now = Noun.atom 0 in (* Use epoch for now *) let ovum = event in let poke_arg = Noun.cell now ovum in (* Build subject: [sample gate] *) let subject = Noun.cell poke_arg poke_gate in (* Standard gate call: [9 2 [0 2] [0 3]] *) 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 Printf.printf " Executing poke...\n%!"; let start = Unix.gettimeofday () in let result = Nock.nock_on subject formula in let elapsed = Unix.gettimeofday () -. start in Printf.printf " ✓ Completed in %.3fs\n" elapsed; (* Parse result: [effects new-kernel] *) begin match result with | Noun.Cell (effects, new_kernel) -> Printf.printf " Result: [effects new-kernel]\n"; (* Count effects *) let rec count_list n noun = match noun with | Noun.Atom _ -> n | Noun.Cell (_, rest) -> count_list (n + 1) rest in let effect_count = count_list 0 effects in Printf.printf " Effects: %d\n" effect_count; (* Update kernel *) kernel := Some new_kernel; Printf.printf " ✓ Kernel updated\n" | Noun.Atom _ -> Printf.printf " ✗ Result is atom (unexpected)\n" end; Printf.printf "\n" with | Noun.Exit -> Printf.printf " ✗ Nock execution failed (Exit)\n"; Printf.printf " This event might not be in the right format\n"; Printf.printf "\n" | Not_found -> Printf.printf " ✗ No poke gate at axis 42\n\n" end ) event_list; (* Final kernel check *) Printf.printf "═══════════════════════════════════════════════════════\n\n"; begin match !kernel with | None -> Printf.printf "✗ No final kernel\n" | Some k -> Printf.printf "🎉 Arvo Boot Complete!\n\n"; (* Verify poke gate *) begin try let _gate = Noun.slot (Z.of_int 42) k in Printf.printf "✓ Final kernel has poke gate at axis 42\n\n"; (* Try a test poke! *) Printf.printf "Testing final kernel with a poke...\n"; let poke_gate = Noun.slot (Z.of_int 42) k in (* Build test ovum: [wire card] *) let wire = Noun.atom 0 in (* / *) let term_test = Noun.Atom (Z.of_string "1953719668") in (* 'test' *) let data = Noun.atom 42 in let card = Noun.cell term_test data in let ovum = Noun.cell wire card in let now = Noun.atom 0 in let poke_arg = Noun.cell now ovum in 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 Printf.printf " Poking with test event [0 [%%test 42]]...\n%!"; 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; begin match result with | Noun.Cell (effects, new_kernel) -> let rec count_list n noun = match noun with | Noun.Atom _ -> n | Noun.Cell (_, rest) -> count_list (n + 1) rest in Printf.printf " Effects produced: %d\n" (count_list 0 effects); Printf.printf " New kernel: %s\n\n" (match new_kernel with Noun.Cell _ -> "cell ✓" | Noun.Atom _ -> "atom"); Printf.printf "🎊 ARVO IS FULLY OPERATIONAL! 🎊\n\n"; Printf.printf "We can now:\n"; Printf.printf " ✅ Send events to Arvo\n"; Printf.printf " ✅ Receive effects\n"; Printf.printf " ✅ Update kernel state\n"; Printf.printf " ✅ Build a complete Urbit runtime!\n" | Noun.Atom _ -> Printf.printf " Result is atom (unexpected)\n" end with | Noun.Exit -> Printf.printf "✗ Test poke failed\n" | Not_found -> Printf.printf "✗ No poke gate in final kernel\n" end end | Noun.Atom _ -> Printf.printf "✗ Pill is an atom\n" let () = Printf.printf "\n"; Printf.printf "═══════════════════════════════════════════════════════════\n"; Printf.printf " Boot Arvo Properly Through All Events\n"; Printf.printf "═══════════════════════════════════════════════════════════\n"; Printf.printf "\n"; Eio_main.run boot_arvo