diff options
author | polwex <polwex@sortug.com> | 2025-10-06 23:06:50 +0700 |
---|---|---|
committer | polwex <polwex@sortug.com> | 2025-10-06 23:06:50 +0700 |
commit | fdab65f6dac4ba85ed4749f61970660d1132d453 (patch) | |
tree | 427123729c6d556f040bed6a0e461f6d0887c9bf /ocaml/lib/boot.ml | |
parent | bf4c5ff0fd28d94b7f22552a79e6fbe2561fe6cf (diff) |
added mutable mugs
Diffstat (limited to 'ocaml/lib/boot.ml')
-rw-r--r-- | ocaml/lib/boot.ml | 101 |
1 files changed, 51 insertions, 50 deletions
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml index f8289ec..1aeafaf 100644 --- a/ocaml/lib/boot.ml +++ b/ocaml/lib/boot.ml @@ -152,7 +152,7 @@ let life eve = (* 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 + | Noun.Atom { z; _ } when Z.equal z Z.zero -> true | _ -> false in @@ -177,14 +177,14 @@ let life eve = (* 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) -> + | Noun.Cell { h = eve_h; t = 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) -> + | Noun.Cell { h = eve_hh; t = 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 + 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%!" @@ -247,7 +247,7 @@ let boot state eve_list = let rec count_events acc noun = match noun with | Noun.Atom _ -> acc - | Noun.Cell (_, rest) -> count_events (acc + 1) rest + | Noun.Cell { t = rest; _ } -> count_events (acc + 1) rest in let event_count = count_events 0 eve_list in @@ -279,7 +279,7 @@ let parse_solid_pill pil = (* Debug: print actual tag value *) (match tag with - | Noun.Atom z -> + | Noun.Atom { z; _ } -> Printf.printf "[Debug] Tag is atom: %s (hex: %s)\n%!" (Z.to_string z) (Z.format "x" z) | Noun.Cell _ -> @@ -289,7 +289,7 @@ let parse_solid_pill pil = let pill_tag = Z.of_string "1819044208" in (* "pill" = 0x6c6c6970 *) begin match tag with - | Noun.Atom z when Z.equal z pill_tag -> + | 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" @@ -351,14 +351,14 @@ let string_to_atom s = 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) + Noun.Atom { z = loop (len - 1) Z.zero; mug = 0l } (* 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 + let wir = Noun.cell (Noun.atom 0) + (Noun.cell arvo_str (Noun.atom 0)) in (* 1. wack: entropy card [%wack [16 random words]] *) let eny_words = Array.init 16 (fun _ -> @@ -367,15 +367,15 @@ let synthesize_mod_events () = 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) + (Noun.cell (Noun.Atom { z = Z.of_int64 eny_words.(i); mug = 0l }) acc) in - let eny_noun = build_word_list 15 (Noun.Atom Z.zero) in + let eny_noun = build_word_list 15 (Noun.atom 0) 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 who = Noun.atom 0 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 @@ -383,36 +383,36 @@ let synthesize_mod_events () = (* 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 + (Noun.cell (Noun.atom 0) (Noun.atom 0)) 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_card = Noun.cell wyrd_tag (Noun.atom 0) 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)))) + (Noun.cell wyrd (Noun.atom 0)))) (* 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 one = Noun.Atom { z = Z.of_int 0x31; mug = 0l } in (* ASCII '1' *) let wir = Noun.cell d (Noun.cell term - (Noun.cell one (Noun.Atom Z.zero))) in + (Noun.cell one (Noun.atom 0))) 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 lit = Noun.atom 0 in + let ven = Noun.atom 0 in (* Placeholder for now *) let cad = Noun.cell boot_tag (Noun.cell lit ven) in Noun.cell wir cad @@ -426,8 +426,8 @@ 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 + | Noun.Atom { z; _ } when Z.equal z Z.zero -> 0 + | Noun.Cell { t = rest; _ } -> 1 + count_list rest | _ -> 0 in @@ -447,31 +447,31 @@ let build_event_list bot mod_ use_ = 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 + let now = Noun.Atom { z = Z.of_int64 now_us; mug = 0l } in (* 1/2^16 seconds increment *) - let bit = Noun.Atom (Z.shift_left Z.one 48) in + let bit = Noun.Atom { z = Z.shift_left Z.one 48; mug = 0l } 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 + | Noun.Atom { z; _ } when Z.equal z Z.zero -> acc + | Noun.Cell { h; t; _ } -> flip (Noun.cell h acc) t | _ -> acc 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) + | 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 (* Start with flipped bot events (NO timestamp) *) - let eve = flip (Noun.Atom Z.zero) bot in + let eve = flip (Noun.atom 0) bot in (* Add timestamped mod/use events by consing to FRONT * This matches C Vere: eve = u3nc(u3nc(now, i), eve) @@ -482,18 +482,19 @@ let build_event_list bot mod_ use_ = *) 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) -> + | Noun.Atom { z; _ } when Z.equal z Z.zero -> acc + | Noun.Cell { h = event; t = rest; _ } -> (* Increment timestamp *) let new_now = match !now_ref, bit with - | Noun.Atom n, Noun.Atom b -> Noun.Atom (Z.add n b) + | Noun.Atom { z = n; _ }, Noun.Atom { z = b; _ } -> + Noun.Atom { z = Z.add n b; mug = 0l } | _ -> !now_ref in now_ref := new_now; (* Create [timestamp event] pair and cons to FRONT *) - let stamped = Noun.Cell (new_now, event) in - let new_acc = Noun.Cell (stamped, acc) in + let stamped = Noun.cell new_now event in + let new_acc = Noun.cell stamped acc in add_timestamped new_acc now_ref rest | _ -> acc @@ -503,21 +504,21 @@ let build_event_list bot mod_ use_ = let eve_with_stamped = add_timestamped eve now_ref lit in (* Flip final list to get: [bot1 bot2 bot3 [time mod1] ...] *) - let ova = flip (Noun.Atom Z.zero) eve_with_stamped in + let ova = flip (Noun.atom 0) 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, _) -> + | Noun.Cell { h = first; _ } -> Printf.printf "[Boot] first = %s\n%!" (if Noun.is_cell first then "cell" else "atom"); (match first with - | Noun.Cell (h, t) -> + | 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 + 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%!" @@ -565,7 +566,7 @@ let boot_lite ~fs state ivory_path = let rec lent n = match n with | Noun.Atom _ when Noun.equal n (Noun.atom 0) -> 0 - | Noun.Cell (_, t) -> 1 + lent t + | Noun.Cell { t; _ } -> 1 + lent t | _ -> 0 in let pil_len = lent pil in @@ -576,8 +577,8 @@ let boot_lite ~fs state ivory_path = 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) -> + | 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 @@ -664,8 +665,8 @@ let boot_solid ~fs state ivory_path solid_path = (* 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 + | Noun.Atom { z; _ } when Z.equal z Z.zero -> 0 + | Noun.Cell { t = rest; _ } -> 1 + count_list rest | _ -> 0 in @@ -684,9 +685,9 @@ let boot_solid ~fs state ivory_path solid_path = Printf.printf " USE list details:\n%!"; let rec walk_list noun i = match noun with - | Noun.Atom z when Z.equal z Z.zero -> + | Noun.Atom { z; _ } when Z.equal z Z.zero -> Printf.printf " [%d] = ~ (list terminator)\n%!" i - | Noun.Cell (head, tail) -> + | Noun.Cell { h = head; t = 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) @@ -702,14 +703,14 @@ let boot_solid ~fs state ivory_path solid_path = (* Debug: Check what's in first BOT event *) Printf.printf " [Debug] Checking first BOT event structure:\n%!"; (match bot with - | Noun.Cell (first_bot, _) -> + | Noun.Cell { h = 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, _) -> + | 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 + let z = match h with Noun.Atom { z; _ } -> z | _ -> Z.zero in "atom(" ^ Z.to_string z ^ ")" else "cell") | _ -> ()) @@ -727,8 +728,8 @@ let boot_solid ~fs state ivory_path solid_path = (* 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) + | Noun.Atom { z; _ } when Z.equal z Z.zero -> l2 + | Noun.Cell { h; t; _ } -> Noun.cell h (weld t l2) | _ -> l2 in |