File 0549-ct-Improve-error-handling-of-bad-regular-expressions.patch of Package erlang

From b55d02e92d7fb8244da333ee5bbd794aa6090ff5 Mon Sep 17 00:00:00 2001
From: Siri Hansen <siri@erlang.org>
Date: Wed, 30 Jan 2019 19:42:32 +0100
Subject: [PATCH 1/2] [ct] Improve error handling of bad regular expressions to
 ct_telnet

---
 lib/common_test/src/ct_telnet.erl                  | 135 +++++++++++++--------
 lib/common_test/test/ct_telnet_SUITE.erl           |  39 +++++-
 .../ct_telnet_faulty_regexp_SUITE.erl              |  79 ++++++++++++
 3 files changed, 198 insertions(+), 55 deletions(-)
 create mode 100644 lib/common_test/test/ct_telnet_SUITE_data/ct_telnet_faulty_regexp_SUITE.erl

diff --git a/lib/common_test/src/ct_telnet.erl b/lib/common_test/src/ct_telnet.erl
index f9abecfd38..3df06cb3b4 100644
--- a/lib/common_test/src/ct_telnet.erl
+++ b/lib/common_test/src/ct_telnet.erl
@@ -211,10 +211,16 @@ expect(Connection,Patterns) ->
 %%% combined in order to match a sequence multiple times.</p>
 expect(Connection,Patterns,Opts) ->
     case get_handle(Connection) of
-	{ok,Pid} ->
-	    call(Pid,{expect,Patterns,Opts});
-	Error ->
-	    Error
+        {ok,Pid} ->
+            case call(Pid,{expect,Patterns,Opts}) of
+                {error,Reason} when element(1,Reason)==bad_pattern ->
+                    %% Faulty user input - should fail the test case
+                    exit({Reason,{?MODULE,?FUNCTION_NAME,3}});
+                Other ->
+                    Other
+            end;
+        Error ->
+            Error
     end.
 
 %%%=================================================================
@@ -674,60 +680,68 @@ silent_teln_expect(Name,Pid,Data,Pattern,Prx,Opts) ->
 %% 3b) Repeat (sequence): 2) is repeated either N times or until a
 %% halt condition is fullfilled.
 teln_expect(Name,Pid,Data,Pattern0,Prx,Opts) ->
-    HaltPatterns =
+    HaltPatterns0 =
 	case get_ignore_prompt(Opts) of
 	    true ->
 		get_haltpatterns(Opts);
 	    false ->
 		[prompt | get_haltpatterns(Opts)]
 	end,
-
-    PromptCheck = get_prompt_check(Opts),
-
-    {WaitForPrompt,Pattern1,Opts1} = wait_for_prompt(Pattern0,Opts),
-
-    Seq = get_seq(Opts1),
-    Pattern2 = convert_pattern(Pattern1,Seq),
-    {IdleTimeout,TotalTimeout} = get_timeouts(Opts1),
-
-    EO = #eo{teln_pid=Pid,
-	     prx=Prx,
-	     idle_timeout=IdleTimeout,
-	     total_timeout=TotalTimeout,
-	     seq=Seq,
-	     haltpatterns=HaltPatterns,
-	     prompt_check=PromptCheck},
+    case convert_pattern(HaltPatterns0,false) of
+        {ok,HaltPatterns} ->
+            {WaitForPrompt,Pattern1,Opts1} = wait_for_prompt(Pattern0,Opts),
+            Seq = get_seq(Opts1),
+            case convert_pattern(Pattern1,Seq) of
+                {ok,Pattern2} ->
+                    {IdleTimeout,TotalTimeout} = get_timeouts(Opts1),
+                    PromptCheck = get_prompt_check(Opts1),
+
+                    EO = #eo{teln_pid=Pid,
+                             prx=Prx,
+                             idle_timeout=IdleTimeout,
+                             total_timeout=TotalTimeout,
+                             seq=Seq,
+                             haltpatterns=HaltPatterns,
+                             prompt_check=PromptCheck},
     
