File 0744-yeccpre.hrl-Never-crash-when-printing-non-standard-t.patch of Package erlang

From 86508d46932fb2c8d2a670151df8db0886531054 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 25 Nov 2021 08:16:29 +0100
Subject: [PATCH] yeccpre.hrl: Never crash when printing non-standard tokens

The standard prologue file (`yeccpre.hrl`) for yecc could crash while
attempting to report a syntax error involving a token not produced by
the `erl_scan` module.

For example, the token `{string,0,<<"hello">>}` looks like a string
token produced by `erl_scan`, but the string value is a binary instead
of the expected list and the default implementation of
`yecctoken_to_string/1` would crash when asked to print it.

Make `yecctoken_to_string/1` more resilient against crashing by
printing the entire token as is if there is a crash when printing
it in the usual way.

(Note: A parser that uses its own non-standard scanner should use its
own customized prologue file if nicely printed tokens are desired.)
---
 lib/parsetools/include/yeccpre.hrl | 33 +++++++++++++++++++-----------
 lib/parsetools/test/yecc_SUITE.erl | 23 ++++++++++++++++++++-
 2 files changed, 43 insertions(+), 13 deletions(-)

diff --git a/lib/parsetools/include/yeccpre.hrl b/lib/parsetools/include/yeccpre.hrl
index 6cfdb60078..e0b132c180 100644
--- a/lib/parsetools/include/yeccpre.hrl
+++ b/lib/parsetools/include/yeccpre.hrl
@@ -148,19 +148,28 @@ yecctoken_location(Token) ->
     end.
 
 -compile({nowarn_unused_function, yecctoken2string/1}).
-yecctoken2string({atom, _, A}) -> io_lib:write_atom(A);
-yecctoken2string({integer,_,N}) -> io_lib:write(N);
-yecctoken2string({float,_,F}) -> io_lib:write(F);
-yecctoken2string({char,_,C}) -> io_lib:write_char(C);
-yecctoken2string({var,_,V}) -> io_lib:format("~s", [V]);
-yecctoken2string({string,_,S}) -> io_lib:write_string(S);
-yecctoken2string({reserved_symbol, _, A}) -> io_lib:write(A);
-yecctoken2string({_Cat, _, Val}) -> io_lib:format("~tp", [Val]);
-yecctoken2string({dot, _}) -> "'.'";
-yecctoken2string({'$end', _}) -> [];
-yecctoken2string({Other, _}) when is_atom(Other) ->
+yecctoken2string(Token) ->
+    try
+        yecctoken2string1(Token)
+    catch
+        _:_ ->
+            io_lib:format("~tp", [Token])
+    end.
+
+-compile({nowarn_unused_function, yecctoken2string1/1}).
+yecctoken2string1({atom, _, A}) -> io_lib:write_atom(A);
+yecctoken2string1({integer,_,N}) -> io_lib:write(N);
+yecctoken2string1({float,_,F}) -> io_lib:write(F);
+yecctoken2string1({char,_,C}) -> io_lib:write_char(C);
+yecctoken2string1({var,_,V}) -> io_lib:format("~s", [V]);
+yecctoken2string1({string,_,S}) -> io_lib:write_string(S);
+yecctoken2string1({reserved_symbol, _, A}) -> io_lib:write(A);
+yecctoken2string1({_Cat, _, Val}) -> io_lib:format("~tp", [Val]);
+yecctoken2string1({dot, _}) -> "'.'";
+yecctoken2string1({'$end', _}) -> [];
+yecctoken2string1({Other, _}) when is_atom(Other) ->
     io_lib:write_atom(Other);
-yecctoken2string(Other) ->
+yecctoken2string1(Other) ->
     io_lib:format("~tp", [Other]).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/parsetools/test/yecc_SUITE.erl b/lib/parsetools/test/yecc_SUITE.erl
index cfdb3e4458..83daa91535 100644
--- a/lib/parsetools/test/yecc_SUITE.erl
+++ b/lib/parsetools/test/yecc_SUITE.erl
@@ -1218,8 +1218,29 @@ yeccpre(Config) when is_list(Config) ->
                 ok.
            ">>,
            default,
+           ok},
+
+          {error_3, <<"
+            Nonterminals statement.
+            Terminals keyword string.
+            Rootsymbol statement.
+
+            statement -> keyword string.
+
+            Erlang code.
+
+            -export([t/0]).
+
+            t() ->
+                %% Never crash in yecctoken_to_string/1 or its helpers,
+                %% even if when tokens are not in the format that erl_scan
+                %% produces.
+                {error, _} = parse([{string, 1, <<\"foo\">>}]),
+                ok.
+           ">>,
+           default,
            ok}],
-       
+
     run(Config, Ts),
     ok.
 
-- 
2.31.1

openSUSE Build Service is sponsored by