File 2392-stdlib-Adjust-test-suites-and-docs-due-to-erl_pp-cha.patch of Package erlang

From b0b0eebc6a915fabb079f4d7e70fe3be34e1df29 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Fri, 12 Apr 2019 15:07:49 +0200
Subject: [PATCH 2/2] stdlib: Adjust test suites and docs due to erl_pp changes

---
 lib/stdlib/doc/src/qlc.xml      | 81 ++++++++++++++++++++++++-----------------
 lib/stdlib/test/qlc_SUITE.erl   | 66 +++++++++++++++++++--------------
 lib/stdlib/test/shell_SUITE.erl |  6 +--
 3 files changed, 88 insertions(+), 65 deletions(-)

diff --git a/lib/stdlib/doc/src/qlc.xml b/lib/stdlib/doc/src/qlc.xml
index fe60c2e9bb..34f7c5bab9 100644
--- a/lib/stdlib/doc/src/qlc.xml
+++ b/lib/stdlib/doc/src/qlc.xml
@@ -4,7 +4,7 @@
 <erlref>
   <header>
     <copyright>
-      <year>2004</year><year>2016</year>
+      <year>2004</year><year>2019</year>
       <holder>Ericsson AB. All Rights Reserved.</holder>
     </copyright>
     <legalnotice>
@@ -581,11 +581,13 @@ gb_iter(I0, N, EFun) ->
 <input>{K} &lt;- ets:table(E1),</input>
 <input>K == 2.71 orelse K == a]),</input>
 <input>io:format("~s~n", [qlc:info(Q1)]).</input>
-ets:match_spec_run(lists:flatmap(fun(V) ->
-                                        ets:lookup(20493, V)
-                                 end,
-                                 [a,2.71]),
-                   ets:match_spec_compile([{{'$1'},[],['$1']}]))</pre>
+ets:match_spec_run(
+       lists:flatmap(fun(V) ->
+			    ets:lookup(#Ref&lt;0.3098908599.2283929601.256025>,
+				       V)
+		     end,
+		     [a, 2.71]),
+       ets:match_spec_compile([{{'$1'}, [], ['$1']}]))</pre>
 
     <p>In the example, operator <c>==/2</c> has been handled
       exactly as <c>=:=/2</c> would have been handled. However,
@@ -607,9 +609,10 @@ ets:match_spec_run(lists:flatmap(fun(V) ->
 <input>end,</input>
 <input>Q2 = F2({2,2}),</input>
 <input>io:format("~s~n", [qlc:info(Q2)]).</input>
-ets:table(53264,
+ets:table(#Ref&lt;0.3098908599.2283929601.256125>,
           [{traverse,
-            {select,[{{'$1','$2'},[{'==','$1',{const,{2,2}}}],['$2']}]}}])
+            {select,
+             [{{'$1', '$2'}, [{'==', '$1', {const, {2, 2}}}], ['$2']}]}}])
 3> <input>lists:sort(qlc:e(Q2)).</input>
 [a,b,c]</pre>
 
@@ -629,8 +632,9 @@ ets:table(53264,
 <input>end,</input>
 <input>Q3 = F3({2,2}),</input>
 <input>io:format("~s~n", [qlc:info(Q3)]).</input>
-ets:match_spec_run(ets:lookup(86033, {2,2}),
-                   ets:match_spec_compile([{{'$1','$2'},[],['$2']}]))
+ets:match_spec_run(ets:lookup(#Ref&lt;0.3098908599.2283929601.256211>,
+                              {2, 2}),
+                   ets:match_spec_compile([{{'$1', '$2'}, [], ['$2']}]))
 5> <input>qlc:e(Q3).</input>
 [b]</pre>
 
@@ -892,21 +896,21 @@ begin
     V1 =
         qlc:q([
                SQV ||
-                   SQV &lt;- [x,y]
+                   SQV &lt;- [x, y]
               ],
-              [{unique,true}]),
+              [{unique, true}]),
     V2 =
         qlc:q([
                SQV ||
-                   SQV &lt;- [a,b]
+                   SQV &lt;- [a, b]
               ],
-              [{unique,true}]),
+              [{unique, true}]),
     qlc:q([
            {X,Y} ||
                X &lt;- V1,
                Y &lt;- V2
           ],
-          [{unique,true}])
+          [{unique, true}])
 end</pre>
         <p>In the following example QLC <c>V2</c> has
           been inserted to show the joined generators and the join
