summaryrefslogtreecommitdiff
path: root/ocaml/test/inspect_events_simple.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/inspect_events_simple.ml')
-rw-r--r--ocaml/test/inspect_events_simple.ml88
1 files changed, 88 insertions, 0 deletions
diff --git a/ocaml/test/inspect_events_simple.ml b/ocaml/test/inspect_events_simple.ml
new file mode 100644
index 0000000..0cb05c9
--- /dev/null
+++ b/ocaml/test/inspect_events_simple.ml
@@ -0,0 +1,88 @@
+(* Simple event structure inspector *)
+
+open Nock_lib
+
+let describe_noun noun =
+ match noun with
+ | Noun.Atom a ->
+ if Z.numbits a <= 32 then
+ Printf.sprintf "Atom(%s)" (Z.to_string a)
+ else
+ Printf.sprintf "Atom(large, %d bits)" (Z.numbits a)
+ | Noun.Cell _ -> "Cell"
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let inspect_events _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) ->
+ Printf.printf "Tag: %s\n\n" (describe_noun tag);
+
+ let event_list = to_list [] events in
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ List.iteri (fun i event ->
+ Printf.printf "Event %d: " i;
+ match event with
+ | Noun.Atom a ->
+ Printf.printf "Atom(%s)\n" (Z.to_string a)
+ | Noun.Cell (head, tail) ->
+ Printf.printf "Cell[%s, %s]\n"
+ (describe_noun head) (describe_noun tail)
+ ) event_list;
+
+ (* Look more closely at events 3 and 4 *)
+ Printf.printf "\n=== Detailed look at events 3 and 4 ===\n\n";
+
+ begin match List.nth_opt event_list 3 with
+ | Some (Noun.Cell (wire, card)) ->
+ Printf.printf "Event 3:\n";
+ Printf.printf " wire: %s\n" (describe_noun wire);
+ Printf.printf " card: ";
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf "Cell[%s, %s]\n"
+ (describe_noun term) (describe_noun data)
+ | Noun.Atom _ ->
+ Printf.printf "%s\n" (describe_noun card)
+ end
+ | Some (Noun.Atom _) ->
+ Printf.printf "Event 3 is an atom\n"
+ | None ->
+ Printf.printf "No event 3\n"
+ end;
+
+ begin match List.nth_opt event_list 4 with
+ | Some (Noun.Cell (wire, card)) ->
+ Printf.printf "\nEvent 4:\n";
+ Printf.printf " wire: %s\n" (describe_noun wire);
+ Printf.printf " card: ";
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf "Cell[%s, %s]\n"
+ (describe_noun term) (describe_noun data)
+ | Noun.Atom _ ->
+ Printf.printf "%s\n" (describe_noun card)
+ end
+ | Some (Noun.Atom _) ->
+ Printf.printf "Event 4 is an atom\n"
+ | None ->
+ Printf.printf "No event 4\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is an atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Simple Event Structure Inspector\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run inspect_events