summaryrefslogtreecommitdiff
path: root/ocaml/lib
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 05:34:08 +0700
committerpolwex <polwex@sortug.com>2025-10-06 05:34:08 +0700
commitc3545b7ba9e8448226417fab6edaa2d039c9babe (patch)
tree798fd2bf87a67ac91e31b2fb7f0cd6590064b2c1 /ocaml/lib
parent9fd3f41bf9a3326c5f0866f39f2ed151adc21565 (diff)
wait what? runtime working?HEADmaster
Diffstat (limited to 'ocaml/lib')
-rw-r--r--ocaml/lib/boot.ml116
-rw-r--r--ocaml/lib/dune2
-rw-r--r--ocaml/lib/io/behn.ml5
-rw-r--r--ocaml/lib/state.ml127
4 files changed, 223 insertions, 27 deletions
diff --git a/ocaml/lib/boot.ml b/ocaml/lib/boot.ml
new file mode 100644
index 0000000..e56c114
--- /dev/null
+++ b/ocaml/lib/boot.ml
@@ -0,0 +1,116 @@
+(* 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\n%!" (Bytes.length pill_bytes);
+
+ (* Cue the pill to get kernel noun *)
+ let kernel_noun = Serial.cue pill_bytes in
+
+ Printf.printf "[Boot] Pill cued successfully\n%!";
+
+ (* 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
diff --git a/ocaml/lib/dune b/ocaml/lib/dune
index ea260c1..97961d5 100644
--- a/ocaml/lib/dune
+++ b/ocaml/lib/dune
@@ -1,4 +1,4 @@
(library
(name nock_lib)
- (modules noun nock bitstream serial eventlog state effects runtime domain_pool nock_parallel)
+ (modules noun nock bitstream serial eventlog state effects boot runtime domain_pool nock_parallel)
(libraries zarith eio eio.unix domainslib))
diff --git a/ocaml/lib/io/behn.ml b/ocaml/lib/io/behn.ml
index 95e1d02..e2ffdac 100644
--- a/ocaml/lib/io/behn.ml
+++ b/ocaml/lib/io/behn.ml
@@ -75,11 +75,10 @@ let timer_fiber behn ~env ~event_stream timer =
Printf.printf "[Behn] Timer %Ld: FIRED! 🔥\n%!" timer.id;
(* Create timer ovum and send to event stream *)
- let ovum_noun = Nock_lib.Effects.timer_ovum ~id:timer.id ~fire_time:timer.fire_time in
- let event = Nock_lib.Noun.cell ovum_noun.wire ovum_noun.card in
+ let ovum = Nock_lib.Effects.timer_ovum ~id:timer.id ~fire_time:timer.fire_time in
(* Send to runtime event stream *)
- Eio.Stream.add event_stream event;
+ Eio.Stream.add event_stream ovum;
Printf.printf "[Behn] Timer %Ld: event sent to runtime\n%!" timer.id
end else begin
Printf.printf "[Behn] Timer %Ld: cancelled, not firing\n%!" timer.id
diff --git a/ocaml/lib/state.ml b/ocaml/lib/state.ml
index f1acefe..6fdf725 100644
--- a/ocaml/lib/state.ml
+++ b/ocaml/lib/state.ml
@@ -73,38 +73,119 @@ let boot state kernel_noun =
Hashtbl.clear state.yot;
Mutex.unlock state.lock
-(* Poke: apply an event to the kernel
+(* Poke Formula - Gate call formula
+ *
+ * This is the Nock formula to call the Arvo kernel gate with an event.
*
- * In real Arvo:
- * - Runs Nock with the poke formula
- * - Updates kernel state
- * - Increments event number
- * - Returns effects
+ * Formula: [9 2 [0 3] [0 2]]
+ * - Opcode 9: Call gate at slot 2
+ * - Argument construction from slots 2 and 3
*
- * For now: simplified version that just stores the event
+ * 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
*)
-let poke state _event_noun =
- Mutex.lock state.lock;
- (* In a real implementation, this would run Nock:
- * let effects = Nock.nock_on state.roc poke_formula in
- * state.roc <- new_kernel_state;
- *
- * For now, we just update event count
+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]]
*)
- state.eve <- Int64.succ state.eve;
- Mutex.unlock state.lock;
+ Noun.cell
+ (Noun.atom 0) (* Opcode 0: slot *)
+ (Noun.atom 3) (* Slot 3: the kernel *)
+
+(* Parse poke result
+ *
+ * Arvo poke result structure: [effects new-kernel]
+ * Or sometimes: [[moves new-kernel] effects]
+ *
+ * For now, simplified: assume result is the new kernel
+ *)
+let parse_poke_result result =
+ (* TODO: Parse real Arvo result structure
+ * For now: treat whole result as new kernel *)
+ let new_kernel = result in
+ let effects = [] in (* No effects parsed yet *)
+ (new_kernel, effects)
+
+(* Poke: apply an event to the kernel
+ *
+ * Real Arvo poke sequence:
+ * 1. Build subject: [event kernel]
+ * 2. Run Nock with poke formula
+ * 3. Parse result: [effects new-kernel]
+ * 4. Update kernel state
+ * 5. Return effects
+ *)
+let poke state event_noun =
+ Mutex.lock state.lock;
+
+ try
+ (* Build subject: [event kernel] *)
+ let subject = Noun.cell event_noun state.roc in
+
+ (* Run Nock with poke formula *)
+ let result = Nock.nock_on subject poke_formula in
+
+ (* Parse result *)
+ let (new_kernel, effects) = parse_poke_result result in
+
+ (* Update kernel state *)
+ state.roc <- new_kernel;
+ state.eve <- Int64.succ state.eve;
- (* Return empty effects list for now *)
- []
+ Mutex.unlock state.lock;
+
+ (* 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);
+ []
+
+(* Peek Formula - Scry formula
+ *
+ * Scry is a read-only query into Arvo.
+ * Formula: Similar to poke but doesn't update state
+ *
+ * For now: simplified - just return the path from the kernel
+ *)
+let peek_formula =
+ (* Simplified: [0 1] - return the whole subject *)
+ Noun.cell
+ (Noun.atom 0)
+ (Noun.atom 1)
(* Peek: query the kernel state (read-only)
*
- * In real Arvo: runs scry requests
- * For now: simplified
+ * Real Arvo scry:
+ * 1. Build subject: [path kernel]
+ * 2. Run Nock with peek formula
+ * 3. Return result (no state update!)
+ *
+ * Multiple domains can peek concurrently since it's read-only.
*)
-let peek state _path =
- (* Peek is read-only, multiple domains can do this concurrently *)
- Some state.roc
+let peek state path_noun =
+ (* No lock needed for read! This is why peek is fast *)
+ let kernel = state.roc in
+
+ try
+ (* Build subject: [path kernel] *)
+ let subject = Noun.cell path_noun kernel in
+
+ (* Run Nock with peek formula - read-only! *)
+ let result = Nock.nock_on subject peek_formula in
+
+ Some result
+
+ with e ->
+ (* Scry failed *)
+ Printf.printf "[State] Peek failed: %s\n%!" (Printexc.to_string e);
+ None
(* Save snapshot to file using Eio
*