File 2622-Only-validate-subject-once-when-global-is-used-in-re.patch of Package erlang

From 0c253ebdd7392e06045c0b1fb16f8aa55d8a7092 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Wed, 22 May 2019 19:02:21 +0200
Subject: [PATCH 2/3] Only validate subject once when global is used in
 re:run()

---
 erts/emulator/beam/bif.tab      |  1 +
 erts/emulator/beam/erl_bif_re.c | 29 +++++++++++++++++++----
 lib/stdlib/src/re.erl           | 52 ++++++++++++++++++++++++++++++++++-------
 3 files changed, 70 insertions(+), 12 deletions(-)

diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 10ca0b5066..db454a95ea 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -399,6 +399,7 @@ bif re:compile/1
 bif re:compile/2
 bif re:run/2
 bif re:run/3
+bif re:internal_run/4
 
 #
 # Bifs in lists module.
diff --git a/erts/emulator/beam/erl_bif_re.c b/erts/emulator/beam/erl_bif_re.c
index ad124fd979..9d99d24a61 100644
--- a/erts/emulator/beam/erl_bif_re.c
+++ b/erts/emulator/beam/erl_bif_re.c
@@ -46,7 +46,7 @@ static Export *urun_trap_exportp = NULL;
 static Export *ucompile_trap_exportp = NULL;
 
 static BIF_RETTYPE re_exec_trap(BIF_ALIST_3);
-static BIF_RETTYPE re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3);
+static BIF_RETTYPE re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3, int first);
 
 static void *erts_erts_pcre_malloc(size_t size) {
     return erts_alloc(ERTS_ALC_T_RE_HEAP,size);
@@ -1110,7 +1110,7 @@ build_capture(Eterm capture_spec[CAPSPEC_SIZE], const pcre *code)
  * The actual re:run/2,3 BIFs
  */
 static BIF_RETTYPE
-re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3)
+re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3, int first)
 {
     const pcre *code_tmp;
     RestartContext restart;
@@ -1136,6 +1136,14 @@ re_run(Process *p, Eterm arg1, Eterm arg2, Eterm arg3)
 	< 0) {
 	BIF_ERROR(p,BADARG);
     }
+    if (!first) {
+        /*
+         * 'first' is false when re:grun() previously has called re:internal_run()
+         * with the same subject; i.e., no need to do yet another validation of
+         * the subject regarding utf8 encoding...
+         */
+        options |= PCRE_NO_UTF8_CHECK;
+    }
     is_list_cap = ((pflags & PARSE_FLAG_CAPTURE_OPT) && 
 		   (capture[CAPSPEC_TYPE] == am_list));
 
@@ -1386,16 +1394,29 @@ handle_iolist:
     BIF_RET(res);
 }
 
