Switch typing-immediate to expect tests

master
Jeremie Dimino 2016-02-02 14:58:34 +00:00
parent 216119d222
commit 3cd841b676
4 changed files with 78 additions and 72 deletions

1
.gitignore vendored
View File

@ -225,6 +225,7 @@
/testsuite/**/*.result
/testsuite/**/*.opt_result
/testsuite/**/*.corrected
/testsuite/**/*.byte
/testsuite/**/*.native
/testsuite/**/program

View File

@ -14,5 +14,5 @@
#**************************************************************************
BASEDIR=../..
include $(BASEDIR)/makefiles/Makefile.toplevel
include $(BASEDIR)/makefiles/Makefile.expect
include $(BASEDIR)/makefiles/Makefile.common

View File

@ -1,5 +1,9 @@
module type S = sig type t [@@immediate] end;;
module F (M : S) : S = M;;
[%%expect{|
module type S = sig type t [@@immediate] end
module F : functor (M : S) -> S
|}];;
(* VALID DECLARATIONS *)
@ -17,40 +21,74 @@ module A = struct
type p = q [@@immediate]
and q = int
end;;
[%%expect{|
module A :
sig
type t [@@immediate]
type s = t [@@immediate]
type r = s
type p = q [@@immediate]
and q = int
end
|}];;
(* Valid using with constraints *)
module type X = sig type t end;;
module Y = struct type t = int end;;
module Z = ((Y : X with type t = int) : sig type t [@@immediate] end);;
[%%expect{|
module type X = sig type t end
module Y : sig type t = int end
module Z : sig type t [@@immediate] end
|}];;
(* Valid using an explicit signature *)
module M_valid : S = struct type t = int end;;
module FM_valid = F (struct type t = int end);;
[%%expect{|
module M_valid : S
module FM_valid : S
|}];;
(* Practical usage over modules *)
module Foo : sig type t val x : t ref end = struct
type t = int
let x = ref 0
end;;
[%%expect{|
module Foo : sig type t val x : t ref end
|}];;
module Bar : sig type t [@@immediate] val x : t ref end = struct
type t = int
let x = ref 0
end;;
[%%expect{|
module Bar : sig type t [@@immediate] val x : t ref end
|}];;
let test f =
let start = Sys.time() in f ();
(Sys.time() -. start);;
[%%expect{|
val test : (unit -> 'a) -> float = <fun>
|}];;
let test_foo () =
for i = 0 to 100_000_000 do
Foo.x := !Foo.x
done;;
[%%expect{|
val test_foo : unit -> unit = <fun>
|}];;
let test_bar () =
for i = 0 to 100_000_000 do
Bar.x := !Bar.x
done;;
[%%expect{|
val test_bar : unit -> unit = <fun>
|}];;
(* Uncomment these to test. Should see substantial speedup!
let () = Printf.printf "No @@immediate: %fs\n" (test test_foo)
@ -63,24 +101,62 @@ let () = Printf.printf "With @@immediate: %fs\n" (test test_bar) *)
module B = struct
type t = string [@@immediate]
end;;
[%%expect{|
Line _, characters 2-31:
Error: Types marked with the immediate attribute must be
non-pointer types like int or bool
|}];;
(* Not guaranteed that t is immediate, so this is an invalid declaration *)
module C = struct
type t
type s = t [@@immediate]
end;;
[%%expect{|
Line _, characters 2-26:
Error: Types marked with the immediate attribute must be
non-pointer types like int or bool
|}];;
(* Can't ascribe to an immediate type signature with a non-immediate type *)
module D : sig type t [@@immediate] end = struct
type t = string
end;;
[%%expect{|
Line _, characters 42-70:
Error: Signature mismatch:
Modules do not match:
sig type t = string end
is not included in
sig type t [@@immediate] end
Type declarations do not match:
type t = string
is not included in
type t [@@immediate]
the first is not an immediate type.
|}];;
(* Same as above but with explicit signature *)
module M_invalid : S = struct type t = string end;;
module FM_invalid = F (struct type t = string end);;
[%%expect{|
Line _, characters 23-49:
Error: Signature mismatch:
Modules do not match: sig type t = string end is not included in S
Type declarations do not match:
type t = string
is not included in
type t [@@immediate]
the first is not an immediate type.
|}];;
(* Can't use a non-immediate type even if mutually recursive *)
module E = struct
type t = s [@@immediate]
and s = string
end;;
[%%expect{|
Line _, characters 2-26:
Error: Types marked with the immediate attribute must be
non-pointer types like int or bool
|}];;

View File

@ -1,71 +0,0 @@
# module type S = sig type t [@@immediate] end
# module F : functor (M : S) -> S
# module A :
sig
type t [@@immediate]
type s = t [@@immediate]
type r = s
type p = q [@@immediate]
and q = int
end
# module type X = sig type t end
# module Y : sig type t = int end
# module Z : sig type t [@@immediate] end
# module M_valid : S
# module FM_valid : S
# module Foo : sig type t val x : t ref end
# module Bar : sig type t [@@immediate] val x : t ref end
# val test : (unit -> 'a) -> float = <fun>
# val test_foo : unit -> unit = <fun>
# val test_bar : unit -> unit = <fun>
# * * Characters 306-335:
type t = string [@@immediate]
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Types marked with the immediate attribute must be
non-pointer types like int or bool
# Characters 106-130:
type s = t [@@immediate]
^^^^^^^^^^^^^^^^^^^^^^^^
Error: Types marked with the immediate attribute must be
non-pointer types like int or bool
# Characters 120-148:
..........................................struct
type t = string
end..
Error: Signature mismatch:
Modules do not match:
sig type t = string end
is not included in
sig type t [@@immediate] end
Type declarations do not match:
type t = string
is not included in
type t [@@immediate]
the first is not an immediate type.
# Characters 72-98:
module M_invalid : S = struct type t = string end;;
^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Signature mismatch:
Modules do not match: sig type t = string end is not included in S
Type declarations do not match:
type t = string
is not included in
type t [@@immediate]
the first is not an immediate type.
# Characters 23-49:
module FM_invalid = F (struct type t = string end);;
^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Signature mismatch:
Modules do not match: sig type t = string end is not included in S
Type declarations do not match:
type t = string
is not included in
type t [@@immediate]
the first is not an immediate type.
# Characters 85-109:
type t = s [@@immediate]
^^^^^^^^^^^^^^^^^^^^^^^^
Error: Types marked with the immediate attribute must be
non-pointer types like int or bool
#