summaryrefslogtreecommitdiff
path: root/ocaml/lib/boot.ml
blob: ce30f2f00b52d2baf381b65fab907bc2ee186bd7 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
(* 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: [%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
 *
 * 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 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 (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 ()