summaryrefslogtreecommitdiff
path: root/ocaml/lib/boot.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 21:27:31 +0700
committerpolwex <polwex@sortug.com>2025-10-06 21:27:31 +0700
commit6ce2c5919f36776fe8aea711b94bbd2d64c8207a (patch)
treef79796c7ea188ed25a2bb0642bebe6dc0d05409c /ocaml/lib/boot.ml
parentbcbd110b17b3c9bcb0e28e28fd33388f1c954a27 (diff)
going in circles man
Diffstat (limited to 'ocaml/lib/boot.ml')
-rw-r--r--ocaml/lib/boot.ml101
1 files changed, 67 insertions, 34 deletions
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml
index 61bb202..f8289ec 100644
--- a/ocaml/lib/boot.ml
+++ b/ocaml/lib/boot.ml
@@ -192,39 +192,21 @@ let life eve =
| _ -> ())
| _ -> ());
- (* First, manually compute the two parts to see where it fails *)
+ (* Call lifecycle formula directly like C does *)
let gat =
try
Printf.printf "[Boot] calling Nock.nock_on(eve, [2 [0 3] [0 2]])...\n%!";
- (* Step 1: Compute *[eve [0 3]] = slot 3 of eve *)
- Printf.printf "[Boot] Step 1: Computing *[eve [0 3]] (slot 3 of subject)...\n%!";
- let slot3_result = Nock.nock_on eve (Noun.cell (Noun.atom 0) (Noun.atom 3)) in
- Printf.printf "[Boot] ✓ Slot 3 computed: %s\n%!"
- (if Noun.is_cell slot3_result then "cell" else "atom");
-
- (* Step 2: Compute *[eve [0 2]] = slot 2 of eve *)
- Printf.printf "[Boot] Step 2: Computing *[eve [0 2]] (slot 2 of subject)...\n%!";
- let slot2_result = Nock.nock_on eve (Noun.cell (Noun.atom 0) (Noun.atom 2)) in
- Printf.printf "[Boot] ✓ Slot 2 computed: %s\n%!"
- (if Noun.is_cell slot2_result then "cell" else "atom");
-
- (* Debug: check if slot2 looks like a valid Nock formula *)
- Printf.printf "[Boot] Checking slot2 structure (should be a formula):\n%!";
- (match slot2_result with
- | Noun.Cell (h, t) ->
- Printf.printf "[Boot] slot2 = [%s %s]\n%!"
- (if Noun.is_atom h then
- let z = match h with Noun.Atom z -> z | _ -> Z.zero in
- "atom(" ^ Z.to_string z ^ ")"
- else "cell")
- (if Noun.is_atom t then "atom" else "cell")
- | Noun.Atom z ->
- Printf.printf "[Boot] slot2 = atom(%s)\n%!" (Z.to_string z));
-
- (* Step 3: Compute *[slot3_result slot2_result] *)
- Printf.printf "[Boot] Step 3: Computing *[slot3 slot2] (nock slot-2 formula on slot-3 subject)...\n%!";
- let result = Nock.nock_on slot3_result slot2_result in
+ (* Build the lifecycle formula: [2 [0 3] [0 2]] *)
+ let lifecycle_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
+
+ let result = Nock.nock_on eve lifecycle_formula in
Printf.printf "[Boot] ✓ Nock.nock_on returned successfully\n%!";
result
with e ->
@@ -559,17 +541,68 @@ let boot_lite ~fs state ivory_path =
Printf.printf "[Lite Boot] Cuing ivory pill...\n%!";
let pil = Serial.cue pill_bytes in
- (* Ivory pill is [%ivory core], extract the core *)
+ (* Ivory pill is [%ivory event_list] - run lifecycle like C does *)
if not (Noun.is_cell pil) then begin
Printf.printf "[Lite Boot] ✗ Pill is not a cell\n%!";
Error "Ivory pill must be a cell"
end else begin
- let _tag = Noun.head pil in
- let core = Noun.tail pil in
+ let tag = Noun.head pil in
+ let eve = Noun.tail pil in
+
+ (* Log tag info *)
+ Printf.printf "[Lite Boot] Tag is %s\n%!"
+ (if Noun.is_atom tag then "atom" else "cell");
+ Printf.printf "[Lite Boot] Event list is %s\n%!"
+ (if Noun.is_atom eve then "atom" else "cell (list)");
+
+ (* Run u3v_life: execute lifecycle formula on event list *)
+ Printf.printf "[Lite Boot] Running lifecycle formula on ivory events...\n%!";
+
+ (* Enable slot debugging *)
+ Noun.slot_debug := true;
+
+ (* Debug: Check pill structure *)
+ let rec lent n =
+ match n with
+ | Noun.Atom _ when Noun.equal n (Noun.atom 0) -> 0
+ | Noun.Cell (_, t) -> 1 + lent t
+ | _ -> 0
+ in
+ let pil_len = lent pil in
+ let eve_len = lent eve in
+ Printf.printf "[Lite Boot] DEBUG: pil has %d elements, eve has %d elements\n%!" pil_len eve_len;
+
+ (* Debug: Dump head(eve) structure in detail *)
+ let rec dump_noun depth max_depth n =
+ if depth >= max_depth then "..."
+ else match n with
+ | Noun.Atom z -> Z.to_string z
+ | Noun.Cell (h, t) ->
+ "[" ^ dump_noun (depth+1) max_depth h ^ " " ^
+ dump_noun (depth+1) max_depth t ^ "]"
+ in
+ let eve_head = Noun.head eve in
+ Printf.printf "[Lite Boot] DEBUG: head(eve) structure (depth 5):\n%s\n%!"
+ (dump_noun 0 5 eve_head);
+
+ (* Build the lifecycle formula: [2 [0 3] [0 2]] *)
+ let lifecycle_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
+
+ (* Execute the lifecycle formula to produce kernel *)
+ let gat = Nock.nock_on eve lifecycle_formula in
+
+ (* Extract slot 7 (the kernel) from resulting gate *)
+ let core = Noun.slot (Z.of_int 7) gat in
- Printf.printf "[Lite Boot] Extracted ivory core, setting as kernel\n%!";
+ Printf.printf "[Lite Boot] ✓ Lifecycle completed\n%!";
- (* Set the core directly as the kernel - no lifecycle formula needed *)
+ (* Set the resulting core as the kernel *)
State.boot state core;
Printf.printf "[Lite Boot] ✓ Ivory kernel booted!\n\n%!";