|
| 1 | +open Stdune |
| 2 | + |
| 3 | +let () = Dune_tests_common.init () |
| 4 | + |
| 5 | +(* Testing the parsing of byte values *) |
| 6 | +let parse_bytes value = |
| 7 | + Dune_sexp.Ast.atom_or_quoted_string Loc.none value |
| 8 | + |> Dune_sexp.Decoder.parse Dune_sexp.Decoder.bytes_unit Univ_map.empty |
| 9 | +;; |
| 10 | + |
| 11 | +let rec long_power (l : int64) (n : int) : int64 = |
| 12 | + if n = 0 then 1L else Int64.mul l @@ long_power l (n - 1) |
| 13 | +;; |
| 14 | + |
| 15 | +let parse_and_assert ?check value = |
| 16 | + let value = parse_bytes value in |
| 17 | + (match check with |
| 18 | + | None -> () |
| 19 | + | Some check -> assert (value = check)); |
| 20 | + value |
| 21 | +;; |
| 22 | + |
| 23 | +let test_bytes ?check value = parse_and_assert ?check value |> Printf.printf "%#Ld\n" |
| 24 | + |
| 25 | +(* Hack to insert underscores for hex values. Digits must only be 0-9 *) |
| 26 | +let test_bytes_hex ?check value = |
| 27 | + match parse_and_assert ?check value |> sprintf "%Lx" |> Int.of_string with |
| 28 | + | Some x -> x |> Printf.sprintf "0x%#d\n" |> print_endline |
| 29 | + | None -> print_endline "hex value must not have letters" |
| 30 | +;; |
| 31 | + |
| 32 | +(* Test parsing of integers. *) |
| 33 | + |
| 34 | +let%expect_test "parsing no suffix" = |
| 35 | + try test_bytes "100" with |
| 36 | + | exn -> |
| 37 | + User_message.print (User_message.make [ Exn.pp exn ]); |
| 38 | + [%expect |
| 39 | + {| |
| 40 | + File "<none>", line 1, characters 0-0: |
| 41 | + Error: missing suffix, use one of B, kB, KiB, MB, MiB, GB, GiB, TB, TiB |}] |
| 42 | +;; |
| 43 | + |
| 44 | +(* Test all suffixes. We print binary units in hex to better see output. *) |
| 45 | + |
| 46 | +let%expect_test "parsing B suffix" = |
| 47 | + test_bytes "1B" ~check:(long_power 1024L 0); |
| 48 | + [%expect {| 1 |}] |
| 49 | +;; |
| 50 | + |
| 51 | +let%expect_test "parsing kB suffix" = |
| 52 | + test_bytes "1kB" ~check:(long_power 1000L 1); |
| 53 | + [%expect {| 1_000 |}] |
| 54 | +;; |
| 55 | + |
| 56 | +let%expect_test "parsing KiB suffix" = |
| 57 | + test_bytes_hex "1KiB" ~check:(long_power 1024L 1); |
| 58 | + [%expect {| 0x400 |}] |
| 59 | +;; |
| 60 | + |
| 61 | +let%expect_test "parsing MB suffix" = |
| 62 | + test_bytes "1MB" ~check:(long_power 1000L 2); |
| 63 | + [%expect {| 1_000_000 |}] |
| 64 | +;; |
| 65 | + |
| 66 | +let%expect_test "parsing MiB suffix" = |
| 67 | + test_bytes_hex "1MiB" ~check:(long_power 1024L 2); |
| 68 | + [%expect {| 0x100_000 |}] |
| 69 | +;; |
| 70 | + |
| 71 | +let%expect_test "parsing GB suffix" = |
| 72 | + test_bytes "1GB" ~check:(long_power 1000L 3); |
| 73 | + [%expect {| 1_000_000_000 |}] |
| 74 | +;; |
| 75 | + |
| 76 | +let%expect_test "parsing GiB suffix" = |
| 77 | + test_bytes_hex "1GiB" ~check:(long_power 1024L 3); |
| 78 | + [%expect {| 0x40_000_000 |}] |
| 79 | +;; |
| 80 | + |
| 81 | +let%expect_test "parsing TB suffix" = |
| 82 | + test_bytes "1TB" ~check:(long_power 1000L 4); |
| 83 | + [%expect {| 1_000_000_000_000 |}] |
| 84 | +;; |
| 85 | + |
| 86 | +let%expect_test "parsing TiB suffix" = |
| 87 | + test_bytes_hex "1TiB" ~check:(long_power 1024L 4); |
| 88 | + [%expect {| 0x10_000_000_000 |}] |
| 89 | +;; |
0 commit comments