Skip to content

Commit d6b2f3b

Browse files
committed
Merge branch 'raimo/triple-quoted-strings-warning' OTP-18821 into maint
* raimo/triple-quoted-strings-warning: Fix OTP test suite Implement warning for adjacent string literals without intervening white space
2 parents 36cd8bd + f1d8f88 commit d6b2f3b

File tree

8 files changed

+88
-68
lines changed

8 files changed

+88
-68
lines changed
3.78 KB
Binary file not shown.

bootstrap/lib/stdlib/ebin/epp.beam

120 Bytes
Binary file not shown.

lib/kernel/test/prim_file_SUITE.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -710,7 +710,7 @@ file_info_basic_file(Config) when is_list(Config) ->
710710
%% Create a short file.
711711
Name = filename:join(RootDir,
712712
atom_to_list(?MODULE)
713-
++"_basic_test"".fil"),
713+
++"_basic_test.fil"),
714714
{ok,Fd1} = ?PRIM_FILE:open(Name, [write]),
715715
?PRIM_FILE:write(Fd1, "foo bar"),
716716
ok = ?PRIM_FILE:close(Fd1),

lib/stdlib/src/epp.erl

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -251,7 +251,12 @@ format_error({warning,Term}) ->
251251
format_error(ftr_after_prefix) ->
252252
"feature directive not allowed after exports or record definitions";
253253
format_error(tqstring) ->
254-
"Triple-quoted (or more) strings will change meaning in OTP-27.0";
254+
"triple-quoted (or more) strings will change meaning in OTP-27.0";
255+
format_error(string_concat) ->
256+
"adjacent string literals without intervening white space\n"
257+
"In OTP-27.0 this will be a triple-quoted string or an error.\n"
258+
"Rewrite them as one string, or insert white space\n"
259+
"between the strings.";
255260
format_error(E) -> file:format_error(E).
256261

257262
-spec scan_file(FileName, Options) ->
@@ -352,9 +357,10 @@ parse_file(Epp) ->
352357
case epp_request(Epp, scan_erl_form) of
353358
{ok,Toks} ->
354359
Warnings =
355-
[{warning, {erl_anno:location(Anno),?MODULE,tqstring}}
356-
%% Warn about using 3 or more double qoutes
357-
|| {tqstring,Anno,_} <- Toks],
360+
[{warning, {erl_anno:location(Anno),?MODULE,Tag}}
361+
|| {Tag,Anno,_} <- Toks,
362+
%% Warn for string concatenation without white space
363+
Tag =:= string_concat],
358364
case erl_parse:parse_form(Toks) of
359365
{ok, Form} ->
360366
[Form|Warnings] ++ parse_file(Epp);

lib/stdlib/src/erl_parse.yrl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ ssa_check_when_clause
7777
ssa_check_when_clauses.
7878

7979
Terminals
80-
char integer float atom tqstring string var
80+
char integer float atom string string_concat var
8181

8282
'(' ')' ',' '->' '{' '}' '[' ']' '|' '||' '<-' ';' ':' '#' '.'
8383
'after' 'begin' 'case' 'try' 'catch' 'end' 'fun' 'if' 'of' 'receive' 'when'
@@ -546,11 +546,11 @@ atomic -> atom : '$1'.
546546
atomic -> strings : '$1'.
547547

548548
strings -> string : '$1'.
549-
strings -> tqstring : {string,?anno('$1'),element(3, '$1')}.
549+
strings -> string string_concat : '$1'.
550550
strings -> string strings :
551551
{string,?anno('$1'),element(3, '$1') ++ element(3, '$2')}.
552-
strings -> tqstring strings :
553-
{string,?anno('$1'),element(3, '$1') ++ element(3, '$2')}.
552+
strings -> string string_concat strings :
553+
{string,?anno('$1'),element(3, '$1') ++ element(3, '$3')}.
554554

555555
prefix_op -> '+' : '$1'.
556556
prefix_op -> '-' : '$1'.