@@ -927,19 +931,21 @@ begin
     V1 =
         qlc:q([
                P0 ||
-                   P0 = {W,Y} &lt;- ets:table(17)
+                   P0 = {W, Y} &lt;-
+                       ets:table(#Ref&lt;0.3098908599.2283929601.256549>)
               ]),
     V2 =
         qlc:q([
-               [G1|G2] ||
+               [G1 | G2] ||
                    G2 &lt;- V1,
-                   G1 &lt;- ets:table(16),
+                   G1 &lt;-
+                       ets:table(#Ref&lt;0.3098908599.2283929601.256548>),
                    element(2, G1) =:= element(1, G2)
               ],
-              [{join,lookup}]),
+              [{join, lookup}]),
     qlc:q([
-           {X,Z,W} ||
-               [{X,Z}|{W,Y}] &lt;- V2
+           {X, Z, W} ||
+               [{X, Z} | {W, Y}] &lt;- V2
           ])
 end</pre>
       </desc>
@@ -1080,27 +1086,27 @@ begin
     V1 =
         qlc:q([
                P0 ||
-                   P0 = {X,Z} &lt;-
-                       qlc:keysort(1, [{a,1},{b,4},{c,6}], [])
+                   P0 = {X, Z} &lt;-
+                       qlc:keysort(1, [{a, 1}, {b, 4}, {c, 6}], [])
               ]),
     V2 =
         qlc:q([
                P0 ||
-                   P0 = {W,Y} &lt;-
-                       qlc:keysort(2, [{2,a},{3,b},{4,c}], [])
+                   P0 = {W, Y} &lt;-
+                       qlc:keysort(2, [{2, a}, {3, b}, {4, c}], [])
               ]),
     V3 =
         qlc:q([
-               [G1|G2] ||
+               [G1 | G2] ||
                    G1 &lt;- V1,
                    G2 &lt;- V2,
                    element(1, G1) == element(2, G2)
               ],
-              [{join,merge},{cache,list}]),
+              [{join, merge}, {cache, list}]),
     qlc:q([
-           {A,X,Z,W} ||
-               A &lt;- [a,b,c],
-               [{X,Z}|{W,Y}] &lt;- V3,
+           {A, X, Z, W} ||
+               A &lt;- [a, b, c],
+               [{X, Z} | {W, Y}] &lt;- V3,
                X =:= Y
           ])
 end</pre>
@@ -1141,14 +1147,21 @@ ets:match_spec_run(
                                 gb_trees:lookup(K,
                                                 gb_trees:from_orddict([]))
                             of
-                                {value,V} ->
-                                    [{K,V}];
+                                {value, V} ->
+                                    [{K, V}];
                                 none ->
                                     []
                             end
                      end,
-                     [{1,a},{1,b},{1,c},{2,a},{2,b},{2,c}]),
-       ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))</pre>
+                     [{1, a},
+                      {1, b},
+                      {1, c},
+                      {2, a},
+                      {2, b},
+                      {2, c}]),
+       ets:match_spec_compile([{{{'$1', '$2'}, '_'},
+                                [],
+                                ['$1']}]))</pre>
         <p>Options:</p>
         <list type="bulleted">
           <item>
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 2354a08f78..8a43f15d2c 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2004-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.
@@ -2436,7 +2436,7 @@ info(Config) when is_list(Config) ->
        <<"{'EXIT', {badarg, _}} = 
                (catch qlc:info([X || {X} <- []], {n_elements, 0})),
           L = lists:seq(1, 1000),
-          \"[1,2,3,4,5,6,7,8,9,10|'...']\" = qlc:info(L, {n_elements, 10}),
+          \"[1, 2, 3, 4, 5, 6, 7, 8, 9, 10 | '...']\" = qlc:info(L, {n_elements, 10}),
           {cons,A1,{integer,A2,1},{atom,A3,'...'}} =
             qlc:info(L, [{n_elements, 1},{format,abstract_code}]),
           1 = erl_anno:line(A1),
