Skip to content

Commit

Permalink
Add tests for rich compiler format
Browse files Browse the repository at this point in the history
  • Loading branch information
ferd committed May 23, 2023
1 parent 415a2ab commit bb664f5
Showing 1 changed file with 94 additions and 0 deletions.
94 changes: 94 additions & 0 deletions apps/rebar/test/rebar_compiler_format_SUITE.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,94 @@
-module(rebar_compiler_format_SUITE).
-compile([export_all, nowarn_export_all]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").

-define(EOL, lists:flatten(io_lib:format("~n",[]))).

all() ->
[minimal, nocolor].

init_per_testcase(minimal, Config) ->
Conf = dict:from_list([{compiler_error_format, minimal}]),
[{conf, Conf} | init_per_testcase(regular, Config)];
init_per_testcase(_, Config) ->
OriginalTerm = os:getenv("TERM"),
os:putenv("TERM", "dumb"), % disable color
application:set_env(cf, colour_term, cf_term:has_color("dumb")),
FileName = filename:join(?config(priv_dir, Config), "oracle.erl"),
ok = file:write_file(FileName, oracle()),
Conf = dict:from_list([{compiler_error_format, rich}]),
[{conf, Conf}, {file, FileName}, {term, OriginalTerm} | Config].

end_per_testcase(_, Config) ->
case ?config(term, Config) of
false ->
os:unsetenv("TERM"),
application:unset_env(cf, colour_term);
Original ->
os:putenv("TERM", Original),
application:set_env(cf, colour_term, cf_term:has_color("Original"))
end,
Config.

oracle() ->
"-module(noline_end);\n"
++ lists:duplicate(9, $\n) ++
"first character on line 11.\n"
++ lists:duplicate(99, $\n) ++
"case X of ^whatever % on line 111\n".

minimal() ->
[{doc, "showing minimal (default) output"}].
minimal(Config) ->
Path = ?config(file, Config),
Conf = ?config(conf, Config),
?assertEqual(Path++":1:20: => unexpected token: ;"++?EOL,
rebar_compiler_format:format(Path, {1,20}, "=> ", "unexpected token: ;", Conf)),
?assertEqual(Path++":11:1: some message"++?EOL,
rebar_compiler_format:format(Path, {11,1}, "", "some message", Conf)),
?assertEqual(Path++":111:11: the character '^' is not expected here."++?EOL,
rebar_compiler_format:format(Path, {111,11}, "", "the character '^' is not expected here.", Conf)),
?assertEqual(Path++":-23:-42: invalid ranges."++?EOL,
rebar_compiler_format:format(Path, {-23,-42}, "", "invalid ranges.", Conf)),
?assertEqual(Path++":-23:-42: invalid ranges."++?EOL,
rebar_compiler_format:format(Path, {-23,-42}, "", "invalid ranges.", Conf)),
?assertEqual(Path++":855:1: invalid ranges."++?EOL,
rebar_compiler_format:format(Path, {855,1}, "", "invalid ranges.", Conf)),
?assertEqual("/very/fake/path.oof:1:1: unknown file."++?EOL,
rebar_compiler_format:format("/very/fake/path.oof", {1,1}, "", "unknown file.", Conf)),
ok.


nocolor() ->
[{doc, "testing all sorts of planned output"}].
nocolor(Config) ->
Path = ?config(file, Config),
Conf = ?config(conf, Config),
?assertEqual(" ┌─ "++Path++":"++?EOL++
" |"++?EOL++
" 1 | -module(noline_end);"++?EOL++
" | ^-- => unexpected token: ;"++?EOL++?EOL,
rebar_compiler_format:format(Path, {1,20}, "=> ", "unexpected token: ;", Conf)),
?assertEqual(" ┌─ "++Path++":"++?EOL++
" |"++?EOL++
" 11 | first character on line 11."++?EOL++
" | ^-- some message"++?EOL++?EOL,
rebar_compiler_format:format(Path, {11,1}, "", "some message", Conf)),
?assertEqual(" ┌─ "++Path++":"++?EOL++
" |"++?EOL++
" 111 | case X of ^whatever % on line 111"++?EOL++
" | ^-- the character '^' is not expected here."++?EOL++?EOL,
rebar_compiler_format:format(Path, {111,11}, "", "the character '^' is not expected here.", Conf)),
%% invalid cases fall back to minimal mode
?assertEqual(Path++":-23:-42: invalid ranges."++?EOL,
rebar_compiler_format:format(Path, {-23,-42}, "", "invalid ranges.", Conf)),
?assertEqual(Path++":-23:-42: invalid ranges."++?EOL,
rebar_compiler_format:format(Path, {-23,-42}, "", "invalid ranges.", Conf)),
?assertEqual(Path++":855:1: invalid ranges."++?EOL,
rebar_compiler_format:format(Path, {855,1}, "", "invalid ranges.", Conf)),
?assertEqual("/very/fake/path.oof:1:1: unknown file."++?EOL,
rebar_compiler_format:format("/very/fake/path.oof", {1,1}, "", "unknown file.", Conf)),
ok.

0 comments on commit bb664f5

Please sign in to comment.