blob: ef10785dda8388a1ce66c0e189c378d8961eb6c2 (
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
|
(* Parse solid pill structure to extract [bot mod use] *)
open Nock_lib
let rec to_list acc noun =
match noun with
| Noun.Atom _ -> List.rev acc
| Noun.Cell (item, rest) -> to_list (item :: acc) rest
let parse_pill _env =
Printf.printf "═══════════════════════════════════════\n";
Printf.printf " Parsing Solid Pill Structure\n";
Printf.printf "═══════════════════════════════════════\n\n";
(* Load the pill *)
let in_channel = open_in_bin "solid.noun" in
let pill = (Marshal.from_channel in_channel : Noun.noun) in
close_in in_channel;
(* According to C Vere mars.c:1560, solid pill structure is:
* First we cue pil_p (the jammed pill data)
* Then we expect: [tag dat]
* Where:
* tag = %pill or %cash
* dat = [type [bot mod use]] or [[cache] [type [bot mod use]]]
*)
Printf.printf "Step 1: Check outer structure\n";
match pill with
| Noun.Cell (tag, rest) ->
Printf.printf " ✓ Pill is a cell [tag rest]\n";
(* Check what the tag is *)
begin match tag with
| Noun.Atom z ->
let tag_str =
try
let bytes = Z.to_bits z in
let len = String.length bytes in
if len > 0 && len <= 20 then
String.sub bytes 0 (min len 20)
else "too-long"
with _ -> "non-ascii"
in
Printf.printf " Tag (atom): %s\n" tag_str;
Printf.printf " Tag (hex): %s\n\n" (Z.format "x" z);
| Noun.Cell _ ->
Printf.printf " Tag is a cell (unexpected!)\n\n"
end;
(* Now parse rest based on structure *)
Printf.printf "Step 2: Parse pill contents\n";
(* Try to extract as [type [bot mod use]] *)
begin match rest with
| Noun.Cell (typ, rest2) ->
Printf.printf " ✓ rest = [type rest2]\n";
begin match typ with
| Noun.Atom z ->
let typ_str =
try
let bytes = Z.to_bits z in
String.sub bytes 0 (min (String.length bytes) 20)
with _ -> "non-ascii"
in
Printf.printf " Type: %s\n\n" typ_str;
| Noun.Cell _ ->
Printf.printf " Type is cell\n\n"
end;
(* Now try to parse rest2 as [bot mod use] *)
begin match rest2 with
| Noun.Cell (bot, rest3) ->
Printf.printf " ✓ Found bot (boot events)\n";
let bot_list = to_list [] bot in
Printf.printf " Bot has %d events\n" (List.length bot_list);
begin match rest3 with
| Noun.Cell (mod_, rest4) ->
Printf.printf " ✓ Found mod (module events)\n";
let mod_list = to_list [] mod_ in
Printf.printf " Mod has %d events\n" (List.length mod_list);
begin match rest4 with
| Noun.Cell (use, _) ->
Printf.printf " ✓ Found use (userspace events)\n";
let use_list = to_list [] use in
Printf.printf " Use has %d events\n\n" (List.length use_list);
(* Total events *)
let total = List.length bot_list + List.length mod_list + List.length use_list in
Printf.printf "═══════════════════════════════════════\n";
Printf.printf " Summary\n";
Printf.printf "═══════════════════════════════════════\n\n";
Printf.printf "Total events: %d\n" total;
Printf.printf " Bot: %d events (lifecycle)\n" (List.length bot_list);
Printf.printf " Mod: %d events (vanes)\n" (List.length mod_list);
Printf.printf " Use: %d events (apps)\n\n" (List.length use_list);
(* Concatenate all events *)
let all_events = bot_list @ mod_list @ use_list in
Printf.printf "Creating full event list...\n";
(* Convert list back to noun list (NOT a proper list yet) *)
let rec make_noun_list events =
match events with
| [] -> Noun.atom 0 (* null terminator *)
| [e] -> Noun.cell e (Noun.atom 0)
| e :: rest -> Noun.cell e (make_noun_list rest)
in
let event_noun = make_noun_list all_events in
Printf.printf "✓ Event list created\n\n";
(* Now test functional BIOS formula! *)
Printf.printf "═══════════════════════════════════════\n";
Printf.printf " Testing Functional BIOS Formula\n";
Printf.printf "═══════════════════════════════════════\n\n";
Printf.printf "Formula: [2 [0 3] [0 2]]\n";
Printf.printf "Subject: %d-event list\n\n" total;
(* Build lifecycle formula: [2 [0 3] [0 2]] *)
let lyf = Noun.cell (Noun.atom 2)
(Noun.cell
(Noun.cell (Noun.atom 0) (Noun.atom 3))
(Noun.cell (Noun.atom 0) (Noun.atom 2))) in
Printf.printf "Running formula...\n%!";
begin try
let start = Unix.gettimeofday () in
let gat = Nock.nock_on event_noun lyf in
let elapsed = Unix.gettimeofday () -. start in
Printf.printf "✓ Formula completed in %.4fs!\n\n" elapsed;
(* Extract slot 7 *)
Printf.printf "Extracting kernel from slot 7...\n";
let kernel = Noun.slot (Z.of_int 7) gat in
Printf.printf "✓ Kernel extracted!\n\n";
Printf.printf "═══════════════════════════════════════\n";
Printf.printf " 🎉 SUCCESS! Functional BIOS Works! 🎉\n";
Printf.printf "═══════════════════════════════════════\n\n";
Printf.printf "The kernel has been computed from the event list\n";
Printf.printf "using the functional BIOS formula.\n\n";
(* Check kernel has slot 23 *)
begin try
let _poke = Noun.slot (Z.of_int 23) kernel in
Printf.printf "✓ Kernel has poke gate at slot 23\n"
with _ ->
Printf.printf "✗ No slot 23 in kernel\n"
end
with
| Noun.Exit ->
Printf.printf "✗ Formula failed (Nock Exit)\n"
| e ->
Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
end
| Noun.Atom _ ->
Printf.printf " ✗ rest4 is atom (expected use)\n"
end
| Noun.Atom _ ->
Printf.printf " ✗ rest3 is atom (expected [mod use])\n"
end
| Noun.Atom _ ->
Printf.printf " ✗ rest2 is atom (expected [bot mod use])\n"
end
| Noun.Atom _ ->
Printf.printf " ✗ rest is atom\n"
end
| Noun.Atom _ ->
Printf.printf "✗ Pill is an atom (expected cell)\n"
let () =
Printf.printf "\n═══════════════════════════════════════\n";
Printf.printf " Parse Solid Pill Structure\n";
Printf.printf "═══════════════════════════════════════\n\n";
Eio_main.run parse_pill
|