File 2666-stdlib-Correct-handling-of-scanner-continuation.patch of Package erlang

From 569b72ffbdbbeb8190a0192aa10625c22aa805ad Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Thu, 26 Sep 2019 13:16:12 +0200
Subject: [PATCH 6/8] stdlib: Correct handling of scanner continuation

And add a few more tests.
---
 lib/stdlib/src/erl_scan.erl        |  8 ++++++++
 lib/stdlib/test/erl_scan_SUITE.erl | 28 +++++++++++++++++++++-------
 2 files changed, 29 insertions(+), 7 deletions(-)

diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl
index 48fd1fb463..3fdc7385d4 100644
--- a/lib/stdlib/src/erl_scan.erl
+++ b/lib/stdlib/src/erl_scan.erl
@@ -946,6 +946,8 @@ scan_number([C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
 scan_number([$_,Next|Cs], St, Line, Col, Toks, [Prev|_]=Ncs, _Us) when
       ?DIGIT(Next) andalso ?DIGIT(Prev) ->
     scan_number(Cs, St, Line, Col, Toks, [Next,$_|Ncs], with_underscore);
+scan_number([$_]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+    {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_number/6}};
 scan_number([$.,C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
     scan_fraction(Cs, St, Line, Col, Toks, [C,$.|Ncs], Us);
 scan_number([$.]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
@@ -992,6 +994,8 @@ scan_based_int([$_,Next|Cs], St, Line, Col, Toks, B, [Prev|_]=Ncs, Bcs, _Us)
       when ?BASED_DIGIT(Next, B) andalso ?BASED_DIGIT(Prev, B) ->
     scan_based_int(Cs, St, Line, Col, Toks, B, [Next,$_|Ncs], Bcs,
                    with_underscore);
+scan_based_int([$_]=Cs, _St, Line, Col, Toks, B, NCs, BCs, Us) ->
+    {more,{Cs,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_int/6}};
 scan_based_int([]=Cs, _St, Line, Col, Toks, B, NCs, BCs, Us) ->
     {more,{Cs,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_int/6}};
 scan_based_int(Cs, St, Line, Col, Toks, B, Ncs0, Bcs, Us) ->
@@ -1013,6 +1017,8 @@ scan_fraction([C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
 scan_fraction([$_,Next|Cs], St, Line, Col, Toks, [Prev|_]=Ncs, _Us) when
       ?DIGIT(Next) andalso ?DIGIT(Prev) ->
     scan_fraction(Cs, St, Line, Col, Toks, [Next,$_|Ncs], with_underscore);
+scan_fraction([$_]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+    {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_fraction/6}};
 scan_fraction([E|Cs], St, Line, Col, Toks, Ncs, Us) when E =:= $e; E =:= $E ->
     scan_exponent_sign(Cs, St, Line, Col, Toks, [E|Ncs], Us);
 scan_fraction([]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
@@ -1039,6 +1045,8 @@ scan_exponent([C|Cs], St, Line, Col, Toks, Ncs, Us) when ?DIGIT(C) ->
 scan_exponent([$_,Next|Cs], St, Line, Col, Toks, [Prev|_]=Ncs, _) when
       ?DIGIT(Next) andalso ?DIGIT(Prev) ->
     scan_exponent(Cs, St, Line, Col, Toks, [Next,$_|Ncs], with_underscore);
+scan_exponent([$_]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
+    {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_exponent/6}};
 scan_exponent([]=Cs, _St, Line, Col, Toks, Ncs, Us) ->
     {more,{Cs,Col,Toks,Line,{Ncs,Us},fun scan_exponent/6}};
 scan_exponent(Cs, St, Line, Col, Toks, Ncs, Us) ->
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 1eb6656051..4ae3301ca0 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1998-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2019. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -306,7 +306,7 @@ integers() ->
          {"1_2", 12}],
     lists:foreach(
          fun({S, I}) ->
-                 {ok, [{integer, 1, I}], _} = erl_scan_string(S)
+                 test_string(S, [{integer, {1, 1}, I}])
          end, UnderscoreSamples),
     UnderscoreErrors =
         ["123_",
@@ -324,6 +324,8 @@ integers() ->
                       ok
               end
       end, UnderscoreErrors),
+    test_string("_123", [{var,{1,1},'_123'}]),
+    test_string("123_", [{integer,{1,1},123},{var,{1,4},'_'}]),
     ok.
 
 base_integers() ->
@@ -339,13 +341,19 @@ base_integers() ->
     {error,{{1,1},erl_scan,{base,1}},{1,2}} =
         erl_scan:string("1#000", {1,1}, []),
 
+    {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"),
+    {error,{{1,1},erl_scan,{base,1000}},{1,6}} =
+        erl_scan:string("1_000#000", {1,1}, []),
+
     test_string("12#bc", [{integer,{1,1},11},{atom,{1,5},c}]),
 
     [begin
          Str = BS ++ "#" ++ S,
-         {error,{1,erl_scan,{illegal,integer}},1} =
-             erl_scan:string(Str)
-     end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ],
+         E = 2 + length(BS),
+         {error,{{1,1},erl_scan,{illegal,integer}},{1,E}} =
+             erl_scan:string(Str, {1,1}, [])
+     end || {BS,S} <- [{"3","3"},{"15","f"},{"12","c"},
+                       {"1_5","f"},{"1_2","c"}] ],
 
     {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"),
     {ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} =
@@ -361,7 +369,7 @@ base_integers() ->
          {"16#abcdef", 16#ABCDEF}],
     lists:foreach(
          fun({S, I}) ->
-                 {ok, [{integer, 1, I}], _} = erl_scan_string(S)
+                 test_string(S, [{integer, {1, 1}, I}])
          end, UnderscoreSamples),
     UnderscoreErrors =
         ["16_#123ABC",
@@ -381,6 +389,8 @@ base_integers() ->
                       ok
               end
       end, UnderscoreErrors),
+    test_string("16#123_", [{integer,{1,1},291},{var,{1,7},'_'}]),
+    test_string("_16#ABC", [{var,{1,1},'_16'},{'#',{1,4}},{var,{1,5},'ABC'}]),
     ok.
 
 floats() ->
@@ -396,6 +406,8 @@ floats() ->
         erl_scan:string("1.0e400"),
     {error,{{1,1},erl_scan,{illegal,float}},{1,8}} =
         erl_scan:string("1.0e400", {1,1}, []),
+    {error,{{1,1},erl_scan,{illegal,float}},{1,9}} =
+        erl_scan:string("1.0e4_00", {1,1}, []),
     [begin
          {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S),
          {error,{{1,1},erl_scan,{illegal,float}},{1,_}} =
@@ -411,7 +423,7 @@ floats() ->
          {"12_34.56_78e-1_8", 1234.5678e-18}],
     lists:foreach(
          fun({S, I}) ->
-                 {ok, [{float, 1, I}], _} = erl_scan_string(S)
+                 test_string(S, [{float, {1, 1}, I}])
          end, UnderscoreSamples),
     UnderscoreErrors =
         ["123_.456",
@@ -430,6 +442,8 @@ floats() ->
                       ok
               end
       end, UnderscoreErrors),
+    test_string("123._", [{integer,{1,1},123},{'.',{1,4}},{var,{1,5},'_'}]),
+    test_string("1.23_e10", [{float,{1,1},1.23},{var,{1,5},'_e10'}]),
     ok.
 
 dots() ->
-- 
2.16.4

openSUSE Build Service is sponsored by