lib/stdlib/src/erl_scan.erl

Lines changed: 13 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -425,12 +425,6 @@ scan1("."=Cs, St, Line, Col, Toks) ->
425425
{more,{Cs,St,Col,Toks,Line,[],fun scan/6}};
426426
scan1([$.=C|Cs], St, Line, Col, Toks) ->
427427
scan_dot(Cs, St, Line, Col, Toks, [C]);
428-
scan1([$",$",$"|Cs], St, Line, Col, Toks) -> %" Emacs
429-
scan_tqstring(Cs, St, Line, Col, Toks, 3); % Number of quote chars
430-
scan1([$",$"]=Cs, St, Line, Col, Toks) ->
431-
{more,{Cs,St,Col,Toks,Line,[],fun scan/6}};
432-
scan1([$"]=Cs, St, Line, Col, Toks) -> %" Emacs
433-
{more,{Cs,St,Col,Toks,Line,[],fun scan/6}};
434428
scan1([$"|Cs], St, Line, Col, Toks) -> %" Emacs
435429
State0 = {[],[],Line,Col},
436430
scan_string(Cs, St, Line, incr_column(Col, 1), Toks, State0);
@@ -834,31 +828,6 @@ scan_char([], St, Line, Col, Toks) ->
834828
scan_char(eof, _St, Line, Col, _Toks) ->
835829
scan_error(char, Line, Col, Line, incr_column(Col, 1), eof).
836830

837-
%% Scan leading $" characters until we have them all
838-
%%
839-
scan_tqstring(Cs, St, Line, Col, Toks, Qs) ->
840-
case Cs of
841-
[$"|Ncs] ->
842-
scan_tqstring(Ncs, St, Line, Col, Toks, Qs+1);
843-
[] ->
844-
{more, {[], St, Col, Toks, Line, Qs, fun scan_tqstring/6}};
845-
_ ->
846-
scan_tqstring_finish(Cs, St, Line, Col, Toks, Qs, tqstring)
847-
end.
848-
849-
scan_tqstring_finish(Cs, St, Line, Col, Toks, Qs, TokTag) when 1 < Qs ->
850-
Anno = anno(Line, Col, St, ?STR(string, St, [$",$"])),
851-
Tok = {TokTag, Anno, ""},
852-
scan_tqstring_finish(
853-
Cs, St, Line, incr_column(Col, 2), [Tok|Toks], Qs-2, string);
854-
scan_tqstring_finish(Cs, St, Line, Col, Toks, Qs, _TokTag) ->
855-
Ncs =
856-
case Qs of
857-
1 -> [$"|Cs];%"
858-
0 -> Cs
859-
end,
860-
scan1(Ncs, St, Line, Col, Toks).
861-
862831
scan_string(Cs, #erl_scan{}=St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->
863832
case scan_string0(Cs, St, Line, Col, $\", Str, Wcs) of %"
864833
{more,Ncs,Nline,Ncol,Nstr,Nwcs} ->
@@ -871,7 +840,19 @@ scan_string(Cs, #erl_scan{}=St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->
871840
scan_error({string,$\",Estr}, Line0, Col0, Nline, Ncol, Ncs); %"
872841
{Ncs,Nline,Ncol,Nstr,Nwcs} ->
873842
Anno = anno(Line0, Col0, St, ?STR(string, St, Nstr)),
874-
scan1(Ncs, St, Nline, Ncol, [{string,Anno,Nwcs}|Toks])
843+
scan_string_concat(
844+
Ncs, St, Nline, Ncol, [{string,Anno,Nwcs}|Toks], [])
845+
end.
846+
847+
scan_string_concat(Cs, St, Line, Col, Toks, _) ->
848+
case Cs of
849+
[$"|_] ->
850+
Anno = anno(Line, Col, St, ?STR(string, St, "")),
851+
scan1(Cs, St, Line, Col, [{string_concat,Anno,""}|Toks]);
852+
[] ->
853+
{more,{Cs,St,Col,Toks,Line,[],fun scan_string_concat/6}};
854+
_ ->
855+
scan1(Cs, St, Line, Col, Toks)
875856
end.
876857

877858
scan_qatom(Cs, #erl_scan{}=St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->

lib/stdlib/test/epp_SUITE.erl

Lines changed: 51 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@
3030
otp_11728/1, encoding/1, extends/1, function_macro/1,
3131
test_error/1, test_warning/1, otp_14285/1,
3232
test_if/1,source_name/1,otp_16978/1,otp_16824/1,scan_file/1,file_macro/1,
33-
triple_quotes_warning/1,
33+
string_concat_warning/1,
3434
deterministic_include/1, nondeterministic_include/1]).
3535

3636
-export([epp_parse_erl_form/2]).
@@ -74,7 +74,7 @@ all() ->
7474
otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
7575
encoding, extends, function_macro, test_error, test_warning,
7676
otp_14285, test_if, source_name, otp_16978, otp_16824, scan_file, file_macro,
77-
triple_quotes_warning,
77+
string_concat_warning,
7878
deterministic_include, nondeterministic_include].
7979

8080
groups() ->
@@ -937,6 +937,7 @@ scan_file(Config) when is_list(Config) ->
937937
[{'-',_}, {atom,_,export}, {'(',_} | _ ] = ExportForm,
938938
[{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm2,
939939
[{'-',_}, {atom,_,file}, {'(',_} | _ ] = FileForm3,
940+
[{atom,_,ok}, {'(',_} | _ ] = FunctionForm,
940941
ok.
941942

942943
macs(Epp) ->
@@ -2057,73 +2058,98 @@ otp_16824(Config) when is_list(Config) ->
20572058
[] = compile(Config, Cs),
20582059
ok.
20592060

2060-
triple_quotes_warning(Config) when is_list(Config) ->
2061+
string_concat_warning(Config) when is_list(Config) ->
20612062
Cs1 =
2062-
[{triple_quotes_warning_1,
2063+
[{string_concat_warning_1,
2064+
<<"\n"
2065+
"-export([foo/0]).\n"
2066+
"foo() ->\n"
2067+
" \" \"\"\".\n">>,
2068+
{warnings,
2069+
[{{4,8},epp,string_concat}]}},
2070+
{string_concat_warning_2,
2071+
<<"\n"
2072+
"-export([foo/0]).\n"
2073+
"foo() ->\n"
2074+
" \" \"\"\" \" \"\"\".\n">>,
2075+
{warnings,
2076+
[{{4,8},epp,string_concat},
2077+
{{4,14},epp,string_concat}]}}],
2078+
[] = compile(Config, Cs1),
2079+
2080+
Cs2 =
2081+
[{string_concat_warning_3,
20632082
<<"\n-doc \"foo\".\n">>,
20642083
[]},
2065-
{triple_quotes_warning_2,
2084+
{string_concat_warning_4,
20662085
<<"\n-doc \"\" \"foo\" \"\".\n">>,
20672086
[]},
2068-
{triple_quotes_warning_3,
2087+
{string_concat_warning_5,
20692088
<<"\n"
20702089
"-doc \"\"\"\n"
20712090
" foo\n"
20722091
" \"\"\".\n">>,
2073-
{warnings,[{{2,6},epp,tqstring}]}},
2074-
{triple_quotes_warning_4,
2092+
{warnings,
2093+
[{{2,8},epp,string_concat},
2094+
{{4,6},epp,string_concat}]}},
2095+
{string_concat_warning_6,
20752096
<<"\n"
20762097
"-doc \"\"\"\"\n"
20772098
" \"\"\"\".\n">>,
20782099
{warnings,
2079-
[{{2,7},epp,tqstring},
2080-
{{3,7},epp,tqstring}]}},
2081-
{triple_quotes_warning_5,
2100+
[{{2,9},epp,string_concat},
2101+
{{3,9},epp,string_concat}]}},
2102+
{string_concat_warning_7,
20822103
<<"\n"
20832104
"-doc \"\"\"\"\"\n"
20842105
" foo\n"
20852106
" \"\"\"\"\".\n">>,
20862107
{warnings,
2087-
[{{2,8},epp,tqstring},
2088-
{{4,9},epp,tqstring}]}}
2108+
[{{2,10},epp,string_concat},
2109+
{{2,12},epp,string_concat},
2110+
{{4,9},epp,string_concat},
2111+
{{4,11},epp,string_concat}]}}
20892112
],
2090-
[] = compile(Config, Cs1),
2113+
[] = compile(Config, Cs2),
20912114

2092-
Cs2 =
2093-
[{triple_quotes_warning_10,
2115+
Cs3 =
2116+
[{string_concat_warning_8,
20942117
<<"\n"
20952118
"-export([foo/0]).\n"
20962119
"foo() ->\n"
20972120
" \"\"\"\n"
20982121
" bar\n"
20992122
" \"\"\".\n">>,
2100-
{warnings,[{{4,5},epp,tqstring}]}},
2101-
{triple_quotes_warning_11,
2123+
{warnings,
2124+
[{{4,7},epp,string_concat},
2125+
{{6,6},epp,string_concat}]}},
2126+
{string_concat_warning_9,
21022127
<<"\n"
21032128
"-export([foo/0]).\n"
21042129
"foo() ->\n"
21052130
" \"\"\"\"\n"
21062131
" ++ lists:duplicate(4, $x) ++\n"
21072132
" \"\"\"\".\n">>,
21082133
{warnings,
2109-
[{{4,5},epp,tqstring},
2110-
{{6,5},epp,tqstring}]}},
2111-
{triple_quotes_warning_12,
2134+
[{{4,7},epp,string_concat},
2135+
{{6,7},epp,string_concat}]}},
2136+
{string_concat_warning_10,
21122137
<<"\n"
21132138
"-export([foo/0]).\n"
21142139
"foo() ->\n"
21152140
" \"\"\"\"\"\n"
21162141
" bar\n"
21172142
" \"\"\"\"\".\n">>,
21182143
{warnings,
2119-
[{{4,5},epp,tqstring},
2120-
{{6,6},epp,tqstring}]}} ],
2121-
[] = compile(Config, Cs2),
2144+
[{{4,7},epp,string_concat},
2145+
{{4,9},epp,string_concat},
2146+
{{6,6},epp,string_concat},
2147+
{{6,8},epp,string_concat}]}} ],
2148+
[] = compile(Config, Cs3),
21222149

21232150
ok.
21242151

21252152

2126-
21272153
%% Start location is 1.
21282154
check(Config, Tests) ->
21292155
eval_tests(Config, fun check_test/3, Tests).

system/doc/general_info/upcoming_incompatibilities.xml

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -278,15 +278,22 @@ String Content
278278
"++ foo() ++"
279279
</pre>
280280
<p>
281-
From Erlang/OTP 26.1 up to 27.0 the compiler issues a warning for
282-
a sequence of 3 or more double-quote characters
281+
From Erlang/OTP 26.1 up to 26.2 the compiler issues a warning
282+
for a sequence of 3 or more double-quote characters
283283
since that is almost certainly a mistake or
284284
something like a result of bad automatic code generation.
285285
If a users gets that warning, the code should be corrected
286286
for example by inserting appropriate spaces between
287287
the empty strings, or removing the redundant ones alltogether,
288288
which will have the same meaning before and after Erlang/OTP 27.
289289
</p>
290+
<p>
291+
From Erlang/OTP 26.2 up to 27.0 this is improved
292+
so the compiler instead issues a warning for adjacent string literals
293+
without intervening white space, which effectively is the same
294+
at a string start, but also covers the same situation
295+
at a string end.
296+
</p>
290297
</section>
291298

292299
</section>

0 commit comments

Comments
 (0)