File 2594-stdlib-Fix-a-minor-pretty-printer-issue.patch of Package erlang

From 5400aa9c08502599977c0cc8040ff9b129d32cac Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Wed, 29 Jan 2020 12:58:54 +0100
Subject: [PATCH 4/5] stdlib: Fix a minor pretty printer issue

In certain cases a space is needed after an integer and before a hash
mark not to confuse the scanner.
---
 lib/stdlib/src/erl_pp.erl        | 20 +++++++++++++++++---
 lib/stdlib/test/erl_pp_SUITE.erl |  8 ++++++++
 2 files changed, 25 insertions(+), 3 deletions(-)

diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 4f0609efb7..4a9244f7e3 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -567,14 +567,16 @@ lexpr({record, _, Name, Fs}, Prec, Opts) ->
 lexpr({record_field, _, Rec, Name, F}, Prec, Opts) ->
     {L,P,R} = inop_prec('#'),
     Rl = lexpr(Rec, L, Opts),
-    Nl = [$#,{atom,Name},$.],
+    Sep = hash_after_integer(Rec, [$#]),
+    Nl = [Sep,{atom,Name},$.],
     El = [Rl,Nl,lexpr(F, R, Opts)],
     maybe_paren(P, Prec, El);
 lexpr({record, _, Rec, Name, Fs}, Prec, Opts) ->
     {L,P,_R} = inop_prec('#'),
     Rl = lexpr(Rec, L, Opts),
+    Sep = hash_after_integer(Rec, []),
     Nl = record_name(Name),
-    El = {first,[Rl,Nl],record_fields(Fs, Opts)},
+    El = {first,[Rl,Sep,Nl],record_fields(Fs, Opts)},
     maybe_paren(P, Prec, El);
 lexpr({record_field, _, {atom,_,''}, F}, Prec, Opts) ->
     {_L,P,R} = inop_prec('.'),
@@ -591,7 +593,8 @@ lexpr({map, _, Fs}, Prec, Opts) ->
 lexpr({map, _, Map, Fs}, Prec, Opts) ->
     {L,P,_R} = inop_prec('#'),
     Rl = lexpr(Map, L, Opts),
-    El = {first,[Rl,$#],map_fields(Fs, Opts)},
+    Sep = hash_after_integer(Map, [$#]),
+    El = {first,[Rl|Sep],map_fields(Fs, Opts)},
     maybe_paren(P, Prec, El);
 lexpr({block,_,Es}, _, Opts) ->
     {list,[{step,'begin',body(Es, Opts)},{reserved,'end'}]};
@@ -721,6 +724,17 @@ lexpr(HookExpr, Precedence, #options{hook = {Mod,Func,Eas}})
 lexpr(HookExpr, Precedence, #options{hook = Func, opts = Options}) ->
     {hook,HookExpr,Precedence,Func,Options}.
 
+%% An integer is separated from the following '#' by a space, which
+%% erl_scan can handle.
+hash_after_integer({integer, _, _}, C) ->
+    [$\s|C];
+hash_after_integer({'fun',_,{function, _, _}}, C) ->
+    [$\s|C];
+hash_after_integer({'fun',_,{function, _, _, _}}, C) ->
+    [$\s|C];
+hash_after_integer(_, C) ->
+    C.
+
 call(Name, Args, Prec, Opts) ->
     {F,P} = func_prec(),
     Item = {first,lexpr(Name, F, Opts),args(Args, Opts)},
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index f341e3a7bf..0dc315e7bb 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1274,6 +1274,14 @@ otp_16435(_Config) ->
            "          A <- []\n    >>.\n"),
     CheckF("f() ->\n    [ \n     (catch foo) ||\n         A <- []\n    ].\n"),
 
+
+    Check = fun(S) -> S = flat_parse_and_pp_expr(S, 0, []) end,
+    Check("5 #r4.f1"),
+    Check("17 #{[] => true}"),
+    Check("0 #r1{f2 = foo}"),
+    Check("fun foo:bar/17 #{}"),
+    Check("fun a/2 #{}"),
+
     ok.
 
 gh_5093(_Config) ->
-- 
2.16.4

openSUSE Build Service is sponsored by