summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_cvere_poke.ml
blob: 28b0c78fd5da73f19e0a5ee476e4b636d0641bcb (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
(* Test C Vere Poke Pattern
 *
 * Implement the exact poke sequence from C Vere:
 * 1. Get slot 23 from Arvo core (poke formula)
 * 2. Run Nock to compute the poke gate
 * 3. Slam: build [battery [event context]] and call arm 2
 *)

open Nock_lib

let slam_on gate event =
  (* C Vere slam_on: u3nc(u3k(u3h(gat)), u3nc(sam, u3k(u3t(u3t(gat))))) *)
  (* Build: [battery [new-sample context]] *)
  let battery = Noun.head gate in
  let context = Noun.tail (Noun.tail gate) in  (* slot 7 *)
  let new_core = Noun.cell battery (Noun.cell event context) in

  (* Kick: call arm 2 *)
  let kick_formula = Noun.cell (Noun.atom 9)
    (Noun.cell (Noun.atom 2)
      (Noun.cell (Noun.atom 0) (Noun.atom 1))) in

  Nock.nock_on new_core kick_formula

let test_cvere_poke env =
  Printf.printf "šŸŽÆ Testing C Vere Poke Pattern\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_root = State.get_arvo state in

      Printf.printf "Step 0: Navigate to real Arvo core\n";
      Printf.printf "  Path: [3 3 2 3 2 3 3 2]\n";

      (* Navigate to real Arvo *)
      let path = [3; 3; 2; 3; 2; 3; 3; 2] in
      let rec navigate noun = function
        | [] -> noun
        | slot :: rest ->
            navigate (Noun.slot (Z.of_int slot) noun) rest
      in
      let arvo = navigate pill_root path in
      Printf.printf "  āœ“ Found real Arvo core\n\n";

      Printf.printf "Step 1: Get slot 23 from Arvo core\n";
      let slot_23_formula = Noun.slot (Z.of_int 23) arvo in
      Printf.printf "  āœ“ Got formula from slot 23\n\n";

      Printf.printf "Step 2: Run Nock to compute poke gate\n";
      Printf.printf "  Subject: Arvo core\n";
      Printf.printf "  Formula: slot 23 contents\n";

      let poke_gate = Nock.nock_on arvo slot_23_formula in
      Printf.printf "  āœ“ Computed poke gate\n\n";

      Printf.printf "Step 3: Create test event (ovum)\n";
      let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
      Printf.printf "  Event: [0 42]\n\n";

      Printf.printf "Step 4: Slam poke gate with event\n";
      Printf.printf "  Building: [battery [event context]]\n";
      Printf.printf "  Calling: arm 2\n\n";

      let start = Unix.gettimeofday () in
      (try
        let result = slam_on poke_gate event in
        let elapsed = Unix.gettimeofday () -. start in

        Printf.printf "šŸŽ‰ POKE SUCCEEDED in %.4fs!\n\n" elapsed;

        (* Result should be [effects new-core] *)
        if Noun.is_cell result then begin
          Printf.printf "Result structure: Cell\n";
          let effects = Noun.head result in
          let new_core = Noun.tail result in

          Printf.printf "  Effects: %s\n"
            (if Noun.is_cell effects then "Cell (list)" else "Atom");
          Printf.printf "  New core: %s\n"
            (if Noun.is_cell new_core then "Cell (updated Arvo)" else "Atom");

          Printf.printf "\n✨ ARVO IS RUNNING!\n";
          Printf.printf "We can now poke Arvo with events!\n"
        end else
          Printf.printf "Result is atom (unexpected)\n"

      with e ->
        Printf.printf "āœ— Poke failed: %s\n" (Printexc.to_string e);
        Printf.printf "Stack trace:\n%s\n" (Printexc.get_backtrace ()))

let () =
  Printf.printf "\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf " Testing C Vere Poke Pattern on Arvo\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf "\n";

  Eio_main.run test_cvere_poke