summaryrefslogtreecommitdiff
path: root/ocaml/lib/boot.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/lib/boot.ml')
-rw-r--r--ocaml/lib/boot.ml94
1 files changed, 72 insertions, 22 deletions
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml
index 92e4907..630da3b 100644
--- a/ocaml/lib/boot.ml
+++ b/ocaml/lib/boot.ml
@@ -121,7 +121,7 @@ let boot_fake state =
let pill = fake_pill () in
boot_from_pill state pill
-(* u3v_life: Execute lifecycle formula on ivory core
+(* u3v_life: Execute lifecycle formula to produce Arvo kernel
*
* From C Vere vortex.c:26:
* u3_noun lyf = u3nt(2, u3nc(0, 3), u3nc(0, 2)); // [2 [0 3] [0 2]]
@@ -129,10 +129,22 @@ let boot_fake state =
* u3_noun cor = u3k(u3x_at(7, gat));
*
* The lifecycle formula [2 [0 3] [0 2]] means:
- * - Opcode 2: nock on computed subject
- * - [0 3] gets the formula at slot 3
- * - [0 2] gets the sample at slot 2
- * This calls the lifecycle arm, then we extract slot 7 (context)
+ * - [0 2] gets slot 2 (head of list) = first event or formula
+ * - [0 3] gets slot 3 (tail of list) = rest of events
+ * - [2 formula subject] = nock(subject formula)
+ * - So this is: nock(tail head) = nock(rest-of-events first-event)
+ *
+ * CRITICAL: This formula expects a specific list structure!
+ * The first item should be a FORMULA, and the rest should be events to process.
+ *
+ * KEY INSIGHT from running C Vere:
+ * - When booting with `-B solid.pill`, Vere FIRST boots an embedded ivory pill
+ * - The ivory pill is booted with eve = null (empty list)!
+ * - THEN it processes the solid pill's events separately via poke
+ *
+ * So u3v_life() is used TWICE:
+ * 1. On ivory pill with null/empty event list → produces initial kernel
+ * 2. On solid pill's bot events → produces updated kernel
*)
let life eve =
try
@@ -144,17 +156,27 @@ let life eve =
Printf.printf "[Boot] Running lifecycle formula [2 [0 3] [0 2]]...\n%!";
- (* Debug: check what's in slot 2 and slot 3 *)
- (try
- let slot2 = Noun.slot (Z.of_int 2) eve in
- let slot3 = Noun.slot (Z.of_int 3) eve in
- Printf.printf "[Boot] Slot 2: %s\n%!"
- (if Noun.is_cell slot2 then "cell" else "atom");
- Printf.printf "[Boot] Slot 3: %s\n%!"
- (if Noun.is_cell slot3 then "cell" else "atom");
- with _ -> ());
-
- (* Run lifecycle formula on ivory core *)
+ (* Check if eve is null (for ivory pill boot) *)
+ let is_null = match eve with
+ | Noun.Atom z when Z.equal z Z.zero -> true
+ | _ -> false
+ in
+
+ if is_null then
+ Printf.printf "[Boot] Lifecycle on NULL event list (ivory pill)\n%!"
+ else begin
+ (* Debug: check what's in slot 2 and slot 3 *)
+ (try
+ let slot2 = Noun.slot (Z.of_int 2) eve in
+ let slot3 = Noun.slot (Z.of_int 3) eve in
+ Printf.printf "[Boot] Slot 2: %s\n%!"
+ (if Noun.is_cell slot2 then "cell" else "atom");
+ Printf.printf "[Boot] Slot 3: %s\n%!"
+ (if Noun.is_cell slot3 then "cell" else "atom");
+ with _ -> ())
+ end;
+
+ (* Run lifecycle formula *)
let gat =
try
Nock.nock_on eve lyf
@@ -165,28 +187,56 @@ let life eve =
in
Printf.printf "[Boot] ✓ Lifecycle formula completed\n%!";
- Printf.printf "[Boot] Result is: %s\n%!"
- (if Noun.is_cell gat then "cell" else "atom");
- (* Extract slot 7 (the context) from resulting gate *)
+ (* Extract slot 7 (the kernel) from resulting gate *)
let cor =
try
Noun.slot (Z.of_int 7) gat
with e ->
Printf.printf "[Boot] ✗ Failed to extract slot 7: %s\n%!"
(Printexc.to_string e);
- Printf.printf "[Boot] (Result type: %s)\n%!"
- (if Noun.is_cell gat then "cell" else "atom");
raise e
in
- Printf.printf "[Boot] ✓ Extracted slot 7 from result\n%!";
+ Printf.printf "[Boot] ✓ Extracted kernel from slot 7\n%!";
cor
with e ->
Printf.printf "[Boot] ✗ u3v_life failed: %s\n%!" (Printexc.to_string e);
raise e
+(* u3v_boot: Full boot sequence with event counting
+ *
+ * From C Vere vortex.c:39:
+ * - Counts events in the list
+ * - Calls u3v_life() safely
+ * - Stores result in u3A->roc (global kernel state)
+ * - Updates event counter u3A->eve_d
+ *)
+let boot state eve_list =
+ (* Count events *)
+ let rec count_events acc noun =
+ match noun with
+ | Noun.Atom _ -> acc
+ | Noun.Cell (_, rest) -> count_events (acc + 1) rest
+ in
+ let event_count = count_events 0 eve_list in
+
+ Printf.printf "[Boot] Booting with %d events\n%!" event_count;
+
+ try
+ (* Call u3v_life to produce kernel *)
+ let kernel = life eve_list in
+
+ (* Store in state *)
+ State.boot state kernel;
+
+ Printf.printf "[Boot] ✓ Boot complete!\n%!";
+ Ok ()
+
+ with e ->
+ Error ("Boot failed: " ^ Printexc.to_string e)
+
(* Boot from ivory pill - the lightweight boot sequence
*
* Ivory pills have structure: ["ivory" core]