Skip to content

Commit

Permalink
Tests
Browse files Browse the repository at this point in the history
  • Loading branch information
gretay-js committed Oct 27, 2021
1 parent 75fcceb commit 5ce06b5
Show file tree
Hide file tree
Showing 2 changed files with 108 additions and 0 deletions.
78 changes: 78 additions & 0 deletions testsuite/tests/asmcomp/evaluation_order.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,78 @@
(* TEST
*)
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
external caml_bytes_get_16 : bytes -> int -> int = "%caml_bytes_get16"
external caml_bytes_set_16 : bytes -> int -> int -> unit = "%caml_bytes_set16"

open Bigarray
type bigstring = (char, int8_unsigned_elt, c_layout) Array1.t

external caml_bigstring_get_16 :
bigstring -> int -> int = "%caml_bigstring_get16"

external caml_bigstring_set_16 :
bigstring -> int -> int -> unit = "%caml_bigstring_set16"

let bigstring_of_string s =
let a = Array1.create char c_layout (String.length s) in
for i = 0 to String.length s - 1 do
a.{i} <- s.[i]
done;
a

let () =
(* stringref_safe *)
String.get (print_endline "hello"; "foo") (print_endline "world"; 0)
|> Printf.printf "%c\n";

(* string_load *)
caml_bytes_get_16 (print_endline "hello"; Bytes.make 10 '\x00')
(print_endline "world"; 0)
|> Printf.printf "%x\n";

(* bigstring_load *)
caml_bigstring_get_16 (print_endline "hello";
bigstring_of_string (String.make 10 '\x00'))
(print_endline "world"; 0)
|> Printf.printf "%x\n";

(* bytes_set *)
caml_bytes_set_16 (print_endline "a"; Bytes.make 10 '\x00')
(print_endline "b"; 0)
(print_endline "c"; 0xFF);

(* bigstring_set *)
caml_bigstring_set_16 (print_endline "a";
bigstring_of_string (String.make 10 '\x00'))
(print_endline "b"; 0)
(print_endline "c"; 0xFF);

(* mk_compare_ints_untagged *)
print_int (compare (print_endline "A"; Sys.opaque_identity (2))
(print_endline "B"; Sys.opaque_identity (3)));
print_newline ();

(* mk_compare_floats *)
print_int (compare (print_endline "A"; Sys.opaque_identity (2.0))
(print_endline "B"; Sys.opaque_identity (3.5)));
print_newline ();

(* bytesset_safe *)
Bytes.set (print_endline "a"; Bytes.make 10 '\x00')
(print_endline "b"; 0)
(print_endline "c"; 'c');

(* safe_div_bi *)
Printf.printf "%nd\n"
(Nativeint.div (print_endline "A"; Sys.opaque_identity (6n))
(print_endline "B"; Sys.opaque_identity (3n)));

(* arrayref_unsafe *)
let[@inline never] test_arrayref_unsafe
: type t . t array -> int -> (t -> string) -> unit =
fun a i c ->
print_endline (c (Array.unsafe_get (print_endline "A"; a) (print_endline "B"; i)))
in
test_arrayref_unsafe [| "1";"2";"3" |] 0 Fun.id;

()
30 changes: 30 additions & 0 deletions testsuite/tests/asmcomp/evaluation_order.reference
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
world
hello
f
world
hello
0
world
hello
0
c
b
a
c
b
a
B
A
-1
B
A
-1
c
b
a
B
A
2
B
A
1

0 comments on commit 5ce06b5

Please sign in to comment.