summaryrefslogtreecommitdiff
path: root/ocaml/test/compare_events_3_4.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 14:35:41 +0700
committerpolwex <polwex@sortug.com>2025-10-06 14:35:41 +0700
commit256376afffe66faa239a6a6aaebb8f68a9c6cbe4 (patch)
tree52f2ea2ba9da38e7edf64bb810708526cdeb14f5 /ocaml/test/compare_events_3_4.ml
parent4a6067863d415e0334b4b61254fab2bd879a6964 (diff)
very stuck
Diffstat (limited to 'ocaml/test/compare_events_3_4.ml')
-rw-r--r--ocaml/test/compare_events_3_4.ml161
1 files changed, 161 insertions, 0 deletions
diff --git a/ocaml/test/compare_events_3_4.ml b/ocaml/test/compare_events_3_4.ml
new file mode 100644
index 0000000..b134d68
--- /dev/null
+++ b/ocaml/test/compare_events_3_4.ml
@@ -0,0 +1,161 @@
+(* Compare Events 3 and 4 structures in detail *)
+
+open Nock_lib
+
+let rec describe_noun noun max_depth current_depth =
+ if current_depth > max_depth then "..."
+ else
+ match noun with
+ | Noun.Atom a ->
+ if Z.numbits a <= 32 then
+ Printf.sprintf "Atom(%s/0x%s)" (Z.to_string a) (Z.format "x" a)
+ else
+ Printf.sprintf "Atom(%d bits)" (Z.numbits a)
+ | Noun.Cell (h, t) ->
+ Printf.sprintf "[%s %s]"
+ (describe_noun h max_depth (current_depth + 1))
+ (describe_noun t max_depth (current_depth + 1))
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let compare _env =
+ Printf.printf "Loading solid pill...\n";
+ let in_channel = open_in_bin "solid.noun" in
+ let pill = (Marshal.from_channel in_channel : Noun.noun) in
+ close_in in_channel;
+
+ match pill with
+ | Noun.Cell (_tag, events) ->
+ let event_list = to_list [] events in
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ (* Compare Event 3 and Event 4 *)
+ let event3 = List.nth_opt event_list 3 in
+ let event4 = List.nth_opt event_list 4 in
+
+ begin match (event3, event4) with
+ | (Some (Noun.Cell (wire3, card3)), Some (Noun.Cell (wire4, card4))) ->
+ Printf.printf "═══════════════════════════════════════════\n";
+ Printf.printf " EVENT 3 (%%park) - SUCCEEDS\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+
+ Printf.printf "Wire structure:\n";
+ Printf.printf " %s\n\n" (describe_noun wire3 3 0);
+
+ begin match card3 with
+ | Noun.Cell (term3, data3) ->
+ Printf.printf "Card term: %s\n" (describe_noun term3 2 0);
+ begin match term3 with
+ | Noun.Atom a ->
+ let bytes = Z.to_bits a in
+ Printf.printf " ASCII: '%s'\n" bytes
+ | _ -> ()
+ end;
+
+ Printf.printf "\nCard data structure (depth 4):\n";
+ Printf.printf " %s\n\n" (describe_noun data3 4 0);
+
+ (* Try to understand data3 structure *)
+ begin match data3 with
+ | Noun.Cell (d3_h, d3_t) ->
+ Printf.printf "Data breakdown:\n";
+ Printf.printf " Head: %s\n" (describe_noun d3_h 3 0);
+ Printf.printf " Tail: %s\n" (describe_noun d3_t 3 0)
+ | _ -> ()
+ end
+
+ | _ -> Printf.printf "Card is not [term data]\n"
+ end;
+
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " EVENT 4 (%%esse) - FAILS\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+
+ Printf.printf "Wire structure:\n";
+ Printf.printf " %s\n\n" (describe_noun wire4 3 0);
+
+ begin match card4 with
+ | Noun.Cell (term4, data4) ->
+ Printf.printf "Card term: %s\n" (describe_noun term4 2 0);
+ begin match term4 with
+ | Noun.Atom a ->
+ let bytes = Z.to_bits a in
+ Printf.printf " ASCII: '%s'\n" bytes
+ | _ -> ()
+ end;
+
+ Printf.printf "\nCard data structure (depth 4):\n";
+ Printf.printf " %s\n\n" (describe_noun data4 4 0);
+
+ (* Try to understand data4 structure *)
+ begin match data4 with
+ | Noun.Cell (d4_h, d4_t) ->
+ Printf.printf "Data breakdown:\n";
+ Printf.printf " Head: %s\n" (describe_noun d4_h 3 0);
+ Printf.printf " Tail: %s\n" (describe_noun d4_t 3 0)
+ | _ -> ()
+ end
+
+ | _ -> Printf.printf "Card is not [term data]\n"
+ end;
+
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " COMPARISON\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+
+ (* Compare wire structures *)
+ let wire3_is_cell = match wire3 with Noun.Cell _ -> true | _ -> false in
+ let wire4_is_cell = match wire4 with Noun.Cell _ -> true | _ -> false in
+
+ Printf.printf "Wire types:\n";
+ Printf.printf " Event 3: %s\n" (if wire3_is_cell then "Cell (path)" else "Atom");
+ Printf.printf " Event 4: %s\n\n" (if wire4_is_cell then "Cell (path)" else "Atom");
+
+ (* Compare card structures *)
+ begin match (card3, card4) with
+ | (Noun.Cell (term3, data3), Noun.Cell (term4, data4)) ->
+ Printf.printf "Card terms:\n";
+ Printf.printf " Event 3: %s\n" (describe_noun term3 1 0);
+ Printf.printf " Event 4: %s\n\n" (describe_noun term4 1 0);
+
+ (* Compare data types *)
+ let data3_type = match data3 with Noun.Atom _ -> "Atom" | Noun.Cell _ -> "Cell" in
+ let data4_type = match data4 with Noun.Atom _ -> "Atom" | Noun.Cell _ -> "Cell" in
+
+ Printf.printf "Data types:\n";
+ Printf.printf " Event 3: %s\n" (data3_type);
+ Printf.printf " Event 4: %s\n\n" (data4_type);
+
+ Printf.printf "KEY DIFFERENCES:\n";
+ if data3_type <> data4_type then
+ Printf.printf " ⚠️ Different data types! (%s vs %s)\n" data3_type data4_type;
+
+ (* Size comparison *)
+ let rec noun_size noun =
+ match noun with
+ | Noun.Atom a -> Z.numbits a
+ | Noun.Cell (h, t) -> (noun_size h) + (noun_size t)
+ in
+ let size3 = noun_size data3 in
+ let size4 = noun_size data4 in
+ Printf.printf " Event 3 data size: %d bits\n" size3;
+ Printf.printf " Event 4 data size: %d bits\n" size4
+
+ | _ -> ()
+ end
+
+ | _ ->
+ Printf.printf "Could not extract both events\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Compare Events 3 and 4\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run compare