diff options
author | polwex <polwex@sortug.com> | 2025-10-06 17:07:33 +0700 |
---|---|---|
committer | polwex <polwex@sortug.com> | 2025-10-06 17:07:33 +0700 |
commit | a4615148975bed241ae26ffa2655dc9c407107d8 (patch) | |
tree | bd127b13f0027cd2870b8f016c5658465785d3df /ocaml/lib/boot.ml | |
parent | 256376afffe66faa239a6a6aaebb8f68a9c6cbe4 (diff) |
maybe now maybe now
Diffstat (limited to 'ocaml/lib/boot.ml')
-rw-r--r-- | ocaml/lib/boot.ml | 271 |
1 files changed, 216 insertions, 55 deletions
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml index 630da3b..ce30f2f 100644 --- a/ocaml/lib/boot.ml +++ b/ocaml/lib/boot.ml @@ -148,12 +148,6 @@ let boot_fake state = *) let life eve = try - (* Build lifecycle formula: [2 [0 3] [0 2]] *) - let lyf = 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 "[Boot] Running lifecycle formula [2 [0 3] [0 2]]...\n%!"; (* Check if eve is null (for ivory pill boot) *) @@ -177,9 +171,27 @@ let life eve = 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 - Nock.nock_on eve lyf + (* 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); @@ -237,56 +249,205 @@ let boot state eve_list = with e -> Error ("Boot failed: " ^ Printexc.to_string e) -(* Boot from ivory pill - the lightweight boot sequence +(* Parse solid pill structure: [%boot [%pill %solid [bot mod use]]] + * + * Following C Vere mars.c:1730 _mars_sift_pill + *) +let parse_solid_pill pil = + (* Extract [%boot com] *) + if not (Noun.is_cell pil) then + Error "Pill must be a cell" + else + let tag = Noun.head pil in + let com = Noun.tail pil in + + (* Check for %boot tag *) + let boot_tag = Z.of_string "1953654151028" in (* "boot" *) + + match tag with + | Noun.Atom z when Z.equal z boot_tag -> + (* Now parse com structure *) + if not (Noun.is_cell com) then + Error "Pill com must be a cell" + else + (* com is [[pill typ] [bot mod use]] *) + let fst = Noun.head com in + let snd = Noun.tail com in + + if not (Noun.is_cell fst) then + Error "Pill fst must be a cell" + else + let pill_tag = Noun.head fst in + let _typ = Noun.tail fst in + + (* Check for %pill tag *) + let pill_atom = Z.of_string "1819633778" in (* "pill" *) + + match pill_tag with + | Noun.Atom z when Z.equal z pill_atom -> + (* Extract [bot mod use] from snd *) + if not (Noun.is_cell snd) then + Error "Events structure must be a cell" + else + let bot = Noun.head snd in + let rest = Noun.tail snd in + + if not (Noun.is_cell rest) then + Error "Mod/use structure must be a cell" + else + let mod_ = Noun.head rest in + let use = Noun.tail (Noun.head (Noun.tail rest)) in + + Ok (bot, mod_, use) + | _ -> + Error "Expected %pill tag" + | _ -> + Error "Expected %boot tag" + +(* Build event list following C Vere mars.c:1814-1836 * - * Ivory pills have structure: ["ivory" core] - * The core contains a lifecycle formula that must be executed + * Key: Bot events are NOT timestamped (bare atoms/cells) + * Mod/use events ARE timestamped as [timestamp event] *) -let boot_ivory ~fs state pill_path = - Printf.printf "[Boot] Booting from ivory pill...\n%!"; +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 - 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; + 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 from solid pill - following C Vere -B flag logic + * + * This follows the exact flow from BOOT_FLOW.md: + * 1. Load pill bytes from file + * 2. Cue to get [%boot com] structure + * 3. Parse into bot/mod/use events + * 4. Timestamp mod/use events (bot stays bare) + * 5. Boot with event list + * + * Skipping disk persistence for now (steps 4-5 in C flow) + *) +let boot_solid ~fs state pill_path = + Printf.printf "\n%!"; + Printf.printf "═══════════════════════════════════════════════════\n%!"; + Printf.printf " Solid Pill Boot (Following C Vere -B Logic)\n%!"; + Printf.printf "═══════════════════════════════════════════════════\n\n%!"; + + (* Step 1: Load pill file *) + Printf.printf "[1] Loading %s...\n%!" pill_path; + + let file_path = Eio.Path.(fs / pill_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 pill -> - (* Check if pill has ivory tag *) - if not (Noun.is_cell pill.kernel) then - Error "Ivory pill must be a cell" - else begin - let hed = Noun.head pill.kernel in - let tal = Noun.tail pill.kernel in - - (* Check for "ivory" tag *) - (* "ivory" as cord (little-endian): 0x79726f7669 = 521610950249 *) - let ivory_tag = Z.of_string "521610950249" in - - match hed with - | Noun.Atom z when Z.equal z ivory_tag -> - Printf.printf "[Boot] ✓ Found ivory tag\n%!"; - Printf.printf "[Boot] Running lifecycle formula...\n%!"; - - (try - let start = Unix.gettimeofday () in - let core = life tal in - let elapsed = Unix.gettimeofday () -. start in - - Printf.printf "[Boot] ✓ Lifecycle completed in %.4fs\n%!" elapsed; - Printf.printf "[Boot] Setting Arvo core...\n%!"; - - State.boot state core; - Printf.printf "[Boot] ✓ Ivory pill booted!\n%!"; - Ok () - with e -> - Error ("Lifecycle failed: " ^ Printexc.to_string e)) - - | _ -> - Printf.printf "[Boot] Warning: No ivory tag found, trying regular boot...\n%!"; - boot_from_pill state pill - end + | Ok (bot, mod_, use_) -> + Printf.printf " ✓ Extracted bot/mod/use events\n\n%!"; + + (* 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 " (Booting Arvo kernel from events)\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 () |