Skip to content

Commit

Permalink
Fix io:format error messages
Browse files Browse the repository at this point in the history
  • Loading branch information
juhlig committed Jun 25, 2024
1 parent c0c2750 commit 4c6a99f
Show file tree
Hide file tree
Showing 5 changed files with 93 additions and 70 deletions.
134 changes: 68 additions & 66 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ Module:format_error(ErrorDescriptor)
-export([is_guard_expr/1]).
-export([bool_option/4,value_option/3,value_option/7]).

-export([check_format_string/1]).
-export([check_format_string/1, check_format_string/2]).

-export_type([error_info/0, error_description/0]).
-export_type([fun_used_vars/0]). % Used from erl_eval.erl.
Expand Down Expand Up @@ -4593,7 +4593,7 @@ check_format_2a(Fmt, FmtAnno, As) ->
end.

check_format_3(Fmt, FmtAnno, As) ->
case check_format_string(Fmt) of
case check_format_string(Fmt, true) of
{ok,Need} ->
check_format_4(Need, FmtAnno, As);
{error,S} ->
Expand Down Expand Up @@ -4643,99 +4643,101 @@ args_list(_Other) -> 'maybe'.
args_length({cons,_A,_H,T}) -> 1 + args_length(T);
args_length({nil,_A}) -> 0.


-doc false.
check_format_string(Fmt) when is_atom(Fmt) ->
check_format_string(atom_to_list(Fmt));
check_format_string(Fmt) when is_binary(Fmt) ->
check_format_string(binary_to_list(Fmt));
check_format_string(Fmt) ->
extract_sequences(Fmt, []).
check_format_string(Fmt, true).

extract_sequences(Fmt, Need0) ->
-doc false.
check_format_string(Fmt, Strict) when is_atom(Fmt) ->
check_format_string(atom_to_list(Fmt), Strict);
check_format_string(Fmt, Strict) when is_binary(Fmt) ->
check_format_string(binary_to_list(Fmt), Strict);
check_format_string(Fmt, Strict) ->
extract_sequences(Fmt, [], Strict).

extract_sequences(Fmt, Need0, Strict) ->
case string:find(Fmt, [$~]) of
nomatch -> {ok,lists:reverse(Need0)}; %That's it
[$~|Fmt1] ->
case extract_sequence(1, Fmt1, Need0) of
{ok,Need1,Rest} -> extract_sequences(Rest, Need1);
case extract_sequence(1, Fmt1, Need0, Strict) of
{ok,Need1,Rest} -> extract_sequences(Rest, Need1, Strict);
Error -> Error
end
end.

extract_sequence(1, [$-,C|Fmt], Need)
extract_sequence(1, [$-,C|Fmt], Need, Strict)
when is_integer(C), C >= $0, C =< $9 ->
extract_sequence_digits(1, Fmt, Need);
extract_sequence(1, [C|Fmt], Need)
extract_sequence_digits(1, Fmt, Need, Strict);
extract_sequence(1, [C|Fmt], Need, Strict)
when is_integer(C), C >= $0, C =< $9 ->
extract_sequence_digits(1, Fmt, Need);
extract_sequence(1, [$-,$*|Fmt], Need) ->
extract_sequence(2, Fmt, [int|Need]);
extract_sequence(1, [$*|Fmt], Need) ->
extract_sequence(2, Fmt, [int|Need]);
extract_sequence(1, Fmt, Need) ->
extract_sequence(2, Fmt, Need);

extract_sequence(2, [$.,C|Fmt], Need)
extract_sequence_digits(1, Fmt, Need, Strict);
extract_sequence(1, [$-,$*|Fmt], Need, Strict) ->
extract_sequence(2, Fmt, [int|Need], Strict);
extract_sequence(1, [$*|Fmt], Need, Strict) ->
extract_sequence(2, Fmt, [int|Need], Strict);
extract_sequence(1, Fmt, Need, Strict) ->
extract_sequence(2, Fmt, Need, Strict);

extract_sequence(2, [$.,C|Fmt], Need, Strict)
when is_integer(C), C >= $0, C =< $9 ->
extract_sequence_digits(2, Fmt, Need);
extract_sequence(2, [$.,$*|Fmt], Need) ->
extract_sequence(3, Fmt, [int|Need]);
extract_sequence(2, [$.|Fmt], Need) ->
extract_sequence(3, Fmt, Need);
extract_sequence(2, Fmt, Need) ->
extract_sequence(4, Fmt, Need);

