summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_arvo_real_poke.ml
blob: af707fe6068e57ecabe381f124da22b95845abfd (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
(* Test REAL Arvo poke - actually call into the kernel *)

open Nock_lib

let test_real_poke env =
  Printf.printf "šŸš€ Testing Real Arvo Poke\n\n";

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

  (* Load ivory pill *)
  Printf.printf "Loading ivory pill...\n%!";
  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;
      failwith "Pill load failed"

  | Ok () ->
      Printf.printf "āœ“ Ivory kernel loaded!\n\n";

      (* Get the kernel *)
      let kernel = state.roc in

      (* Try to find the poke gate at slot 23 (traditional Arvo location) *)
      Printf.printf "Looking for poke gate...\n";

      try
        (* Try slot 23 *)
        let gate = Noun.slot (Z.of_int 23) kernel in
        Printf.printf "āœ“ Found gate at slot 23\n\n";

        (* Create test event: [wire card] *)
        let event = Noun.cell
          (Noun.atom 0)  (* wire *)
          (Noun.cell (Noun.atom 1) (Noun.atom 42))  (* card *)
        in

        Printf.printf "Calling Arvo with event [0 [1 42]]...\n";

        (* Try the standard gate call formula: [9 2 [0 2] [0 3]]
         * This means:
         * - 9 2: call gate at axis 2 (of the subject)
         * - [0 2]: get sample (event) at axis 2
         * - [0 3]: get context (gate) at axis 3
         *
         * Subject is: [event gate]
         *)
        let subject = Noun.cell event 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 "Running nock...\n";
        let result = Nock.nock_on subject formula in
        Printf.printf "āœ“ Poke succeeded!\n\n";

        (* Check result structure *)
        begin match result with
        | Noun.Cell (effects, new_kernel) ->
            Printf.printf "Result is a cell: [effects new_kernel]\n";
            Printf.printf "Effects: %s\n"
              (match effects with
               | Noun.Atom _ -> "atom"
               | Noun.Cell _ -> "cell");
            Printf.printf "New kernel: %s\n"
              (match new_kernel with
               | Noun.Atom _ -> "atom"
               | Noun.Cell _ -> "cell");
            Printf.printf "\nšŸŽ‰ ARVO POKE SUCCESSFUL!\n"

        | Noun.Atom _ ->
            Printf.printf "Result is an atom (unexpected)\n"
        end

      with Noun.Exit ->
        Printf.printf "āœ— Nock execution failed (Exit)\n";
        Printf.printf "Slot 23 might not be the right location\n\n";

        (* Try to explore the kernel structure *)
        Printf.printf "Let me explore the kernel structure...\n";
        for i = 2 to 30 do
          try
            let slot_val = Noun.slot (Z.of_int i) kernel in
            let is_cell = match slot_val with Noun.Cell _ -> "cell" | Noun.Atom _ -> "atom" in
            Printf.printf "  Slot %d: %s\n" i is_cell
          with _ -> ()
        done

let () =
  Printf.printf "\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf " Testing REAL Arvo Poke (Actually Call Into Kernel)\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf "\n";

  Eio_main.run test_real_poke