-    case get_repeat(Opts1) of
-	false ->
-	    case teln_expect1(Name,Pid,Data,Pattern2,[],EO) of
-		{ok,Matched,Rest} when WaitForPrompt ->
-		    case lists:reverse(Matched) of
-			[{prompt,_},Matched1] ->
-			    {ok,Matched1,Rest};
-			[{prompt,_}|Matched1] ->
-			    {ok,lists:reverse(Matched1),Rest}
-		    end;
-		{ok,Matched,Rest} ->
-		    {ok,Matched,Rest};
-		{halt,Why,Rest} ->
-		    {error,Why,Rest};
-		{error,Reason} ->
-		    {error,Reason}
-	    end;
-	N ->
-	    EO1 = EO#eo{repeat=N},
-	    repeat_expect(Name,Pid,Data,Pattern2,[],EO1)
+                    case get_repeat(Opts1) of
+                        false ->
+                            case teln_expect1(Name,Pid,Data,Pattern2,[],EO) of
+                                {ok,Matched,Rest} when WaitForPrompt ->
+                                    case lists:reverse(Matched) of
+                                        [{prompt,_},Matched1] ->
+                                            {ok,Matched1,Rest};
+                                        [{prompt,_}|Matched1] ->
+                                            {ok,lists:reverse(Matched1),Rest}
+                                    end;
+                                {ok,Matched,Rest} ->
+                                    {ok,Matched,Rest};
+                                {halt,Why,Rest} ->
+                                    {error,Why,Rest};
+                                {error,Reason} ->
+                                    {error,Reason}
+                            end;
+                        N ->
+                            EO1 = EO#eo{repeat=N},
+                            repeat_expect(Name,Pid,Data,Pattern2,[],EO1)
+                    end;
+               Error ->
+                    Error
+            end;
+        Error ->
+            Error
     end.
 
-convert_pattern(Pattern,Seq) 
-  when is_list(Pattern) and not is_integer(hd(Pattern)) ->
-    case Seq of
-	true -> Pattern;
-	false -> rm_dupl(Pattern,[])
-    end;
+convert_pattern(Pattern0,Seq)
+  when Pattern0==[] orelse (is_list(Pattern0) and not is_integer(hd(Pattern0))) ->
+    Pattern =
+        case Seq of
+            true -> Pattern0;
+            false -> rm_dupl(Pattern0,[])
+        end,
+    compile_pattern(Pattern,[]);
 convert_pattern(Pattern,_Seq) ->
-    [Pattern].
+    compile_pattern([Pattern],[]).
 
 rm_dupl([P|Ps],Acc) ->
     case lists:member(P,Acc) of
@@ -739,6 +753,25 @@ rm_dupl([P|Ps],Acc) ->
 rm_dupl([],Acc) ->
     lists:reverse(Acc).
 