extract_sequence(3, [$.,$*|Fmt], Need) ->
extract_sequence(4, Fmt, [int|Need]);
extract_sequence(3, [$.,_|Fmt], Need) ->
extract_sequence(4, Fmt, Need);
extract_sequence(3, Fmt, Need) ->
extract_sequence(4, Fmt, Need);

extract_sequence(4, Fmt0, Need) ->
case extract_modifiers(Fmt0, []) of
extract_sequence_digits(2, Fmt, Need, Strict);
extract_sequence(2, [$.,$*|Fmt], Need, Strict) ->
extract_sequence(3, Fmt, [int|Need], Strict);
extract_sequence(2, [$.|Fmt], Need, Strict) ->
extract_sequence(3, Fmt, Need, Strict);
extract_sequence(2, Fmt, Need, Strict) ->
extract_sequence(4, Fmt, Need, Strict);

extract_sequence(3, [$.,$*|Fmt], Need, Strict) ->
extract_sequence(4, Fmt, [int|Need], Strict);
extract_sequence(3, [$.,_|Fmt], Need, Strict) ->
extract_sequence(4, Fmt, Need, Strict);
extract_sequence(3, Fmt, Need, Strict) ->
extract_sequence(4, Fmt, Need, Strict);

extract_sequence(4, Fmt0, Need0, Strict) ->
case extract_modifiers(Fmt0, [], Need0, Strict) of
{error, _} = Error ->
Error;
{[C|Fmt], Modifiers} ->
{[C|Fmt], Modifiers, Need1} when Strict ->
maybe
ok ?= check_modifiers(C, Modifiers),
case ordsets:is_element($K, Modifiers) of
true ->
extract_sequence(5, [C|Fmt], ['fun'|Need]);
false ->
extract_sequence(5, [C|Fmt], Need)
end
extract_sequence(5, [C|Fmt], Need1, Strict)
end;
{[], _} ->
extract_sequence(5, [], Need)
{Fmt, _, Need1} ->
extract_sequence(5, Fmt, Need1, Strict)
end;

extract_sequence(5, [C|Fmt], Need0) ->
extract_sequence(5, [C|Fmt], Need0, _Strict) ->
case control_type(C, Need0) of
error -> {error,"invalid control ~" ++ [C]};
Need1 -> {ok,Need1,Fmt}
end;
extract_sequence(_, [], _Need) -> {error,"truncated"}.
extract_sequence(_, [], _Need, _Strict) -> {error,"truncated"}.
extract_sequence_digits(Fld, [C|Fmt], Need)
extract_sequence_digits(Fld, [C|Fmt], Need, Strict)
when is_integer(C), C >= $0, C =< $9 ->
extract_sequence_digits(Fld, Fmt, Need);
extract_sequence_digits(Fld, Fmt, Need) ->
extract_sequence(Fld+1, Fmt, Need).
extract_sequence_digits(Fld, Fmt, Need, Strict);
extract_sequence_digits(Fld, Fmt, Need, Strict) ->
extract_sequence(Fld+1, Fmt, Need, Strict).
extract_modifiers([C|Fmt], Modifiers0) ->
case is_modifier(C) of
true ->
extract_modifiers([C|Fmt], Modifiers0, Need0, Strict) ->
case is_modifier(C, Need0) of
{true, Need1} when Strict ->
case ordsets:add_element(C, Modifiers0) of
Modifiers0 ->
{error, "repeated modifier " ++ [C]};
Modifiers ->
extract_modifiers(Fmt, Modifiers)
extract_modifiers(Fmt, Modifiers, Need1, Strict)
end;
{true, Need1} ->
extract_modifiers(Fmt, ordsets:add_element(C, Modifiers0), Need1, Strict);
false ->
{[C|Fmt], Modifiers0}
{[C|Fmt], Modifiers0, Need0}
end;
extract_modifiers([], Modifiers) ->
{[], Modifiers}.
extract_modifiers([], Modifiers, Need, _Strict) ->
{[], Modifiers, Need}.
check_modifiers(C, Modifiers) ->
maybe
Expand All @@ -4760,11 +4762,11 @@ check_modifiers_1(M, Modifiers, C, Cs) ->
{error, "conflicting modifiers ~" ++ M ++ [C]}
end.
is_modifier($k) -> true;
is_modifier($K) -> true;
is_modifier($l) -> true;
is_modifier($t) -> true;
is_modifier(_) -> false.
is_modifier($k, Need) -> {true, Need};
is_modifier($K, Need) -> {true, ['fun'|Need]};
is_modifier($l, Need) -> {true, Need};
is_modifier($t, Need) -> {true, Need};
is_modifier(_, _) -> false.
control_type($~, Need) -> Need;
control_type($c, Need) -> [int|Need];
Expand Down
9 changes: 7 additions & 2 deletions lib/stdlib/src/erl_stdlib_errors.erl
Original file line number Diff line number Diff line change
Expand Up @@ -540,7 +540,7 @@ check_io_format([Fmt, Args], Cause) ->
_ when not is_list(Args) ->
[[],must_be_list(Args)];
true ->
case erl_lint:check_format_string(Fmt) of
case erl_lint:check_format_string(Fmt, false) of
{error,S} ->
[io_lib:format("format string invalid (~ts)",[S])];
{ok,ArgTypes} when length(ArgTypes) =/= length(Args) ->
Expand Down Expand Up @@ -587,6 +587,11 @@ check_io_arguments([], [], _No) ->
[];
check_io_arguments([Type|TypeT], [Arg|ArgT], No) ->
case Type of
'fun' when Arg =:= undefined; Arg =:= ordered; Arg =:= reversed; is_function(Arg, 2) ->
check_io_arguments(TypeT, ArgT, No+1);
'fun' ->
[io_lib:format("element ~B must be 'undefined', 'ordered', 'reversed', or a fun that takes two arguments", [No]) |
check_io_arguments(TypeT, ArgT, No+1)];
float when is_float(Arg) ->
check_io_arguments(TypeT, ArgT, No+1);
int when is_integer(Arg) ->
Expand Down Expand Up @@ -1157,7 +1162,7 @@ expand_error(not_integer) ->
expand_error(not_list) ->
<<"not a list">>;
expand_error(not_map_iterator_order) ->
<<"not 'undefined', 'ordered', or a fun that takes two arguments">>;
<<"not 'undefined', 'ordered', 'reversed', or a fun that takes two arguments">>;
expand_error(not_map_or_iterator) ->
<<"not a map or an iterator">>;
expand_error(not_number) ->
Expand Down
2 changes: 1 addition & 1 deletion lib/stdlib/test/erl_lint_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -3819,7 +3819,7 @@ otp_8051(Config) when is_list(Config) ->

