(* Boot - Arvo Kernel Boot System * * This module handles: * - Loading pill files (jammed Arvo kernels) * - Parsing pill structure * - Initial boot sequence * * Pill Structure: * - A pill is a jammed noun containing the Arvo kernel * - Format varies, but typically: [kernel-gate initial-state] * - Or just the kernel-gate itself *) (* Boot error *) type error = | FileNotFound of string | InvalidPill of string | BootFailed of string (* Pill type *) type pill = { kernel: Noun.noun; (* The Arvo kernel gate *) boot_ova: Noun.noun list; (* Initial events to process *) } (* Load pill from file using Eio * * Steps: * 1. Read jammed pill file * 2. Cue to get kernel noun * 3. Parse pill structure *) let load_pill ~fs pill_path = try Printf.printf "[Boot] Loading pill from %s...\n%!" pill_path; (* Read pill file *) let file_path = Eio.Path.(fs / pill_path) in let pill_bytes = Eio.Path.load file_path |> Bytes.of_string in Printf.printf "[Boot] Pill file: %d bytes (%.1f MB)\n%!" (Bytes.length pill_bytes) (float_of_int (Bytes.length pill_bytes) /. 1024.0 /. 1024.0); Printf.printf "[Boot] Cuing pill (this may take a while)...\n%!"; let start = Unix.gettimeofday () in (* Cue the pill to get kernel noun *) let kernel_noun = Serial.cue pill_bytes in let elapsed = Unix.gettimeofday () -. start in Printf.printf "[Boot] Pill cued successfully in %.2f seconds\n%!" elapsed; (* For now, treat the entire pill as the kernel * In a real implementation, we'd parse the structure: * - Check if it's a cell with [kernel boot-events] * - Or just a single kernel gate *) Ok { kernel = kernel_noun; boot_ova = []; (* No boot events for now *) } with | Sys_error msg -> Error (FileNotFound msg) | e -> Error (InvalidPill (Printexc.to_string e)) (* Create a minimal fake pill for testing * * This creates a trivial kernel that's just an atom. * In reality, the kernel is a huge compiled gate, but for * testing we can use this simple version. *) let fake_pill () = { kernel = Noun.atom 0; (* Minimal kernel - just 0 *) boot_ova = []; } (* Boot Arvo from a pill * * Steps: * 1. Set kernel state to pill's kernel * 2. Process boot events if any * 3. Initialize event counter to 0 *) let boot_from_pill state pill = Printf.printf "[Boot] Initializing Arvo kernel...\n%!"; (* Set kernel state *) State.boot state pill.kernel; (* Process boot events if any *) List.iteri (fun i _ovum -> Printf.printf "[Boot] Processing boot event %d\n%!" i; (* In real implementation: State.poke state ovum *) ) pill.boot_ova; Printf.printf "[Boot] ✓ Arvo kernel booted!\n%!"; Ok () (* Boot from pill file - convenience function *) let boot_from_file ~fs state pill_path = match load_pill ~fs pill_path with | Error err -> let msg = match err with | FileNotFound s -> "File not found: " ^ s | InvalidPill s -> "Invalid pill: " ^ s | BootFailed s -> "Boot failed: " ^ s in Printf.printf "[Boot] Error: %s\n%!" msg; Error msg | Ok pill -> boot_from_pill state pill (* Create minimal boot for testing (no pill file needed) *) let boot_fake state = Printf.printf "[Boot] Creating fake minimal kernel...\n%!"; let pill = fake_pill () in boot_from_pill state pill (* 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]] * u3_noun gat = u3n_nock_on(eve, lyf); * u3_noun cor = u3k(u3x_at(7, gat)); * * The lifecycle formula [2 [0 3] [0 2]] means: * - [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 Printf.printf "[Boot] Running lifecycle formula [2 [0 3] [0 2]]...\n%!"; (* 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 *) 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%!"; (* First, manually compute the two parts to see where it fails *) let gat = try (* 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"); (* 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 with e -> Printf.printf "[Boot] ✗ Nock failed during lifecycle: %s\n%!" (Printexc.to_string e); raise e in Printf.printf "[Boot] ✓ Lifecycle formula completed\n%!"; (* 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); raise e in 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) (* Parse solid pill structure: [%pill %solid [bot mod use]] * * Following actual solid pill format (not wrapped in %boot) *) let parse_solid_pill pil = if not (Noun.is_cell pil) then Error "Pill must be a cell" else let tag = Noun.head pil in let rest = Noun.tail pil in (* Debug: print actual tag value *) (match tag with | Noun.Atom z -> Printf.printf "[Debug] Tag is atom: %s (hex: %s)\n%!" (Z.to_string z) (Z.format "x" z) | Noun.Cell _ -> Printf.printf "[Debug] Tag is cell (unexpected!)\n%!"); (* Check for %pill tag *) let pill_tag = Z.of_string "1819044208" in (* "pill" = 0x6c6c6970 *) begin match tag with | Noun.Atom z when Z.equal z pill_tag -> (* rest should be [%solid bot mod use], extract all 4 *) if not (Noun.is_cell rest) then Error "Pill rest must be a cell" else (* Extract using u3r_qual pattern: [a b c d] *) let typ = Noun.head rest in let rest1 = Noun.tail rest in Printf.printf "[Debug] typ (should be %%solid): %s\n%!" (if Noun.is_atom typ then "atom" else "cell"); Printf.printf "[Debug] rest1 structure: %s\n%!" (if Noun.is_cell rest1 then "cell" else "atom"); if not (Noun.is_cell rest1) then Error "After typ, expected [bot mod use]" else let bot = Noun.head rest1 in let rest2 = Noun.tail rest1 in Printf.printf "[Debug] bot: %s\n%!" (if Noun.is_cell bot then "cell (list)" else "atom"); Printf.printf "[Debug] rest2 (should be [mod use]): %s\n%!" (if Noun.is_cell rest2 then "cell" else "atom"); if not (Noun.is_cell rest2) then Error "After bot, expected [mod use]" else (* u3r_qual extracts [typ bot mod use] as: * typ = head(dat) * bot = head(tail(dat)) * mod = head(tail(tail(dat))) * use = tail(tail(tail(dat))) <- NOTE: TAIL, not head! * * So rest2 = [mod use], where: * mod = head(rest2) * use = tail(rest2) <- This is just 'use', not [use cax] *) let mod_ = Noun.head rest2 in let use_ = Noun.tail rest2 in Printf.printf "[Debug] mod: %s\n%!" (if Noun.is_cell mod_ then "cell (list)" else "atom"); Printf.printf "[Debug] use: %s\n%!" (if Noun.is_cell use_ then "cell (list)" else "atom"); Ok (bot, mod_, use_) | Noun.Atom _ -> Error "Expected %pill tag" | Noun.Cell _ -> Error "Expected %pill tag (got cell)" end (* Helper: Convert string to atom (big-endian bytes) *) let string_to_atom s = let len = String.length s in let rec loop i acc = if i < 0 then acc else let byte = Char.code s.[i] in loop (i - 1) (Z.add (Z.mul acc (Z.of_int 256)) (Z.of_int byte)) in Noun.Atom (loop (len - 1) Z.zero) (* Synthesize the 4 MOD events - following C Vere mars.c:1763-1779 *) let synthesize_mod_events () = (* Wire for all mod events: [%$ %arvo ~] which is [0 'arvo' 0] *) let arvo_str = string_to_atom "arvo" in let wir = Noun.cell (Noun.Atom Z.zero) (Noun.cell arvo_str (Noun.Atom Z.zero)) in (* 1. wack: entropy card [%wack [16 random words]] *) let eny_words = Array.init 16 (fun _ -> Random.int64 Int64.max_int) in (* Build list of entropy words *) let rec build_word_list i acc = if i < 0 then acc else build_word_list (i - 1) (Noun.cell (Noun.Atom (Z.of_int64 eny_words.(i))) acc) in let eny_noun = build_word_list 15 (Noun.Atom Z.zero) in let wack_tag = string_to_atom "wack" in let wack_card = Noun.cell wack_tag eny_noun in let wack = Noun.cell (wir) wack_card in (* 2. whom: identity card [%whom ship] *) let who = Noun.Atom Z.zero in (* ~zod = 0 *) let whom_tag = string_to_atom "whom" in let whom_card = Noun.cell whom_tag who in let whom = Noun.cell (wir) whom_card in (* 3. verb: verbose flag [%verb ~ 0] (0 = verbose off) *) let verb_tag = string_to_atom "verb" in let verb_card = Noun.cell verb_tag (Noun.cell (Noun.Atom Z.zero) (Noun.Atom Z.zero)) in let verb = Noun.cell (wir) verb_card in (* 4. wyrd: version card - simplified for now *) (* TODO: Implement proper version card like _mars_wyrd_card *) let wyrd_tag = string_to_atom "wyrd" in let wyrd_card = Noun.cell wyrd_tag (Noun.Atom Z.zero) in let wyrd = Noun.cell wir wyrd_card in (* Build list: [wack whom verb wyrd ~] *) Noun.cell wack (Noun.cell whom (Noun.cell verb (Noun.cell wyrd (Noun.Atom Z.zero)))) (* Synthesize legacy boot USE event - following C Vere mars.c:1785-1789 *) let synthesize_boot_event () = (* Wire: [%d %term '1' ~] which is ['d' 'term' 0x31 0] *) let d = string_to_atom "d" in let term = string_to_atom "term" in let one = Noun.Atom (Z.of_int 0x31) in (* ASCII '1' *) let wir = Noun.cell d (Noun.cell term (Noun.cell one (Noun.Atom Z.zero))) in (* Card: [%boot lit ven] - simplified *) (* lit = 0 (c3n = false), ven will be filled in properly later *) let boot_tag = string_to_atom "boot" in let lit = Noun.Atom Z.zero in let ven = Noun.Atom Z.zero in (* Placeholder for now *) let cad = Noun.cell boot_tag (Noun.cell lit ven) in Noun.cell wir cad (* Build event list following C Vere mars.c:1814-1836 * * Key: Bot events are NOT timestamped (bare atoms/cells) * Mod/use events ARE timestamped as [timestamp event] *) let build_event_list bot mod_ use_ = (* Count events *) let rec count_list noun = match noun with | Noun.Atom z when Z.equal z Z.zero -> 0 | Noun.Cell (_, rest) -> 1 + count_list rest | _ -> 0 in let bot_c = count_list bot in let mod_c = count_list mod_ in let use_c = count_list use_ in Printf.printf "[Boot] Building event list:\n%!"; Printf.printf " Bot events: %d (NO timestamp)\n%!" bot_c; Printf.printf " Mod events: %d (WITH timestamp)\n%!" mod_c; Printf.printf " Use events: %d (WITH timestamp)\n%!" use_c; Printf.printf " Total: %d events\n%!" (bot_c + mod_c + use_c); (* Get current time in Urbit format (128-bit @da timestamp) *) let now_timeval = Unix.gettimeofday () in (* Convert to microseconds since Unix epoch *) let now_us = Int64.of_float (now_timeval *. 1_000_000.0) in (* Urbit epoch is ~292 billion years before Unix epoch For now, use simplified timestamp *) let now = Noun.Atom (Z.of_int64 now_us) in (* 1/2^16 seconds increment *) let bit = Noun.Atom (Z.shift_left Z.one 48) in (* Helper: flip a list *) let rec flip acc noun = match noun with | Noun.Atom z when Z.equal z Z.zero -> acc | Noun.Cell (h, t) -> flip (Noun.Cell (h, acc)) t | _ -> 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 | Noun.Atom z when Z.equal z Z.zero -> l2 | Noun.Cell (h, t) -> Noun.Cell (h, weld t l2) | _ -> l2 in let lit = weld mod_ use_ in (* Add timestamped events *) let rec add_timestamped acc now_ref noun = match noun with | Noun.Atom z when Z.equal z Z.zero -> acc | Noun.Cell (event, rest) -> (* Increment timestamp *) let new_now = match !now_ref, bit with | Noun.Atom n, Noun.Atom b -> Noun.Atom (Z.add n b) | _ -> !now_ref in now_ref := new_now; (* Create [timestamp event] pair *) 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 | _ -> acc in let now_ref = ref now in let eve_with_stamped = add_timestamped eve now_ref lit in (* Flip final list *) let ova = flip (Noun.Atom Z.zero) eve_with_stamped in Printf.printf "[Boot] ✓ Event list built: %d events\n%!" (count_list ova); ova (* Boot lite - bootstrap ivory pill * * Following C Vere king.c:283 u3v_boot_lite * The ivory pill is [%ivory core], we extract the core *) let boot_lite ~fs state ivory_path = Printf.printf "[Lite Boot] Loading ivory pill from %s...\n%!" ivory_path; let file_path = Eio.Path.(fs / ivory_path) in let pill_bytes = Eio.Path.load file_path |> Bytes.of_string in Printf.printf "[Lite Boot] Cuing ivory pill...\n%!"; let pil = Serial.cue pill_bytes in (* Ivory pill is [%ivory core], extract the core *) 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 Printf.printf "[Lite Boot] Extracted ivory core, setting as kernel\n%!"; (* Set the core directly as the kernel - no lifecycle formula needed *) State.boot state core; Printf.printf "[Lite Boot] ✓ Ivory kernel booted!\n\n%!"; Ok () end (* Boot from solid pill - following C Vere -B flag logic * * CRITICAL: Must boot ivory FIRST, then solid events! * * This follows the exact flow from BOOT_FLOW.md: * Phase 1: Boot ivory pill (creates minimal kernel) * Phase 2: Boot solid events (metamorphosis to full kernel) * * Skipping disk persistence for now (steps 4-5 in C flow) *) let boot_solid ~fs state ivory_path solid_path = Printf.printf "\n%!"; Printf.printf "═══════════════════════════════════════════════════\n%!"; Printf.printf " Solid Pill Boot (Following C Vere -B Logic)\n%!"; Printf.printf "═══════════════════════════════════════════════════\n\n%!"; (* PHASE 1: Boot ivory pill first *) Printf.printf "PHASE 1: IVORY BOOTSTRAP\n%!"; Printf.printf "─────────────────────────────────────────────────\n%!"; (match boot_lite ~fs state ivory_path with | Error msg -> Error ("Ivory boot failed: " ^ msg) | Ok () -> Printf.printf "─────────────────────────────────────────────────\n\n%!"; (* PHASE 2: Boot solid events *) Printf.printf "PHASE 2: SOLID PILL BOOT\n%!"; Printf.printf "─────────────────────────────────────────────────\n\n%!"; (* Step 1: Load pill file *) Printf.printf "[1] Loading %s...\n%!" solid_path; let file_path = Eio.Path.(fs / solid_path) in let pill_bytes = Eio.Path.load file_path |> Bytes.of_string in Printf.printf " ✓ Loaded %d bytes\n\n%!" (Bytes.length pill_bytes); (* Step 2: Cue the pill *) Printf.printf "[2] Cuing pill...\n%!"; let pil = Serial.cue pill_bytes in Printf.printf " ✓ Cued successfully\n\n%!"; (* Step 3: Parse pill structure *) Printf.printf "[3] Parsing pill structure...\n%!"; match parse_solid_pill pil with | Error msg -> Printf.printf " ✗ Parse failed: %s\n%!" msg; Error msg | Ok (bot, mod_, use_) -> Printf.printf " ✓ Extracted bot/mod/use events\n%!"; (* Count helper *) let rec count_list noun = match noun with | Noun.Atom z when Z.equal z Z.zero -> 0 | Noun.Cell (_, rest) -> 1 + count_list rest | _ -> 0 in (* Debug: check structure of each *) Printf.printf " Bot structure: %s (count=%d)\n%!" (if Noun.is_cell bot then "cell (list)" else "atom") (count_list bot); Printf.printf " Mod structure: %s (count=%d)\n%!" (if Noun.is_cell mod_ then "cell (list)" else "atom") (count_list mod_); Printf.printf " Use structure: %s (count=%d)\n%!" (if Noun.is_cell use_ then "cell (list)" else "atom") (count_list use_); (* Debug: walk through USE list and show structure *) Printf.printf " USE list details:\n%!"; let rec walk_list noun i = match noun with | Noun.Atom z when Z.equal z Z.zero -> Printf.printf " [%d] = ~ (list terminator)\n%!" i | Noun.Cell (head, tail) -> Printf.printf " [%d] = %s\n%!" i (if Noun.is_cell head then "CELL" else "ATOM"); if i < 5 then walk_list tail (i + 1) | Noun.Atom _ -> Printf.printf " [%d] = ATOM (improper list!)\n%!" i in walk_list use_ 0; Printf.printf "\n%!"; (* Step 3.5: Synthesize events (C Vere mars.c:1763-1789) *) Printf.printf "[3.5] Synthesizing events (like C Vere)...\n%!"; (* Generate 4 synthetic MOD events *) let synth_mod = synthesize_mod_events () in Printf.printf " ✓ Generated 4 synthetic MOD events\n%!"; (* Generate 1 synthetic USE event *) let synth_use = synthesize_boot_event () in Printf.printf " ✓ Generated 1 synthetic USE event\n%!"; (* Prepend synthetic events *) (* Helper to prepend to a list *) let rec weld l1 l2 = match l1 with | Noun.Atom z when Z.equal z Z.zero -> l2 | Noun.Cell (h, t) -> Noun.Cell (h, weld t l2) | _ -> l2 in let mod_ = weld synth_mod mod_ in (* 4 synthetic + 0 from pill *) let use_ = Noun.cell synth_use use_ in (* 1 synthetic + 2 from pill *) Printf.printf " ✓ Prepended synthetic events\n%!"; Printf.printf " After synthesis: mod=%d, use=%d\n\n%!" (count_list mod_) (count_list use_); (* Step 4: Build event list (C Vere style) *) Printf.printf "[4] Building event list (C Vere style)...\n%!"; let ova = build_event_list bot mod_ use_ in Printf.printf "\n%!"; (* Step 5: Boot with event list *) Printf.printf "[5] Calling u3v_boot with event list...\n%!"; Printf.printf " (Metamorphosis: replacing ivory kernel)\n\n%!"; match boot state ova with | Error msg -> Printf.printf " ✗ BOOT FAILED: %s\n%!" msg; Error msg | Ok () -> Printf.printf " ✓ BOOT SUCCEEDED!\n%!"; Printf.printf "\n%!"; Printf.printf "═══════════════════════════════════════════════════\n%!"; Printf.printf " ✓ SOLID PILL BOOT COMPLETE!\n%!"; Printf.printf "═══════════════════════════════════════════════════\n\n%!"; Ok ())