blob: 3aa2150e78905e79b00530bb5743e7ea34293e6c (
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
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
|
(* Debug exactly what happens when we slam Event 4 *)
open Nock_lib
let slam_on gate event =
Printf.printf " Building slam...\n";
let battery = Noun.head gate in
Printf.printf " Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
let payload = Noun.tail gate in
Printf.printf " Payload: %s\n" (match payload with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
let context = Noun.tail payload in
Printf.printf " Context (slot 7): %s\n" (match context with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
let new_core = Noun.cell battery (Noun.cell event context) in
Printf.printf " New core: built\n";
let kick_formula = Noun.cell (Noun.atom 9)
(Noun.cell (Noun.atom 2)
(Noun.cell (Noun.atom 0) (Noun.atom 1))) in
Printf.printf " Kick formula: [9 2 0 1]\n";
Printf.printf " Executing Nock...\n%!";
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 debug _env =
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
(* Get Event 1 (initial kernel) *)
let kernel1 = List.nth event_list 1 in
(* Slam Event 3 to get kernel after Event 3 *)
let event3 = List.nth event_list 3 in
Printf.printf "\n=== SLAMMING EVENT 3 ===\n\n";
let poke_gate3 = Noun.slot (Z.of_int 23) kernel1 in
let now3 = Noun.atom 0 in
let poke_arg3 = Noun.cell now3 event3 in
let result3 = slam_on poke_gate3 poke_arg3 in
let kernel_after_3 = match result3 with
| Noun.Cell (_effects, new_kernel) ->
Printf.printf "✓ Event 3 succeeded\n\n";
new_kernel
| Noun.Atom _ ->
Printf.printf "✗ Event 3 returned atom\n";
kernel1
in
(* Now try Event 4 *)
let event4 = List.nth event_list 4 in
Printf.printf "=== SLAMMING EVENT 4 ===\n\n";
Printf.printf "Event 4 structure:\n";
begin match event4 with
| Noun.Cell (wire, card) ->
Printf.printf " [wire card]\n";
Printf.printf " Wire: %s\n" (match wire with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
begin match card with
| Noun.Cell (term, data) ->
Printf.printf " Card: [term data]\n";
Printf.printf " Term: %s\n" (match term with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
Printf.printf " Data: %s\n\n" (match data with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
| _ -> ()
end
| _ -> Printf.printf " Not [wire card]\n\n"
end;
Printf.printf "Kernel after Event 3:\n";
begin try
let _poke23 = Noun.slot (Z.of_int 23) kernel_after_3 in
Printf.printf " ✓ Has slot 23\n"
with _ ->
Printf.printf " ✗ No slot 23\n"
end;
begin try
let _poke42 = Noun.slot (Z.of_int 42) kernel_after_3 in
Printf.printf " ✓ Has slot 42\n\n"
with _ ->
Printf.printf " ✗ No slot 42\n\n"
end;
Printf.printf "Attempting Event 4 slam...\n";
begin try
let poke_gate4 = Noun.slot (Z.of_int 23) kernel_after_3 in
Printf.printf " ✓ Found poke gate at slot 23\n";
let now4 = Noun.atom 0 in
let poke_arg4 = Noun.cell now4 event4 in
Printf.printf " Poke arg: [now ovum]\n\n";
let result4 = slam_on poke_gate4 poke_arg4 in
begin match result4 with
| Noun.Cell (_effects, _new_kernel) ->
Printf.printf "\n🎉 EVENT 4 SUCCEEDED!\n"
| Noun.Atom _ ->
Printf.printf "\nResult is atom\n"
end
with
| Noun.Exit ->
Printf.printf "\n✗ Nock Exit - examining gate structure...\n\n";
(* Try to understand why it failed *)
begin try
let poke_gate4 = Noun.slot (Z.of_int 23) kernel_after_3 in
Printf.printf "Poke gate structure:\n";
begin match poke_gate4 with
| Noun.Cell (battery, payload) ->
Printf.printf " Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
begin match payload with
| Noun.Cell (sample, context) ->
Printf.printf " Payload: [sample context]\n";
Printf.printf " Sample: %s\n" (match sample with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
Printf.printf " Context: %s\n" (match context with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell")
| _ ->
Printf.printf " Payload: %s (not [sample context])\n"
(match payload with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell")
end
| Noun.Atom _ ->
Printf.printf " Poke gate is an atom!\n"
end
with e ->
Printf.printf "Error examining gate: %s\n" (Printexc.to_string e)
end
| e ->
Printf.printf "\n✗ Error: %s\n" (Printexc.to_string e)
end
| Noun.Atom _ ->
Printf.printf "Pill is atom\n"
let () =
Printf.printf "\n═══════════════════════════════════════════\n";
Printf.printf " Debug Event 4 Slam\n";
Printf.printf "═══════════════════════════════════════════\n\n";
Eio_main.run debug
|