%% Check that format warnings are generated.
format_warn(Config) when is_list(Config) ->
L1 = 16,
L1 = 23,
L2 = 5,
format_level(1, L1, Config),
format_level(2, L1+L2, Config),
Expand Down
8 changes: 8 additions & 0 deletions lib/stdlib/test/erl_lint_SUITE_data/format.erl
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,14 @@ f(F) ->
io:format("~14p", [F]),
io:format("~*p", [a, F]), %no type checking
io:format("~*p", [14, F]),
io:format("~tlp", [F]), %1
io:format("~kKp", [undefined, F]), %1
io:format("~tb", [1]), %1
io:format("~lb", [1]), %1
io:format("~kb", [1]), %1
io:format("~Kb", [undefined, 1]), %1
io:format("~llp", [F]), %1
io:fwrite("~p", []), %1
io_lib:format("~p", []), %1
Expand Down
10 changes: 9 additions & 1 deletion lib/stdlib/test/io_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -3135,7 +3135,15 @@ error_info(Config) ->
{Format,["~s",["Спутник-1"]],[{1,"failed to format string"}]},
{Format,["~s",[1]],[{2,"1 must be of type string"}]},
{Format,["~s~s",[a,1]],[{2,"2 must be of type string"}]},
{Format,["~s",[[a]]],[{2,"1 must be of type string"}]}] || Format <- [format,fwrite]]
{Format,["~s",[[a]]],[{2,"1 must be of type string"}]},

%% Ensure error messages contain the correct reason (GH-8568)
{Format, ["~ltkKltkKp", []], [{1,"wrong number of arguments"}]},
{Format, ["~ltkKltkKm", [undefined, ordered, a]], [{1,"format string"}]},
{Format, ["~ltkKltkKb", [undefined, ordered, a]], [{2,"3 must be of type integer"}]},
{Format, ["~ltkKp", [foo, #{a => b}]], [{2,"1 must be 'undefined', 'ordered', 'reversed', or a fun that takes two arguments"}]}
]
|| Format <- [format,fwrite]]

],

Expand Down

0 comments on commit 4c6a99f

Please sign in to comment.