+BIF_RETTYPE
+re_internal_run_4(BIF_ALIST_4)
+{
+    int first;
+    if (BIF_ARG_4 == am_false)
+        first = 0;
+    else if (BIF_ARG_4 == am_true)
+        first = !0;
+    else
+        BIF_ERROR(BIF_P,BADARG);
+    return re_run(BIF_P,BIF_ARG_1, BIF_ARG_2, BIF_ARG_3, first);
+}
+
 BIF_RETTYPE
 re_run_3(BIF_ALIST_3)
 {
-    return re_run(BIF_P,BIF_ARG_1, BIF_ARG_2, BIF_ARG_3);
+    return re_run(BIF_P,BIF_ARG_1, BIF_ARG_2, BIF_ARG_3, !0);
 }
 
 BIF_RETTYPE
 re_run_2(BIF_ALIST_2) 
 {
-    return re_run(BIF_P,BIF_ARG_1, BIF_ARG_2, NIL);
+    return re_run(BIF_P,BIF_ARG_1, BIF_ARG_2, NIL, !0);
 }
 
 /*
diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl
index 726b409d4d..197564b895 100644
--- a/lib/stdlib/src/re.erl
+++ b/lib/stdlib/src/re.erl
@@ -33,6 +33,8 @@
 
 %%% BIFs
 
+-export([internal_run/4]).
+
 -export([version/0, compile/1, compile/2, run/2, run/3, inspect/2]).
 
 -spec version() -> binary().
@@ -100,6 +102,40 @@ run(_, _) ->
 run(_, _, _) ->
     erlang:nif_error(undef).
 
+-spec internal_run(Subject, RE, Options, FirstCall) -> {match, Captured} |
+                                                       match |
+                                                       nomatch |
+                                                       {error, ErrType} when
+      Subject :: iodata() | unicode:charlist(),
+      RE :: mp() | iodata() | unicode:charlist(),
+      Options :: [Option],
+      Option :: anchored | global | notbol | noteol | notempty 
+	      | notempty_atstart | report_errors
+              | {offset, non_neg_integer()} |
+		{match_limit, non_neg_integer()} |
+		{match_limit_recursion, non_neg_integer()} |
+                {newline, NLSpec :: nl_spec()} |
+                bsr_anycrlf | bsr_unicode | {capture, ValueSpec} |
+                {capture, ValueSpec, Type} | CompileOpt,
+      Type :: index | list | binary,
+      ValueSpec :: all | all_but_first | all_names | first | none | ValueList,
+      ValueList :: [ValueID],
+      ValueID :: integer() | string() | atom(),
+      CompileOpt :: compile_option(),
+      Captured :: [CaptureData] | [[CaptureData]],
+      CaptureData :: {integer(), integer()}
+                   | ListConversionData
+                   | binary(),
+      ListConversionData :: string()
+                          | {error, string(), binary()}
+                          | {incomplete, string(), binary()},
+      ErrType :: match_limit | match_limit_recursion | {compile,  CompileErr}, 
+      CompileErr :: {ErrString :: string(), Position :: non_neg_integer()},
+      FirstCall :: boolean().
+
+internal_run(_, _, _, _) ->
+    erlang:nif_error(undef).
+
 -spec inspect(MP,Item) -> {namelist, [ binary() ]} when
       MP :: mp(),
       Item :: namelist.
@@ -765,17 +801,17 @@ do_grun(FlatSubject,Subject,Unicode,CRLF,RE,{Options0,NeedClean}) ->
     try
 	postprocess(loopexec(FlatSubject,RE,InitialOffset,
 			     byte_size(FlatSubject),
-			     Unicode,CRLF,StrippedOptions),
+			     Unicode,CRLF,StrippedOptions,true),
 		    SelectReturn,ConvertReturn,FlatSubject,Unicode)
     catch
 	throw:ErrTuple ->
 	    ErrTuple
     end.
 
-loopexec(_,_,X,Y,_,_,_) when X > Y ->
+loopexec(_,_,X,Y,_,_,_,_) when X > Y ->
     {match,[]};
-loopexec(Subject,RE,X,Y,Unicode,CRLF,Options) ->
-    case re:run(Subject,RE,[{offset,X}]++Options) of
+loopexec(Subject,RE,X,Y,Unicode,CRLF,Options, First) ->
+    case re:internal_run(Subject,RE,[{offset,X}]++Options,First) of
 	{error, Err} ->
 	    throw({error,Err});
 	nomatch ->
@@ -784,11 +820,11 @@ loopexec(Subject,RE,X,Y,Unicode,CRLF,Options) ->
 	    {match,Rest} = 
 		case B>0 of
 		    true ->
-			loopexec(Subject,RE,A+B,Y,Unicode,CRLF,Options);
+			loopexec(Subject,RE,A+B,Y,Unicode,CRLF,Options,false);
 		    false ->
 			{match,M} = 
-			    case re:run(Subject,RE,[{offset,X},notempty_atstart,
-						anchored]++Options) of
+			    case re:internal_run(Subject,RE,[{offset,X},notempty_atstart,
+                                                             anchored]++Options,false) of
 				nomatch ->
 				    {match,[]};
 				{match,Other} ->
@@ -801,7 +837,7 @@ loopexec(Subject,RE,X,Y,Unicode,CRLF,Options) ->
 				       forward(Subject,A,1,Unicode,CRLF)
 			       end,
 			{match,MM} = loopexec(Subject,RE,NewA,Y,
-					      Unicode,CRLF,Options),
+					      Unicode,CRLF,Options,false),
 			case M of 
 			    [] ->
 				{match,MM};
-- 
2.16.4

openSUSE Build Service is sponsored by