blob: c87c5c8ee89f11108bb58ff48f8cdfc712404ef9 (
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
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
|
(* Boot Arvo using slam on slot 23 *)
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 boot_arvo _env =
Printf.printf "š Booting Arvo with Slot 23 Slam\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 *)
let kernel = ref None in
List.iteri (fun i event ->
Printf.printf "=== Event %d ===\n" i;
match event with
| Noun.Atom a ->
Printf.printf "Atom: %s\n\n" (Z.to_string a)
| Noun.Cell _ ->
if i = 1 then begin
(* Event 1: Initial larval kernel *)
Printf.printf "Initial larval kernel\n";
kernel := Some event;
(* Verify slot 23 exists *)
begin try
let _poke = Noun.slot (Z.of_int 23) event in
Printf.printf " ā Has poke gate at slot 23\n\n"
with _ ->
Printf.printf " ā No poke at slot 23\n\n"
end
end else if i > 2 then begin
(* Events 3-4: Larval initialization events *)
Printf.printf "Boot event (ovum)\n";
match !kernel with
| None ->
Printf.printf " ā No kernel yet\n\n"
| Some k ->
begin try
let poke_gate = Noun.slot (Z.of_int 23) k in
(* Build poke args: [now ovum] *)
(* The event itself should be the ovum [wire card] *)
let now = Noun.atom 0 in
let ovum = event in
let poke_arg = Noun.cell now ovum in
Printf.printf " ā Slamming poke at slot 23...\n";
let start = Unix.gettimeofday () in
let result = slam_on poke_gate poke_arg in
let elapsed = Unix.gettimeofday () -. start in
Printf.printf " ā Poke succeeded in %.4fs!\n" elapsed;
(* Parse result: [effects new-kernel] *)
begin match result with
| Noun.Cell (_effects, new_kernel) ->
Printf.printf " Result: [effects new-kernel]\n";
(* Update kernel *)
kernel := Some new_kernel;
Printf.printf " ā Kernel updated\n"
| Noun.Atom _ ->
Printf.printf " ā Result is atom (unexpected)\n"
end;
Printf.printf "\n"
with
| Noun.Exit ->
Printf.printf " ā Poke failed (Nock Exit)\n\n"
| e ->
Printf.printf " ā Error: %s\n\n" (Printexc.to_string e)
end
end else begin
Printf.printf "Separator/other\n\n"
end
) event_list;
(* Test final kernel *)
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n\n";
begin match !kernel with
| None ->
Printf.printf "ā No final kernel\n"
| Some k ->
Printf.printf "š Boot Complete!\n\n";
(* Check which slots exist in final kernel *)
Printf.printf "Checking final kernel:\n";
begin try
let _poke23 = Noun.slot (Z.of_int 23) k in
Printf.printf " ā Has slot 23 (larval poke)\n"
with _ ->
Printf.printf " ā No slot 23\n"
end;
begin try
let _poke42 = Noun.slot (Z.of_int 42) k in
Printf.printf " ā Has slot 42 (adult poke)\n"
with _ ->
Printf.printf " ā No slot 42\n"
end;
Printf.printf "\nTrying test poke on slot 42...\n";
(* Try slot 42 (adult Arvo) *)
begin try
let poke_gate = Noun.slot (Z.of_int 42) k in
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 poke_arg = Noun.cell now ovum in
Printf.printf " Slamming slot 42...\n";
let result = slam_on poke_gate poke_arg in
begin match result with
| Noun.Cell _ ->
Printf.printf " š SLOT 42 WORKS! ARVO IS RUNNING!\n"
| Noun.Atom _ ->
Printf.printf " Result is atom\n"
end
with
| Noun.Exit ->
Printf.printf " ā Slot 42 poke failed (Nock Exit)\n"
| e ->
Printf.printf " ā Error: %s\n" (Printexc.to_string e)
end;
Printf.printf "\nTrying test poke on slot 23...\n";
(* Also try slot 23 *)
begin try
let poke_gate = Noun.slot (Z.of_int 23) k in
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 poke_arg = Noun.cell now ovum in
Printf.printf " Slamming slot 23...\n";
let result = slam_on poke_gate poke_arg in
begin match result with
| Noun.Cell _ ->
Printf.printf " ā Slot 23 also works!\n"
| Noun.Atom _ ->
Printf.printf " Result is atom\n"
end
with
| Noun.Exit ->
Printf.printf " ā Slot 23 poke failed (Nock Exit)\n"
| e ->
Printf.printf " ā Error: %s\n" (Printexc.to_string e)
end
end
| Noun.Atom _ ->
Printf.printf "ā Pill is atom\n"
let () =
Printf.printf "\nāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n";
Printf.printf " Boot Arvo with Slot 23 Slam\n";
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n\n";
Eio_main.run boot_arvo
|