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.ml92
1 files changed, 83 insertions, 9 deletions
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml
index 9e3f17c..61bb202 100644
--- a/ocaml/lib/boot.ml
+++ b/ocaml/lib/boot.ml
@@ -174,9 +174,29 @@ let life eve =
Printf.printf "[Boot] About to execute: *[eve [2 [0 3] [0 2]]]\n%!";
Printf.printf "[Boot] This expands to: *[*[eve [0 3]] *[eve [0 2]]]\n%!";
+ (* Log eve structure before nock - matching C vortex.c:43-59 *)
+ Printf.printf "[Boot] eve is %s\n%!" (if Noun.is_cell eve then "cell" else "atom");
+ (match eve with
+ | Noun.Cell (eve_h, eve_t) ->
+ Printf.printf "[Boot] eve head is %s\n%!" (if Noun.is_cell eve_h then "cell" else "atom");
+ Printf.printf "[Boot] eve tail is %s\n%!" (if Noun.is_cell eve_t then "cell" else "atom");
+ (match eve_h with
+ | Noun.Cell (eve_hh, eve_ht) ->
+ Printf.printf "[Boot] eve head.head is %s\n%!"
+ (if Noun.is_atom eve_hh then
+ let z = match eve_hh with Noun.Atom z -> z | _ -> Z.zero in
+ "atom(" ^ Z.to_string z ^ ")"
+ else "cell");
+ Printf.printf "[Boot] eve head.tail is %s\n%!"
+ (if Noun.is_cell eve_ht then "cell" else "atom")
+ | _ -> ())
+ | _ -> ());
+
(* First, manually compute the two parts to see where it fails *)
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
@@ -189,9 +209,24 @@ let life eve =
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%!";
- Nock.nock_on slot3_result slot2_result
+ let result = Nock.nock_on slot3_result slot2_result in
+ Printf.printf "[Boot] ✓ Nock.nock_on returned successfully\n%!";
+ result
with e ->
Printf.printf "[Boot] ✗ Nock failed during lifecycle: %s\n%!"
(Printexc.to_string e);
@@ -443,9 +478,6 @@ let build_event_list bot mod_ use_ =
| _ -> acc
in
- (* Start with flipped bot events (NO timestamp) *)
- let eve = flip (Noun.Atom Z.zero) bot in
-
(* Weld mod and use lists *)
let rec weld l1 l2 =
match l1 with
@@ -456,7 +488,16 @@ let build_event_list bot mod_ use_ =
let lit = weld mod_ use_ in
- (* Add timestamped events *)
+ (* Start with flipped bot events (NO timestamp) *)
+ let eve = flip (Noun.Atom Z.zero) bot in
+
+ (* Add timestamped mod/use events by consing to FRONT
+ * This matches C Vere: eve = u3nc(u3nc(now, i), eve)
+ * After all events are added, eve looks like:
+ * [[time use_last] ... [time mod1] bot3 bot2 bot1 ~]
+ * Then we flip to get:
+ * [bot1 bot2 bot3 [time mod1] ... [time use_last]]
+ *)
let rec add_timestamped acc now_ref noun =
match noun with
| Noun.Atom z when Z.equal z Z.zero -> acc
@@ -468,10 +509,8 @@ let build_event_list bot mod_ use_ =
in
now_ref := new_now;
- (* Create [timestamp event] pair *)
+ (* Create [timestamp event] pair and cons to FRONT *)
let stamped = Noun.Cell (new_now, event) in
-
- (* Cons onto accumulator *)
let new_acc = Noun.Cell (stamped, acc) in
add_timestamped new_acc now_ref rest
@@ -481,10 +520,29 @@ let build_event_list bot mod_ use_ =
let now_ref = ref now in
let eve_with_stamped = add_timestamped eve now_ref lit in
- (* Flip final list *)
+ (* Flip final list to get: [bot1 bot2 bot3 [time mod1] ...] *)
let ova = flip (Noun.Atom Z.zero) eve_with_stamped in
Printf.printf "[Boot] ✓ Event list built: %d events\n%!" (count_list ova);
+
+ (* Debug: Check first few events *)
+ Printf.printf "[Boot] First event structure:\n%!";
+ (match ova with
+ | Noun.Cell (first, _) ->
+ Printf.printf "[Boot] first = %s\n%!"
+ (if Noun.is_cell first then "cell" else "atom");
+ (match first with
+ | Noun.Cell (h, t) ->
+ Printf.printf "[Boot] head = %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");
+ Printf.printf "[Boot] tail = %s\n%!"
+ (if Noun.is_cell t then "cell" else "atom")
+ | _ -> ())
+ | _ -> ());
+
ova
(* Boot lite - bootstrap ivory pill
@@ -608,6 +666,22 @@ let boot_solid ~fs state ivory_path solid_path =
(* Step 3.5: Synthesize events (C Vere mars.c:1763-1789) *)
Printf.printf "[3.5] Synthesizing events (like C Vere)...\n%!";
+ (* Debug: Check what's in first BOT event *)
+ Printf.printf " [Debug] Checking first BOT event structure:\n%!";
+ (match bot with
+ | Noun.Cell (first_bot, _) ->
+ Printf.printf " first_bot is %s\n%!"
+ (if Noun.is_cell first_bot then "cell" else "atom");
+ (match first_bot with
+ | Noun.Cell (h, _) ->
+ Printf.printf " first_bot head is %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")
+ | _ -> ())
+ | _ -> ());
+
(* Generate 4 synthetic MOD events *)
let synth_mod = synthesize_mod_events () in
Printf.printf " ✓ Generated 4 synthetic MOD events\n%!";