blob: 21a9433ce8242bfaf8c761e964f48c6fe86b1879 (
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
|
(* Explore solid pill structure to find Arvo *)
open Nock_lib
let test_solid env =
Printf.printf "š Exploring Solid Pill Structure\n\n";
Eio.Switch.run @@ fun _sw ->
let _fs = Eio.Stdenv.fs env in
(* Load solid pill (use cached .noun for speed) *)
Printf.printf "Loading solid pill from cache...\n";
let in_channel = open_in_bin "solid.noun" in
let pill = (Marshal.from_channel in_channel : Noun.noun) in
close_in in_channel;
Printf.printf "ā Loaded from solid.noun\n\n";
(* Solid pill structure: [tag boot-events] *)
match pill with
| Noun.Atom _ ->
Printf.printf "ā Pill is an atom (unexpected)\n"
| Noun.Cell (tag, events) ->
Printf.printf "Pill structure: [tag events]\n";
begin match tag with
| Noun.Atom a ->
Printf.printf " Tag: %s (hex: 0x%s)\n"
(Z.to_string a) (Z.format "x" a)
| _ -> Printf.printf " Tag: cell\n"
end;
(* Events should be a list *)
Printf.printf "\nExploring boot events...\n";
let rec count_list n noun =
match noun with
| Noun.Atom _ -> (n, noun) (* terminator *)
| Noun.Cell (item, rest) ->
Printf.printf " Event %d: %s\n" n
(match item with
| Noun.Atom _ -> "atom"
| Noun.Cell _ -> "cell");
count_list (n + 1) rest
in
let (event_count, terminator) = count_list 0 events in
Printf.printf "\nTotal events: %d\n" event_count;
Printf.printf "Terminator: %s\n\n"
(match terminator with
| Noun.Atom a -> Printf.sprintf "atom %s" (Z.to_string a)
| Noun.Cell _ -> "cell");
(* The 5th event should be the final Arvo kernel *)
Printf.printf "Extracting final Arvo kernel (last event)...\n";
let rec get_last noun =
match noun with
| Noun.Atom _ -> None
| Noun.Cell (item, rest) ->
match rest with
| Noun.Atom _ -> Some item (* This is the last *)
| Noun.Cell _ -> get_last rest
in
match get_last events with
| None -> Printf.printf "ā Could not find last event\n"
| Some last_event ->
Printf.printf "ā Found last event\n";
(* Last event structure: [wire card] where card produces Arvo *)
begin match last_event with
| Noun.Cell (_wire, card) ->
Printf.printf " Event is [wire card]\n";
Printf.printf " Card: %s\n\n"
(match card with
| Noun.Atom _ -> "atom"
| Noun.Cell _ -> "cell");
(* Try to run this event to get Arvo *)
Printf.printf "Attempting to extract Arvo kernel...\n";
(* The card might be the kernel directly, or we need to eval it *)
(* Let's check if card has the poke interface at slot 23 *)
begin try
let potential_arvo = card in
let _gate = Noun.slot (Z.of_int 23) potential_arvo in
Printf.printf "ā Found gate at slot 23 in card!\n";
Printf.printf "\nThis looks like the Arvo kernel!\n";
Printf.printf "Let's explore it...\n\n";
(* Show structure *)
for i = 2 to 30 do
try
let slot_val = Noun.slot (Z.of_int i) potential_arvo in
let typ = match slot_val with
| Noun.Cell _ -> "cell"
| Noun.Atom _ -> "atom"
in
Printf.printf " Slot %d: %s\n" i typ
with _ -> ()
done;
Printf.printf "\nš Found Arvo in solid pill!\n"
with _ ->
Printf.printf "ā No gate at slot 23\n";
Printf.printf "Card might need to be evaluated first\n"
end
| _ ->
Printf.printf " Event is not a cell\n"
end
let () =
Printf.printf "\n";
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n";
Printf.printf " Exploring Solid Pill Structure\n";
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n";
Printf.printf "\n";
Eio_main.run test_solid
|