summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_solid_cvere_pattern.ml
blob: a0a4c586512fb06fde32b2033d52e9af9089e57c (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
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
(* Test C Vere poke pattern on solid pill *)

open Nock_lib

let slam_on gate event =
  (* C Vere slam_on: [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 arm 2: [9 2 0 1] *)
  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 rec to_list acc noun =
  match noun with
  | Noun.Atom _ -> List.rev acc
  | Noun.Cell (item, rest) -> to_list (item :: acc) rest

let test_poke _env =
  Printf.printf "šŸŽÆ Testing C Vere Pattern on Solid Pill\n\n";

  (* Load solid pill *)
  Printf.printf "Loading solid pill...\n";
  let in_channel = open_in_bin "solid.noun" in
  let pill = (Marshal.from_channel in_channel : Noun.noun) in
  close_in in_channel;

  match pill with
  | Noun.Cell (_tag, events) ->
      let event_list = to_list [] events in
      Printf.printf "Found %d events\n\n" (List.length event_list);

      (* Event 1 is the initial kernel *)
      begin match List.nth_opt event_list 1 with
      | Some kernel ->
          Printf.printf "Testing on Event 1 (initial kernel):\n\n";

          (* Try slot 23 (C Vere pattern) *)
          Printf.printf "Step 1: Get formula from slot 23...\n";
          begin try
            let slot_23_formula = Noun.slot (Z.of_int 23) kernel in
            Printf.printf "  āœ“ Found formula at slot 23\n\n";

            Printf.printf "Step 2: Run formula to compute poke gate...\n";
            let poke_gate = Nock.nock_on kernel slot_23_formula in
            Printf.printf "  āœ“ Computed poke gate\n\n";

            Printf.printf "Step 3: Build test event...\n";
            (* Build proper ovum: [wire card] *)
            let wire = Noun.atom 0 in
            let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
            let ovum = Noun.cell wire card in

            (* Build poke args: [now ovum] *)
            let now = Noun.atom 0 in
            let event = Noun.cell now ovum in
            Printf.printf "  Event: [now [wire card]]\n\n";

            Printf.printf "Step 4: Slam poke gate...\n";
            let start = Unix.gettimeofday () in
            let result = slam_on poke_gate event 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) ->
                Printf.printf "Result: [effects new-kernel]\n";
                Printf.printf "  āœ“ Got expected structure!\n\n";
                Printf.printf "šŸŽ‰ SOLID PILL ARVO IS WORKING!\n"
            | Noun.Atom _ ->
                Printf.printf "Result is atom (unexpected)\n"
            end

          with
          | Noun.Exit ->
              Printf.printf "  āœ— Nock failed (Exit)\n\n";

              (* Try slot 42 instead *)
              Printf.printf "Trying slot 42 instead...\n";
              begin try
                let slot_42 = Noun.slot (Z.of_int 42) kernel in
                Printf.printf "  āœ“ Found something at slot 42\n";

                (* Check if it's a formula or a gate *)
                Printf.printf "  Attempting to use as formula...\n";
                let poke_gate = Nock.nock_on kernel slot_42 in
                Printf.printf "  āœ“ Computed gate from slot 42\n\n";

                let wire = Noun.atom 0 in
                let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
                let ovum = Noun.cell wire card in
                let now = Noun.atom 0 in
                let event = Noun.cell now ovum in

                let result = slam_on poke_gate event in
                Printf.printf "  āœ“ Poke with slot 42 succeeded!\n\n";

                begin match result with
                | Noun.Cell _ ->
                    Printf.printf "šŸŽ‰ SLOT 42 WORKS!\n"
                | Noun.Atom _ ->
                    Printf.printf "Result is atom\n"
                end

              with
              | Noun.Exit -> Printf.printf "  āœ— Slot 42 also failed\n"
              | Not_found -> Printf.printf "  āœ— No slot 42\n"
              end
          | Not_found ->
              Printf.printf "  āœ— No slot 23 found\n"
          end

      | None ->
          Printf.printf "āœ— No event 1\n"
      end

  | Noun.Atom _ ->
      Printf.printf "āœ— Pill is atom\n"

let () =
  Printf.printf "\n═══════════════════════════════════════════════════════════\n";
  Printf.printf " Test C Vere Pattern on Solid Pill\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n\n";
  Eio_main.run test_poke