File 3021-erts-support-unicode-cmdline-in-compilation-server.patch of Package erlang
From 29b15f58f57f83a141fe430104b5aaa3e7d98d6e Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Wed, 14 Sep 2022 12:57:40 +0200
Subject: [PATCH] erts: support unicode cmdline in compilation server
---
erts/etc/common/erlc.c | 5 ++--
erts/test/erlc_SUITE.erl | 26 ++++++++++++++++++-
.../\360\237\230\200/erl_test_unicode.erl" | 25 ++++++++++++++++++
lib/kernel/src/erl_compile_server.erl | 7 ++---
lib/stdlib/test/edlin_expand_SUITE.erl | 2 +-
5 files changed, 57 insertions(+), 8 deletions(-)
create mode 100644 "erts/test/erlc_SUITE_data/src/\360\237\230\200/erl_test_unicode.erl"
diff --git a/erts/etc/common/erlc.c b/erts/etc/common/erlc.c
index 6cded37733..da378a8654 100644
--- a/erts/etc/common/erlc.c
+++ b/erts/etc/common/erlc.c
@@ -742,14 +742,14 @@ call_compile_server(char** argv)
ei_x_encode_atom(&args, "encoding");
ei_x_encode_atom(&args, get_encoding());
ei_x_encode_atom(&args, "cwd");
- ei_x_encode_string(&args, cwd);
+ ei_x_encode_binary(&args, cwd, strlen(cwd));
ei_x_encode_atom(&args, "env");
encode_env(&args);
ei_x_encode_atom(&args, "command_line");
argc = 0;
while (argv[argc]) {
ei_x_encode_list_header(&args, 1);
- ei_x_encode_string(&args, possibly_unquote(argv[argc]));
+ ei_x_encode_binary(&args, possibly_unquote(argv[argc]), strlen(argv[argc]));
argc++;
}
ei_x_encode_empty_list(&args); /* End of command_line */
@@ -773,7 +773,6 @@ call_compile_server(char** argv)
/*
* Decode the answer.
*/
-
dec_index = 0;
if (ei_decode_atom(reply.buff, &dec_index, atom) == 0 &&
strcmp(atom, "wrong_config") == 0) {
diff --git a/erts/test/erlc_SUITE.erl b/erts/test/erlc_SUITE.erl
index 449aedf301..213215fa17 100644
--- a/erts/test/erlc_SUITE.erl
+++ b/erts/test/erlc_SUITE.erl
@@ -28,6 +28,7 @@
compile_yecc/1, compile_script/1,
compile_mib/1, good_citizen/1, deep_cwd/1, arg_overflow/1,
make_dep_options/1,
+ unicode_paths/1,
features_erlc_describe/1,
features_erlc_unknown/1,
features_directives/1,
@@ -56,7 +57,8 @@ groups() ->
tests() ->
[compile_erl, compile_yecc, compile_script, compile_mib,
- good_citizen, deep_cwd, arg_overflow, make_dep_options].
+ good_citizen, deep_cwd, arg_overflow, make_dep_options,
+ unicode_paths].
feature_tests() ->
[features_erlc_describe,
@@ -487,6 +489,28 @@ make_dep_options(Config) ->
false = exists(BeamFileName),
ok.
+unicode_paths(Config) ->
+ case {os:type(), file:native_name_encoding()} of
+ {{win32,_}, _} -> {skip, "Unicode paths not supported on windows"};
+ {_,latin1} -> {skip, "Cannot interpret unicode filenames when native_name_encoding is latin1"};
+ _ ->
+ DepRE = ["_OK_"],
+ {SrcDir,OutDir0,Cmd0} = get_cmd(Config),
+ OutDir = filename:join(OutDir0,"😀"),
+ ok = case file:make_dir(OutDir) of
+ {error, eexist} -> ok;
+ ok -> ok;
+ E -> E
+ end,
+ Cmd = Cmd0 ++ " +brief -o "++OutDir,
+ FileName = filename:join([SrcDir, "😀", "erl_test_unicode.erl"]),
+ BeamFileName = filename:join(OutDir, "erl_test_unicode.beam"),
+ run(Config, Cmd, FileName, "", DepRE),
+ true = exists(BeamFileName),
+ file:delete(BeamFileName),
+ file:delete(OutDir)
+ end,
+ ok.
%%% Tests related to the features mechanism
%% Support macros and functions
diff --git "a/erts/test/erlc_SUITE_data/src/\360\237\230\200/erl_test_unicode.erl" "b/erts/test/erlc_SUITE_data/src/\360\237\230\200/erl_test_unicode.erl"
new file mode 100644
index 0000000000..32a208b7e2
--- /dev/null
+++ "b/erts/test/erlc_SUITE_data/src/\360\237\230\200/erl_test_unicode.erl"
@@ -0,0 +1,25 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 1997-2016. 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.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(erl_test_unicode).
+-export(['😀'/1]).
+
+'😀'(0) ->
+ '😀'.
diff --git a/lib/kernel/src/erl_compile_server.erl b/lib/kernel/src/erl_compile_server.erl
index f4b719068e..b679b277b8 100644
--- a/lib/kernel/src/erl_compile_server.erl
+++ b/lib/kernel/src/erl_compile_server.erl
@@ -68,7 +68,7 @@ handle_call({compile, Parameters}, From, #st{jobs=Jobs}=St0) ->
case verify_context(PathArgs, Parameters, St0) of
{ok, St1} ->
#{cwd := Cwd, encoding := Enc} = Parameters,
- PidRef = spawn_monitor(fun() -> exit(do_compile(ErlcArgs, Cwd, Enc)) end),
+ PidRef = spawn_monitor(fun() -> exit(do_compile(ErlcArgs, unicode:characters_to_list(Cwd, Enc), Enc)) end),
St = St1#st{jobs=Jobs#{PidRef => From}},
{noreply, St#st{timeout=?IDLE_TIMEOUT}};
wrong_config ->
@@ -145,8 +145,9 @@ do_compile(ErlcArgs, Cwd, Enc) ->
{error, StdOutput, StdErrorOutput}
end.
-parse_command_line(#{command_line := CmdLine, cwd := Cwd}) ->
- parse_command_line_1(CmdLine, Cwd, [], []).
+parse_command_line(#{command_line := CmdLine0, cwd := Cwd, encoding := Enc}) ->
+ CmdLine = lists:map(fun(A) -> unicode:characters_to_list(A, Enc) end, CmdLine0),
+ parse_command_line_1(CmdLine, unicode:characters_to_list(Cwd, Enc), [], []).
parse_command_line_1(["-pa", Pa|T], Cwd, PaAcc, PzAcc) ->
parse_command_line_1(T, Cwd, [Pa|PaAcc], PzAcc);
--
2.35.3