blob: 5679c3f2eb1d7f9e967cddb5ac12d25621d7276f (
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
|
(* Test the functional BIOS formula [2 [0 3] [0 2]] on event list *)
open Nock_lib
let test_bios _env =
Printf.printf "š Testing Functional BIOS Formula\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) ->
Printf.printf "Found events\n\n";
(* Build the functional BIOS formula: [2 [0 3] [0 2]] *)
Printf.printf "Building functional BIOS formula: [2 [0 3] [0 2]]\n";
let bios_formula = 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 "Formula: %s\n\n"
(match bios_formula with Noun.Cell _ -> "built" | _ -> "error");
(* Run the formula on the event list! *)
Printf.printf "Running formula on entire event list...\n";
Printf.printf "(This processes ALL 5 events at once!)\n\n";
let start = Unix.gettimeofday () in
begin try
let result = Nock.nock_on events bios_formula in
let elapsed = Unix.gettimeofday () -. start in
Printf.printf "ā Formula succeeded in %.4fs!\n\n" elapsed;
(* Extract slot 7 from result *)
Printf.printf "Extracting slot 7 from result...\n";
begin try
let kernel = Noun.slot (Z.of_int 7) result in
Printf.printf "ā Got kernel at slot 7!\n\n";
(* Check what slots this kernel has *)
Printf.printf "Checking kernel slots:\n";
begin try
let _poke23 = Noun.slot (Z.of_int 23) kernel 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) kernel in
Printf.printf " ā Has slot 42 (adult poke)\n"
with _ ->
Printf.printf " ā No slot 42\n"
end;
Printf.printf "\nš FUNCTIONAL BIOS BOOT COMPLETE!\n\n";
(* Try a test poke on slot 42 *)
Printf.printf "Testing poke on slot 42...\n";
begin try
let poke_gate = Noun.slot (Z.of_int 42) kernel in
(* Build test event *)
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
(* Slam *)
let battery = Noun.head poke_gate in
let context = Noun.tail (Noun.tail poke_gate) in
let new_core = Noun.cell battery (Noun.cell poke_arg context) in
let kick_formula = Noun.cell (Noun.atom 9)
(Noun.cell (Noun.atom 2)
(Noun.cell (Noun.atom 0) (Noun.atom 1))) in
let poke_result = Nock.nock_on new_core kick_formula in
begin match poke_result with
| Noun.Cell (_effects, _new_kernel) ->
Printf.printf " š SLOT 42 POKE WORKS!\n\n";
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n";
Printf.printf " ARVO IS FULLY BOOTED AND OPERATIONAL!\n";
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n\n";
Printf.printf "This means we can now:\n";
Printf.printf " ā
Run the functional BIOS formula\n";
Printf.printf " ā
Extract the booted kernel\n";
Printf.printf " ā
Poke events into Arvo\n";
Printf.printf " ā
Build a complete Urbit runtime!\n"
| Noun.Atom _ ->
Printf.printf " Result is atom\n"
end
with
| Noun.Exit ->
Printf.printf " ā Poke failed (Nock Exit)\n"
| e ->
Printf.printf " ā Error: %s\n" (Printexc.to_string e)
end
with
| Not_found ->
Printf.printf "ā No slot 7 in result\n"
| e ->
Printf.printf "ā Error accessing slot 7: %s\n" (Printexc.to_string e)
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 "ā Pill is atom\n"
let () =
Printf.printf "\nāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n";
Printf.printf " Test Functional BIOS Formula\n";
Printf.printf "āāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāāā\n\n";
Eio_main.run test_bios
|