@@ -2447,8 +2447,8 @@ info(Config) when is_list(Config) ->
                                                             {atom,_,'...'}}}},
                      {call,_,_,_}]} = 
           qlc:info(Q, [{n_elements, 3},{format,abstract_code}]),
-          \"ets:match_spec_run([a,b,c,d,e,f],\n\"
-          \"                   ets:match_spec_compile([{'$1',[true],\"
+          \"ets:match_spec_run([a, b, c, d, e, f],\n\"
+          \"                   ets:match_spec_compile([{'$1', [true], \"
           \"[{{'$1'}}]}]))\" = 
              qlc:info(Q, [{n_elements, infinity}])">>,
 
@@ -6547,7 +6547,7 @@ otp_7114(Config) when is_list(Config) ->
 otp_7232(Config) when is_list(Config) ->
     Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"),
                   erlang:make_ref()],
-             \"[fun math:sqrt/1,<0.4.1>,#Ref<\" ++ _  = qlc:info(L),
+             \"[fun math:sqrt/1, <0.4.1>, #Ref<\" ++ _  = qlc:info(L),
              {call,_,
                {remote,_,{atom,_,qlc},{atom,_,sort}},
                [{cons,_,
@@ -6563,7 +6563,7 @@ otp_7232(Config) when is_list(Config) ->
              \"qlc:sort([55296,56296],[{order,fun'-function/0-fun-2-'/2}])\" =
                 format_info(Q, true),
              AC = qlc:info(Q, {format, abstract_code}),
-             \"qlc:sort([55296,56296], [{order,fun '-function/0-fun-2-'/2}])\" =
+             \"qlc:sort([55296, 56296], [{order, fun '-function/0-fun-2-'/2}])\" =
                 binary_to_list(iolist_to_binary(erl_pp:expr(AC)))">>,
 
          %% OTP-7234. erl_parse:abstract() handles bit strings
@@ -7088,21 +7088,21 @@ manpage(Config) when is_list(Config) ->
               \"    V1 =\n\"
               \"        qlc:q([ \n\"
               \"               SQV ||\n\"
-              \"                   SQV <- [x,y]\n\"
+              \"                   SQV <- [x, y]\n\"
               \"              ],\n\"
-              \"              [{unique,true}]),\n\"
+              \"              [{unique, true}]),\n\"
               \"    V2 =\n\"
               \"        qlc:q([ \n\"
               \"               SQV ||\n\"
-              \"                   SQV <- [a,b]\n\"
+              \"                   SQV <- [a, b]\n\"
               \"              ],\n\"
-              \"              [{unique,true}]),\n\"
+              \"              [{unique, true}]),\n\"
               \"    qlc:q([ \n\"
-              \"           {X,Y} ||\n\"
+              \"           {X, Y} ||\n\"
               \"               X <- V1,\n\"
               \"               Y <- V2\n\"
               \"          ],\n\"
-              \"          [{unique,true}])\n\"
+              \"          [{unique, true}])\n\"
               \"end\",
           true = B =:= qlc:info(QH, unique_all)">>,
 
@@ -7118,19 +7118,19 @@ manpage(Config) when is_list(Config) ->
               \"    V1 =\n\"
               \"        qlc:q([ \n\"
               \"               P0 ||\n\"
-              \"                   P0 = {W,Y} <- ets:table(_)\n\"
+              \"                   P0 = {W, Y} <- ets:table(_)\n\"
               \"              ]),\n\"
               \"    V2 =\n\"
               \"        qlc:q([ \n\"
-              \"               [G1|G2] ||\n\"
+              \"               [G1 | G2] ||\n\"
               \"                   G2 <- V1,\n\"
               \"                   G1 <- ets:table(_),\n\"
               \"                   element(2, G1) =:= element(1, G2)\n\"
               \"              ],\n\"
-              \"              [{join,lookup}]),\n\"
+              \"              [{join, lookup}]),\n\"
               \"    qlc:q([ \n\"
-              \"           {X,Z,W} ||\n\"
-              \"               [{X,Z}|{W,Y}] <- V2\n\"
+              \"           {X, Z, W} ||\n\"
+              \"               [{X, Z} | {W, Y}] <- V2\n\"
               \"          ])\n\"
               \"end\",
           Info1 =
@@ -7155,25 +7155,28 @@ manpage(Config) when is_list(Config) ->
        \"    V1 =\n\"
        \"        qlc:q([ \n\"
        \"               P0 ||\n\"
-       \"                   P0 = {X,Z} <- qlc:keysort(1, [{a,1},{b,4},{c,6}], [])\n\"
+       \"                   P0 = {X, Z} <-\n\"
+       \"                       qlc:keysort(1, [{a, 1}, {b, 4}, {c, 6}], [])\n\"
        \"              ]),\n\"
        \"    V2 =\n\"
        \"        qlc:q([ \n\"
        \"               P0 ||\n\"
-       \"                   P0 = {W,Y} <- qlc:keysort(2, [{2,a},{3,b},{4,c}], [])\n\"
+       \"                   P0 = {W, Y} <-\n\"
+       \"                       qlc:keysort(2, [{2, a}, {3, b}, {4, c}], [])\n\"
+
        \"              ]),\n\"
        \"    V3 =\n\"
        \"        qlc:q([ \n\"
-       \"               [G1|G2] ||\n\"
+       \"               [G1 | G2] ||\n\"
        \"                   G1 <- V1,\n\"
        \"                   G2 <- V2,\n\"
        \"                   element(1, G1) == element(2, G2)\n\"
        \"              ],\n\"
-       \"              [{join,merge},{cache,list}]),\n\"
+       \"              [{join, merge}, {cache, list}]),\n\"
        \"    qlc:q([ \n\"
-       \"           {A,X,Z,W} ||\n\"
-       \"               A <- [a,b,c],\n\"
-       \"               [{X,Z}|{W,Y}] <- V3,\n\"
+       \"           {A, X, Z, W} ||\n\"
+       \"               A <- [a, b, c],\n\"
+       \"               [{X, Z} | {W, Y}] <- V3,\n\"
        \"               X =:= Y\n\"
        \"          ])\n\"
        \"end\",
@@ -7215,14 +7218,21 @@ manpage(Config) when is_list(Config) ->
                                             gb_trees:lookup(K,
                                                             gb_trees:from_orddict([]))
                                         of
-                                            {value,V} ->
-                                                [{K,V}];
+                                            {value, V} ->
+                                                [{K, V}];
                                             none ->
                                                 []
                                         end
                                  end,
-                                 [{1,a},{1,b},{1,c},{2,a},{2,b},{2,c}]),
-                   ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))\",
+                                 [{1, a},
+                                  {1, b},
+                                  {1, c},
+                                  {2, a},
+                                  {2, b},
+                                  {2, c}]),
+                   ets:match_spec_compile([{{{'$1', '$2'}, '_'},
+                                            [],
+                                            ['$1']}]))\",
           L = qlc:info(QH)">>
       ],
     run(Config, Ts),
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 22136d687c..cdb6031b07 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2004-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.
@@ -2591,7 +2591,7 @@ otp_7184(Config) when is_list(Config) ->
 otp_7232(Config) when is_list(Config) ->
     Info = <<"qlc:info(qlc:sort(qlc:q([X || X <- [55296,56296]]), "
              "{order, fun(A,B)-> A>B end})).">>,
-    "qlc:sort([55296,56296],\n"
+    "qlc:sort([55296, 56296],\n"
     "         [{order,\n"
     "           fun(A, B) ->\n"
     "                  A > B\n"
@@ -2752,7 +2752,7 @@ otp_10302(Config) when is_list(Config) ->
            h().">>,
 
     "ok.\n\"\x{400}\"\nA = \"\x{400}\".\nok.\n"
-    "1: io:setopts([{encoding,utf8}])\n-> ok.\n"
+    "1: io:setopts([{encoding, utf8}])\n-> ok.\n"
     "2: A = [1024] = \"\x{400}\"\n-> \"\x{400}\"\n"
     "3: b()\n-> ok.\nok.\n" = t({Node,Test4}),
 
-- 
2.16.4

openSUSE Build Service is sponsored by