File 2543-Add-yield_on_subject_validation-test.patch of Package erlang

From f9f857c8094e6bb50a944316ea120e53cd5552ed Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Fri, 24 May 2019 14:50:00 +0200
Subject: [PATCH 1/3] Add yield_on_subject_validation() test

---
 lib/stdlib/test/re_SUITE.erl | 29 +++++++++++++++++++++++++++--
 1 file changed, 27 insertions(+), 2 deletions(-)

diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index 7b82647416..55ed99d4a7 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -28,7 +28,7 @@
 	 pcre_compile_workspace_overflow/1,re_infinite_loop/1, 
 	 re_backwards_accented/1,opt_dupnames/1,opt_all_names/1,inspect/1,
 	 opt_no_start_optimize/1,opt_never_utf/1,opt_ucp/1,
-	 match_limit/1,sub_binaries/1,copt/1,global_unicode_validation/1,
+	 match_limit/1,sub_binaries/1,copt/1,global_unicode_validation/1,yield_on_subject_validation/1,
          bad_utf8_subject/1]).
 
 -include_lib("common_test/include/ct.hrl").
@@ -46,7 +46,7 @@ all() ->
      pcre_compile_workspace_overflow, re_infinite_loop, 
      re_backwards_accented, opt_dupnames, opt_all_names, 
      inspect, opt_no_start_optimize,opt_never_utf,opt_ucp,
-     match_limit, sub_binaries, re_version, global_unicode_validation,
+     match_limit, sub_binaries, re_version, global_unicode_validation, yield_on_subject_validation,
      bad_utf8_subject].
 
 groups() -> 
@@ -227,6 +227,33 @@ re_version(_Config) ->
     Res = Fun(),
     End = erlang:monotonic_time(nanosecond),
     {End-Start, Res}.
+
+yield_on_subject_validation(Config) when is_list(Config) ->
+    Go = make_ref(),
+    Bin = binary:copy(<<"abc\n">>,100000),
+    {P, M} = spawn_opt(fun () ->
+                               receive Go -> ok end,
+                               {match,[{1,1}]} = re:run(Bin, <<"b">>, [unicode])
+                       end,
+                       [link, monitor]),
+    1 = erlang:trace(P, true, [running]),
+    P ! Go,
+    N = count_re_run_trap_out(P, M),
+    true = N >= 5,
+    ok.
+
+count_re_run_trap_out(P, M) when is_reference(M) ->
+    receive {'DOWN',M,process,P,normal} -> ok end,
+    TD = erlang:trace_delivered(P),
+    receive {trace_delivered, P, TD} -> ok end,
+    count_re_run_trap_out(P, 0);
+count_re_run_trap_out(P, N) when is_integer(N) ->
+    receive
+        {trace,P,out,{erlang,re_run_trap,3}} ->
+            count_re_run_trap_out(P, N+1)
+    after 0 ->
+            N
+    end.
 
 %% Test compile options given directly to run.
 combined_options(Config) when is_list(Config) ->
-- 
2.16.4

openSUSE Build Service is sponsored by