summaryrefslogtreecommitdiff
path: root/ocaml/test/test_pills.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/test_pills.ml')
-rw-r--r--ocaml/test/test_pills.ml124
1 files changed, 124 insertions, 0 deletions
diff --git a/ocaml/test/test_pills.ml b/ocaml/test/test_pills.ml
new file mode 100644
index 0000000..d926fc0
--- /dev/null
+++ b/ocaml/test/test_pills.ml
@@ -0,0 +1,124 @@
+open Nock_lib
+open Noun
+open Serial
+
+let read_file path =
+ let ic = open_in_bin path in
+ let len = in_channel_length ic in
+ let bytes = really_input_string ic len in
+ close_in ic;
+ Bytes.of_string bytes
+
+let rec find_project_root dir =
+ let pills_dir = Filename.concat dir "pills" in
+ if Sys.file_exists pills_dir && Sys.is_directory pills_dir then
+ dir
+ else
+ let parent = Filename.dirname dir in
+ if String.equal parent dir then
+ invalid_arg "unable to locate project root containing pills/"
+ else
+ find_project_root parent
+
+let project_root =
+ let exe_dir = Filename.dirname Sys.executable_name in
+ find_project_root exe_dir
+
+let pill_path name = Filename.concat project_root (Filename.concat "pills" name)
+
+let pill_paths = List.map pill_path [ "baby.pill"; "ivory.pill" ]
+
+let test_pill path () =
+ Printf.printf "[pill] %s\n%!" path;
+ let bytes = read_file path in
+ let cue_noun = cue bytes in
+ Alcotest.(check bool) (path ^ " parsed") true (Noun.is_cell cue_noun)
+
+let tests = List.map (fun path -> path, `Quick, test_pill path) pill_paths
+
+let error_to_string = function
+ | Boot.Invalid_pill s -> Printf.sprintf "invalid pill: %s" s
+ | Boot.Unsupported s -> Printf.sprintf "unsupported pill: %s" s
+
+let count_list noun =
+ let rec loop acc = function
+ | Atom z when Z.equal z Z.zero -> acc
+ | Cell (_, t) -> loop (acc + 1) t
+ | _ -> Alcotest.fail "expected null-terminated list"
+ in
+ loop 0 noun
+
+let solid_event_count path =
+ let noun = cue (read_file path) in
+ match noun with
+ | Cell (tag, rest) ->
+ let pill_tag = Z.of_int 0x6c6c6970 in
+ let solid_tag = Z.of_int 0x64696c6f in
+ begin match tag, rest with
+ | Atom z, Cell (typ, payload) when Z.equal z pill_tag ->
+ begin match typ, payload with
+ | Atom t, Cell (bot, Cell (mod_, use_)) when Z.equal t solid_tag ->
+ count_list bot + count_list mod_ + count_list use_
+ | _ -> Alcotest.fail "malformed solid payload"
+ end
+ | _ -> Alcotest.fail "invalid solid pill tag"
+ end
+ | _ -> Alcotest.fail "solid pill not a cell"
+
+let test_boot_ivory () =
+ let state = State.create () in
+ match Boot.boot_ivory state (pill_path "ivory.pill") with
+ | Ok () ->
+ Alcotest.(check int64) "eve reset" 0L (State.event_number state);
+ Alcotest.(check bool) "arvo core is cell" true (Noun.is_cell (State.arvo_core state))
+ | Error err -> Alcotest.failf "boot_ivory failed: %s" (error_to_string err)
+
+let test_boot_solid () =
+ let solid_limit =
+ match Sys.getenv_opt "SOLID_LIMIT" with
+ | None -> None
+ | Some value ->
+ begin match int_of_string_opt value with
+ | Some n when n > 0 -> Some n
+ | _ -> Alcotest.fail "SOLID_LIMIT must be a positive integer"
+ end
+ in
+ match solid_limit with
+ | None ->
+ Printf.printf "[solid] skipping; set SOLID_LIMIT to replay events\n%!"
+ | Some requested_limit ->
+ let ivory = pill_path "ivory.pill" in
+ let solid = pill_path "solid.pill" in
+ let state = State.create () in
+ let total_events = solid_event_count solid in
+ if total_events = 0 then Alcotest.fail "solid pill contained no events";
+ let limit = min requested_limit total_events in
+ match Boot.boot_ivory state ivory with
+ | Error err -> Alcotest.failf "boot_ivory failed: %s" (error_to_string err)
+ | Ok () ->
+ let booted_core = State.arvo_core state in
+ let seen = ref [] in
+ let fake_apply _ event =
+ seen := event :: !seen;
+ Noun.zero
+ in
+ match Boot.boot_solid ~limit ~apply:fake_apply state solid with
+ | Error err -> Alcotest.failf "boot_solid failed: %s" (error_to_string err)
+ | Ok () ->
+ let events = List.rev !seen in
+ Alcotest.(check int) "event count" limit (List.length events);
+ Alcotest.(check int64) "eve unchanged" 0L (State.event_number state);
+ Alcotest.(check bool) "core unchanged"
+ true (Noun.equal booted_core (State.arvo_core state))
+
+
+let boot_tests = [
+ "boot_ivory", `Quick, test_boot_ivory;
+ "boot_solid", `Slow, test_boot_solid;
+]
+
+let () =
+ Alcotest.run "pills"
+ [ "pill roundtrips", tests;
+ "boot", boot_tests;
+ ]