+compile_pattern([prompt|Patterns],Acc) ->
+    compile_pattern(Patterns,[prompt|Acc]);
+compile_pattern([{prompt,_}=P|Patterns],Acc) ->
+    compile_pattern(Patterns,[P|Acc]);
+compile_pattern([{Tag,Pattern}|Patterns],Acc) ->
+    try re:compile(Pattern,[unicode]) of
+        {ok,MP} -> compile_pattern(Patterns,[{Tag,MP}|Acc]);
+        {error,Error} -> {error,{bad_pattern,{Tag,Pattern},Error}}
+    catch error:badarg -> {error,{bad_pattern,{Tag,Pattern}}}
+    end;
+compile_pattern([Pattern|Patterns],Acc) ->
+    try re:compile(Pattern,[unicode]) of
+        {ok,MP} -> compile_pattern(Patterns,[MP|Acc]);
+        {error,Error} -> {error,{bad_pattern,Pattern,Error}}
+    catch error:badarg -> {error,{bad_pattern,Pattern}}
+    end;
+compile_pattern([],Acc) ->
+    {ok,lists:reverse(Acc)}.
+
 get_timeouts(Opts) ->
     {case lists:keysearch(idle_timeout,1,Opts) of
 	 {value,{_,T}} ->
@@ -772,7 +805,7 @@ get_seq(Opts) ->
 get_haltpatterns(Opts) ->
     case lists:keysearch(halt,1,Opts) of
 	{value,{halt,HaltPatterns}} ->
-	    convert_pattern(HaltPatterns,false);
+	    HaltPatterns;
 	false ->
 	    []
     end.
diff --git a/lib/common_test/test/ct_telnet_SUITE.erl b/lib/common_test/test/ct_telnet_SUITE.erl
index a0089c9bc9..f71b7c370f 100644
--- a/lib/common_test/test/ct_telnet_SUITE.erl
+++ b/lib/common_test/test/ct_telnet_SUITE.erl
@@ -50,10 +50,10 @@
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 groups() ->
-    [{legacy, [], [unix_telnet,own_server,timetrap]},
-     {raw,    [], [unix_telnet,own_server,timetrap]},
-     {html,   [], [unix_telnet,own_server]},
-     {silent, [], [unix_telnet,own_server]}].
+    [{legacy, [], [unix_telnet,own_server,faulty_regexp,timetrap]},
+     {raw,    [], [unix_telnet,own_server,faulty_regexp,timetrap]},
+     {html,   [], [unix_telnet,own_server,faulty_regexp]},
+     {silent, [], [unix_telnet,own_server,faulty_regexp]}].
 
 all() ->
     [
@@ -119,6 +119,12 @@ own_server(Config) ->
     all_tests_in_suite(own_server,"ct_telnet_own_server_SUITE",
 		       CfgFile,Config).
 
+faulty_regexp(Config) ->
+    CfgFile = "telnet.faulty_regexp." ++
+	atom_to_list(groupname(Config)) ++ ".cfg",
+    all_tests_in_suite(faulty_regexp,"ct_telnet_faulty_regexp_SUITE",
+		       CfgFile,Config).
+
 timetrap(Config) ->
     CfgFile = "telnet.timetrap." ++
 	atom_to_list(groupname(Config)) ++ ".cfg",
@@ -225,6 +231,31 @@ events_to_check(unix_telnet,Config) ->
     all_cases(ct_telnet_basic_SUITE,Config);
 events_to_check(own_server,Config) ->
     all_cases(ct_telnet_own_server_SUITE,Config);
+events_to_check(faulty_regexp,_Config) ->
+    [{?eh,start_logging,{'DEF','RUNDIR'}},
+     {?eh,tc_done,
+      {ct_telnet_faulty_regexp_SUITE,expect_pattern,
+       {failed,
+        {error,{{bad_pattern,"invalid(pattern",{"missing )",15}},
+                {ct_telnet,expect,3}}}}}},
+     {?eh,tc_done,
+      {ct_telnet_faulty_regexp_SUITE,expect_pattern_no_string,
+       {failed,
+        {error,{{bad_pattern,invalid_pattern},
+                {ct_telnet,expect,3}}}}}},
+     {?eh,tc_done,
+      {ct_telnet_faulty_regexp_SUITE,expect_tag_pattern,
+       {failed,
+        {error,{{bad_pattern,{tag,"invalid(pattern"},{"missing )",15}},
+                {ct_telnet,expect,3}}}}}},
+     {?eh,tc_done,
+      {ct_telnet_faulty_regexp_SUITE,expect_tag_pattern_no_string,
+       {failed,
+        {error,{{bad_pattern,{tag,invalid_pattern}},
+                {ct_telnet,expect,3}}}}}},
+     {?eh,tc_done,{ct_telnet_faulty_regexp_SUITE,expect_pattern_unicode,ok}},
+     {?eh,tc_done,{ct_telnet_faulty_regexp_SUITE,expect_tag_pattern_unicode,ok}},
+     {?eh,stop_logging,[]}];
 events_to_check(timetrap,_Config) ->
     [{?eh,start_logging,{'DEF','RUNDIR'}},
      {?eh,tc_done,{ct_telnet_timetrap_SUITE,expect_timetrap,
diff --git a/lib/common_test/test/ct_telnet_SUITE_data/ct_telnet_faulty_regexp_SUITE.erl b/lib/common_test/test/ct_telnet_SUITE_data/ct_telnet_faulty_regexp_SUITE.erl
new file mode 100644
index 0000000000..a5c9451a9c
--- /dev/null
+++ b/lib/common_test/test/ct_telnet_SUITE_data/ct_telnet_faulty_regexp_SUITE.erl
@@ -0,0 +1,79 @@
+-module(ct_telnet_faulty_regexp_SUITE).
+
+-compile(export_all).
+
+-include_lib("common_test/include/ct.hrl").
+
+-define(name, telnet_server_conn1).
+
+%%--------------------------------------------------------------------
+%% TEST SERVER CALLBACK FUNCTIONS
+%%--------------------------------------------------------------------
+
+init_per_suite(Config) ->
+    Config.
+
+end_per_suite(_Config) ->
+    ok.
+
+suite() -> [{require,?name,{unix,[telnet]}},
+	    {require,ct_conn_log},
+ 	    {ct_hooks, [{cth_conn_log,[]}]}].
+
+all() ->
+    [expect_pattern,
+     expect_pattern_no_string,
+     expect_tag_pattern,
+     expect_tag_pattern_no_string,
+     expect_pattern_unicode,
+     expect_tag_pattern_unicode].
+
+groups() ->
+    [].
+
+init_per_group(_GroupName, Config) ->
+    Config.
+
+end_per_group(_GroupName, Config) ->
+    Config.
+
+init_per_testcase(_,Config) ->
+    ct:log("init_per_testcase: opening telnet connection...",[]),
+    {ok,_} = ct_telnet:open(?name),
+    ct:log("...done",[]),
+    Config.
+
+end_per_testcase(_,_Config) ->
+    ct:log("end_per_testcase: closing telnet connection...",[]),
+    _ = ct_telnet:close(?name),
+    ct:log("...done",[]),
+    ok.
+
+expect_pattern(_) ->
+    ok = ct_telnet:send(?name, "echo ayt"),
+    ok = ct_telnet:expect(?name, "invalid(pattern").
+
+expect_pattern_no_string(_) ->
+    ok = ct_telnet:send(?name, "echo ayt"),
+    ok = ct_telnet:expect(?name, invalid_pattern).
+
+expect_tag_pattern(_) ->
+    ok = ct_telnet:send(?name, "echo ayt"),
+    ok = ct_telnet:expect(?name, {tag,"invalid(pattern"}).
+
+expect_tag_pattern_no_string(_) ->
+    ok = ct_telnet:send(?name, "echo ayt"),
+    ok = ct_telnet:expect(?name, {tag,invalid_pattern}).
+
+%% Test that a unicode pattern can be given without the testcase
+%% failing.  Do however notice that there is no real unicode support
+%% in ct_telnet yet, that is, the telnet binary mode is not supported.
+expect_pattern_unicode(_) ->
+    ok = ct_telnet:send(?name, "echo ayt"),
+    {error,{prompt,_}} = ct_telnet:expect(?name, "pattern_with_unicode_αβ"),
+    ok.
+
+expect_tag_pattern_unicode(_) ->
+    ok = ct_telnet:send(?name, "echo ayt"),
+    {error,{prompt,_}} = ct_telnet:expect(?name, "pattern_with_unicode_αβ"),
+    ok.
-- 
2.16.4

openSUSE Build Service is sponsored by