summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_ivory_boot.ml
blob: f9d511ab1a5732c87274acaf1ad99f65ec66a5bc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
(* Test Ivory Pill Boot Sequence
 *
 * Implements C Vere's u3v_life() lifecycle boot
 *)

open Nock_lib

let test_ivory_boot env =
  Printf.printf "šŸŽÆ Testing Ivory Pill Boot (C Vere u3v_life pattern)\n\n";

  Eio.Switch.run @@ fun _sw ->
  let fs = Eio.Stdenv.fs env in

  (* Create state *)
  let state = State.create () in

  (* Boot using ivory boot sequence *)
  Printf.printf "Step 1: Load ivory pill\n";
  Printf.printf "Step 2: Validate 'ivory' tag\n";
  Printf.printf "Step 3: Run lifecycle formula [2 [0 3] [0 2]]\n";
  Printf.printf "Step 4: Extract slot 7 from result\n\n";

  match Boot.boot_lite ~fs state "ivory.pill" with
  | Error msg ->
      Printf.printf "āœ— Boot failed: %s\n%!" msg

  | Ok () ->
      let arvo = State.get_arvo state in
      Printf.printf "\n✨ SUCCESS! Ivory pill booted!\n\n";

      (* Verify structure *)
      Printf.printf "Verifying booted core structure:\n";
      Printf.printf "  Is cell: %s\n" (if Noun.is_cell arvo then "āœ“" else "āœ—");

      if Noun.is_cell arvo then begin
        let battery = Noun.head arvo in
        let payload = Noun.tail arvo in

        Printf.printf "  Battery: %s\n"
          (if Noun.is_cell battery then "āœ“ Cell (contains code)" else "Atom");
        Printf.printf "  Payload: %s\n\n"
          (if Noun.is_cell payload then "āœ“ Cell (contains data)" else "Atom");

        (* Now try the C Vere poke pattern on this booted core *)
        Printf.printf "Testing if this core has slot 23 (poke interface)...\n";
        (try
          let slot_23 = Noun.slot (Z.of_int 23) arvo in
          Printf.printf "  āœ“ Slot 23 exists!\n";
          Printf.printf "  Is formula: %s\n"
            (if Noun.is_cell slot_23 then "āœ“ Cell" else "Atom");

          (* Try to run poke sequence *)
          Printf.printf "\nAttempting C Vere poke sequence:\n";
          Printf.printf "  1. Get slot 23 formula\n";
          Printf.printf "  2. Run formula on Arvo core\n";
          Printf.printf "  3. Slam result with test event\n\n";

          let poke_gate = Nock.nock_on arvo slot_23 in
          Printf.printf "  āœ“ Got poke gate from slot 23\n";

          (* Create test event *)
          let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in

          (* Slam: build [battery [event context]] and call arm 2 *)
          let battery = Noun.head poke_gate in
          let context = Noun.tail (Noun.tail poke_gate) in
          let new_core = Noun.cell battery (Noun.cell event context) in
          let kick_formula = Noun.cell (Noun.atom 9)
            (Noun.cell (Noun.atom 2)
              (Noun.cell (Noun.atom 0) (Noun.atom 1))) in

          let start = Unix.gettimeofday () in
          let result = Nock.nock_on new_core kick_formula in
          let elapsed = Unix.gettimeofday () -. start in

          Printf.printf "  āœ“ Poke succeeded in %.4fs!\n" elapsed;
          Printf.printf "  Result: %s\n\n"
            (if Noun.is_cell result then "Cell (effects + new state)" else "Atom");

          Printf.printf "šŸŽ‰ FULL ARVO BOOT SUCCESSFUL!\n";
          Printf.printf "We have a working Arvo instance!\n"

        with e ->
          Printf.printf "  āœ— Slot 23 not found: %s\n" (Printexc.to_string e);
          Printf.printf "\nThis is expected for ivory pills.\n";
          Printf.printf "Ivory contains %%zuse core, not full Arvo.\n";
          Printf.printf "For full poke interface, need solid/brass pill.\n")
      end

let () =
  Printf.printf "\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf " Testing Ivory Pill Boot Sequence (u3v_life)\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf "\n";

  Eio_main.run test_ivory_boot