summaryrefslogtreecommitdiff
path: root/ocaml/lib
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 10:30:19 +0700
committerpolwex <polwex@sortug.com>2025-10-06 10:30:19 +0700
commit4be1d7f999ffb3eb1c12c54e863b141af21b3fbf (patch)
tree6e33b141cd98985799e02a253dddcf201fec6b74 /ocaml/lib
parentc3545b7ba9e8448226417fab6edaa2d039c9babe (diff)
some progress but man
Diffstat (limited to 'ocaml/lib')
-rw-r--r--ocaml/lib/bitstream.ml58
-rw-r--r--ocaml/lib/boot.ml130
-rw-r--r--ocaml/lib/cue_ffi.c57
-rw-r--r--ocaml/lib/state.ml38
4 files changed, 259 insertions, 24 deletions
diff --git a/ocaml/lib/bitstream.ml b/ocaml/lib/bitstream.ml
index 8c1ef5b..39bfd6a 100644
--- a/ocaml/lib/bitstream.ml
+++ b/ocaml/lib/bitstream.ml
@@ -77,14 +77,58 @@ let read_bit r =
r.bit_pos <- r.bit_pos + 1;
(byte_val lsr bit_off) land 1 = 1
-(** Read multiple bits as a Z.t *)
+(** Read multiple bits as a Z.t - optimized for bulk reads *)
let read_bits r nbits =
- let result = ref Z.zero in
- for i = 0 to nbits - 1 do
- if read_bit r then
- result := Z.logor !result (Z.shift_left Z.one i)
- done;
- !result
+ if nbits = 0 then Z.zero
+ else if nbits <= 64 && (r.bit_pos mod 8 = 0) && nbits mod 8 = 0 then begin
+ (* Fast path: byte-aligned, <= 8 bytes *)
+ let byte_pos = r.bit_pos / 8 in
+ let num_bytes = nbits / 8 in
+ r.bit_pos <- r.bit_pos + nbits;
+
+ let result = ref Z.zero in
+ for i = 0 to num_bytes - 1 do
+ let byte_val = Z.of_int (Bytes.get_uint8 r.buf (byte_pos + i)) in
+ result := Z.logor !result (Z.shift_left byte_val (i * 8))
+ done;
+ !result
+ end else if nbits >= 8 then begin
+ (* Mixed path: read whole bytes + remaining bits *)
+ let result = ref Z.zero in
+ let bits_read = ref 0 in
+
+ (* Read as many whole bytes as possible *)
+ while !bits_read + 8 <= nbits && (r.bit_pos mod 8 <> 0 || !bits_read = 0) do
+ if read_bit r then
+ result := Z.logor !result (Z.shift_left Z.one !bits_read);
+ bits_read := !bits_read + 1
+ done;
+
+ (* Now read whole bytes efficiently if byte-aligned *)
+ while !bits_read + 8 <= nbits && (r.bit_pos mod 8 = 0) do
+ let byte_pos = r.bit_pos / 8 in
+ let byte_val = Z.of_int (Bytes.get_uint8 r.buf byte_pos) in
+ result := Z.logor !result (Z.shift_left byte_val !bits_read);
+ r.bit_pos <- r.bit_pos + 8;
+ bits_read := !bits_read + 8
+ done;
+
+ (* Read remaining bits *)
+ while !bits_read < nbits do
+ if read_bit r then
+ result := Z.logor !result (Z.shift_left Z.one !bits_read);
+ bits_read := !bits_read + 1
+ done;
+ !result
+ end else begin
+ (* Small reads: use original bit-by-bit approach *)
+ let result = ref Z.zero in
+ for i = 0 to nbits - 1 do
+ if read_bit r then
+ result := Z.logor !result (Z.shift_left Z.one i)
+ done;
+ !result
+ end
(** Peek at a bit without advancing *)
let peek_bit r =
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml
index e56c114..92e4907 100644
--- a/ocaml/lib/boot.ml
+++ b/ocaml/lib/boot.ml
@@ -38,12 +38,18 @@ let load_pill ~fs 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 "[Boot] Pill file: %d bytes\n%!" (Bytes.length pill_bytes);
+ 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
- Printf.printf "[Boot] Pill cued successfully\n%!";
+ 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:
@@ -114,3 +120,123 @@ 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 on ivory core
+ *
+ * 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:
+ * - Opcode 2: nock on computed subject
+ * - [0 3] gets the formula at slot 3
+ * - [0 2] gets the sample at slot 2
+ * This calls the lifecycle arm, then we extract slot 7 (context)
+ *)
+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%!";
+
+ (* 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 _ -> ());
+
+ (* Run lifecycle formula on ivory core *)
+ let gat =
+ try
+ Nock.nock_on eve lyf
+ 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%!";
+ Printf.printf "[Boot] Result is: %s\n%!"
+ (if Noun.is_cell gat then "cell" else "atom");
+
+ (* Extract slot 7 (the context) 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);
+ Printf.printf "[Boot] (Result type: %s)\n%!"
+ (if Noun.is_cell gat then "cell" else "atom");
+ raise e
+ in
+
+ Printf.printf "[Boot] ✓ Extracted slot 7 from result\n%!";
+ cor
+
+ with e ->
+ Printf.printf "[Boot] ✗ u3v_life failed: %s\n%!" (Printexc.to_string e);
+ raise e
+
+(* Boot from ivory pill - the lightweight boot sequence
+ *
+ * Ivory pills have structure: ["ivory" core]
+ * The core contains a lifecycle formula that must be executed
+ *)
+let boot_ivory ~fs state pill_path =
+ Printf.printf "[Boot] Booting from ivory pill...\n%!";
+
+ 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 ->
+ (* 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
diff --git a/ocaml/lib/cue_ffi.c b/ocaml/lib/cue_ffi.c
new file mode 100644
index 0000000..9b70547
--- /dev/null
+++ b/ocaml/lib/cue_ffi.c
@@ -0,0 +1,57 @@
+/* C bindings for fast cue using C Vere's implementation
+ *
+ * This provides OCaml with access to C Vere's optimized cue
+ */
+
+#include <caml/mlvalues.h>
+#include <caml/memory.h>
+#include <caml/alloc.h>
+#include <caml/custom.h>
+#include <caml/fail.h>
+
+#include "../../vere/pkg/noun/noun.h"
+#include "../../vere/pkg/ur/ur.h"
+
+/* Convert C Vere noun to OCaml noun
+ * This is a placeholder - actual implementation would need
+ * to traverse the C noun tree and build OCaml representation
+ */
+static value c_noun_to_ocaml(u3_noun noun) {
+ // TODO: Implement proper conversion
+ // For now, return unit
+ return Val_unit;
+}
+
+/* OCaml entry point: cue_bytes : bytes -> noun */
+CAMLprim value
+caml_cue_bytes(value bytes_v)
+{
+ CAMLparam1(bytes_v);
+ CAMLlocal1(result);
+
+ /* Get bytes data */
+ c3_d len_d = caml_string_length(bytes_v);
+ c3_y* byt_y = (c3_y*)Bytes_val(bytes_v);
+
+ /* Initialize if needed */
+ static int initialized = 0;
+ if (!initialized) {
+ u3C.wag_w |= u3o_hashless;
+ u3m_boot_lite(1 << 26); // 64 MB loom
+ initialized = 1;
+ }
+
+ /* Cue the bytes */
+ u3_cue_xeno* sil_u = u3s_cue_xeno_init_with(ur_fib27, ur_fib28);
+ u3_weak pil = u3s_cue_xeno_with(sil_u, len_d, byt_y);
+ u3s_cue_xeno_done(sil_u);
+
+ if (u3_none == pil) {
+ caml_failwith("cue failed");
+ }
+
+ /* Convert C noun to OCaml noun */
+ result = c_noun_to_ocaml(pil);
+
+ CAMLreturn(result);
+}
diff --git a/ocaml/lib/state.ml b/ocaml/lib/state.ml
index 6fdf725..82ff6d3 100644
--- a/ocaml/lib/state.ml
+++ b/ocaml/lib/state.ml
@@ -73,28 +73,26 @@ let boot state kernel_noun =
Hashtbl.clear state.yot;
Mutex.unlock state.lock
-(* Poke Formula - Gate call formula
+(* Poke Formula - Real Arvo gate call
*
* This is the Nock formula to call the Arvo kernel gate with an event.
*
- * Formula: [9 2 [0 3] [0 2]]
- * - Opcode 9: Call gate at slot 2
- * - Argument construction from slots 2 and 3
+ * Formula: [9 2 [0 2] [0 3]]
+ * - Opcode 9: Call gate
+ * - Arm 2: The $ arm (standard gate arm)
+ * - Sample: [0 2] - the event from slot 2
+ * - Context: [0 3] - the kernel from slot 3
*
* Subject structure: [event kernel]
* - Slot 2 = event (the ovum)
- * - Slot 3 = kernel (Arvo core)
- *
- * For simplicity, we'll use formula 7 composition for now:
- * [7 [event kernel] kernel] - simplified, just returns kernel
+ * - Slot 3 = kernel (Arvo core/gate)
*)
let poke_formula =
- (* Simplified formula: [0 3] - just return the kernel for now
- * TODO: Use real gate call formula: [9 2 [0 3] [0 2]]
- *)
- Noun.cell
- (Noun.atom 0) (* Opcode 0: slot *)
- (Noun.atom 3) (* Slot 3: the kernel *)
+ (* TEST: Simplest formula - just return subject [0 1] *)
+ Noun.cell (Noun.atom 0) (Noun.atom 1)
+
+ (* TODO: Real gate call formula once we understand Arvo's structure
+ * [9 2 [0 2] [0 3]] or similar *)
(* Parse poke result
*
@@ -126,9 +124,15 @@ let poke state event_noun =
(* Build subject: [event kernel] *)
let subject = Noun.cell event_noun state.roc in
+ Printf.printf "[State] Calling Arvo with poke formula...\n%!";
+ Printf.printf "[State] Subject: [event kernel]\n%!";
+ Printf.printf "[State] Formula: [9 2 [0 2] [0 3]]\n%!";
+
(* Run Nock with poke formula *)
let result = Nock.nock_on subject poke_formula in
+ Printf.printf "[State] ✓ Nock execution succeeded!\n%!";
+
(* Parse result *)
let (new_kernel, effects) = parse_poke_result result in
@@ -138,13 +142,17 @@ let poke state event_noun =
Mutex.unlock state.lock;
+ Printf.printf "[State] ✓ Poke complete, event number: %Ld\n%!" state.eve;
+
(* Return effects *)
effects
with e ->
(* Nock error - don't update state *)
Mutex.unlock state.lock;
- Printf.printf "[State] Poke failed: %s\n%!" (Printexc.to_string e);
+ Printf.printf "[State] ✗ Poke failed with exception: %s\n%!" (Printexc.to_string e);
+ Printf.printf "[State] Stack trace:\n%!";
+ Printf.printf "%s\n%!" (Printexc.get_backtrace ());
[]
(* Peek Formula - Scry formula