summaryrefslogtreecommitdiff
path: root/ocaml/test/test_real_arvo.ml
blob: 0c052d78333ce1bc9035dae745d98d43ac971835 (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
98
99
100
101
102
103
104
105
106
107
108
109
110
111
(* Extract and Test Real Arvo
 *
 * We found a callable gate at depth 8 - let's extract and test it!
 *)

open Nock_lib

let rec navigate_to_depth noun path =
  match path with
  | [] -> noun
  | slot :: rest ->
      let next = Noun.slot (Z.of_int slot) noun in
      navigate_to_depth next rest

let test_real_arvo env =
  Printf.printf "🎯 Testing Real Arvo Gate\n\n";

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

  (* Load ivory pill *)
  let state = State.create () in
  match Boot.boot_from_file ~fs state "ivory.pill" with
  | Error msg ->
      Printf.printf "✗ Failed to load pill: %s\n%!" msg
  | Ok () ->
      let pill = State.get_arvo state in

      (* Navigate to the callable gate we found
       * We need to find which path leads to depth 8 callable gate
       * Let me try common paths *)

      let test_paths = [
        ([3; 3; 2; 3; 2; 3; 3; 2], "REAL ARVO PATH");
      ] in

      Printf.printf "Trying different paths to depth 8...\n\n";

      List.iter (fun (path, desc) ->
        Printf.printf "Path %s: " desc;
        try
          let gate = navigate_to_depth pill path in

          (* Check if it's a gate *)
          if Noun.is_cell gate &&
             Noun.is_cell (Noun.head gate) &&  (* battery is cell *)
             Noun.is_cell (Noun.tail gate) then begin

            (* Try to call it *)
            try
              let formula = Noun.cell (Noun.atom 9)
                (Noun.cell (Noun.atom 2)
                  (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
              let _result = Nock.nock_on gate formula in
              Printf.printf "✓ FOUND ARVO!\n\n";

              (* Now try a real poke *)
              Printf.printf "  Testing poke with event...\n";
              let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
              let poke_subject = Noun.cell event gate in

              (* Try different poke formulas *)

              (* Formula 1: [8 gate [9 2 [0 1]]] - push gate, call arm 2 *)
              Printf.printf "  Trying formula 1: [8 gate [9 2 [0 1]]]...\n";
              (try
                let f1 = Noun.cell (Noun.atom 8)
                  (Noun.cell gate
                    (Noun.cell (Noun.atom 9)
                      (Noun.cell (Noun.atom 2)
                        (Noun.cell (Noun.atom 0) (Noun.atom 1))))) in
                let _ = Nock.nock_on poke_subject f1 in
                Printf.printf "  ✓ Formula 1 works!\n"
              with e ->
                Printf.printf "  ✗ Formula 1 failed: %s\n" (Printexc.to_string e));

              (* Formula 2: [7 [[0 2] gate] [9 2 [0 1]]] - compose event with gate, call *)
              Printf.printf "  Trying formula 2: [7 [[0 2] gate] [9 2 [0 1]]]...\n";
              let poke_formula = Noun.cell (Noun.atom 7)
                (Noun.cell
                  (Noun.cell (Noun.cell (Noun.atom 0) (Noun.atom 2)) gate)  (* [event gate] *)
                  (Noun.cell (Noun.atom 9)
                    (Noun.cell (Noun.atom 2)
                      (Noun.cell (Noun.atom 0) (Noun.atom 1))))) in  (* call arm 2 *)

              let start = Unix.gettimeofday () in
              let result = Nock.nock_on poke_subject poke_formula in
              let elapsed = Unix.gettimeofday () -. start in

              Printf.printf "  ✓ POKE SUCCEEDED in %.4fs!\n" elapsed;
              Printf.printf "  Result is: %s\n\n"
                (if Noun.is_cell result then "Cell (new state + effects)" else "Atom");

              Printf.printf "🎉 WE CAN CALL ARVO!\n"
            with e ->
              Printf.printf "✗ Call failed: %s\n\n" (Printexc.to_string e)
          end else
            Printf.printf "not a gate\n"

        with e ->
          Printf.printf "✗ %s\n" (Printexc.to_string e)
      ) test_paths

let () =
  Printf.printf "\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf " Extracting and Testing Real Arvo\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf "\n";

  Eio_main.run test_real_arvo