File 0247-parsetools-Remove-line-from-test-suites.patch of Package erlang
From 8ed8c671d31bf2d90ec9a5a6d98ec5b98ca76b61 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 24 Nov 2020 07:48:41 +0100
Subject: [PATCH 1/3] parsetools: Remove ?line from test suites
---
lib/parsetools/test/leex_SUITE.erl | 182 +++++++-------
lib/parsetools/test/yecc_SUITE.erl | 387 ++++++++++++++---------------
2 files changed, 283 insertions(+), 286 deletions(-)
diff --git a/lib/parsetools/test/leex_SUITE.erl b/lib/parsetools/test/leex_SUITE.erl
index ad8fb11beb..16f67f7f26 100644
--- a/lib/parsetools/test/leex_SUITE.erl
+++ b/lib/parsetools/test/leex_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2019. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2020. 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.
@@ -25,7 +25,6 @@
-include_lib("kernel/include/file.hrl").
-ifdef(debug).
--define(line, put(line, ?LINE), ).
-define(config(X,Y), foo).
-define(datadir, "leex_SUITE_data").
-define(privdir, "leex_SUITE_priv").
@@ -51,7 +50,7 @@
-define(default_timeout, ?t:minutes(1)).
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?default_timeout),
+ Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
end_per_testcase(_Case, Config) ->
@@ -90,31 +89,31 @@ file(suite) -> [];
file(Config) when is_list(Config) ->
Dir = ?privdir,
Ret = [return, {report, false}],
- ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
leex:file("not_a_file", Ret),
- ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
leex:file("not_a_file", [{return,true}]),
- ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
leex:file("not_a_file", [{report,false},return_errors]),
- ?line error = leex:file("not_a_file"),
- ?line error = leex:file("not_a_file", [{return,false},report]),
- ?line error = leex:file("not_a_file", [return_warnings,{report,false}]),
+ error = leex:file("not_a_file"),
+ error = leex:file("not_a_file", [{return,false},report]),
+ error = leex:file("not_a_file", [return_warnings,{report,false}]),
Filename = filename:join(Dir, "file.xrl"),
file:delete(Filename),
- ?line {'EXIT', {badarg, _}} = (catch leex:file({foo})),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} = (catch leex:file({foo})),
+ {'EXIT', {badarg, _}} =
(catch leex:file(Filename, {parserfile,{foo}})),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch leex:file(Filename, {includefile,{foo}})),
- ?line {'EXIT', {badarg, _}} = (catch leex:file(Filename, no_option)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} = (catch leex:file(Filename, no_option)),
+ {'EXIT', {badarg, _}} =
(catch leex:file(Filename, [return | report])),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch leex:file(Filename, {return,foo})),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch leex:file(Filename, includefile)),
Mini = <<"Definitions.\n"
@@ -122,14 +121,14 @@ file(Config) when is_list(Config) ->
"Rules.\n"
"{L}+ : {token,{word,TokenLine,TokenChars}}.\n"
"Erlang code.\n">>,
- ?line ok = file:write_file(Filename, Mini),
- ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
+ ok = file:write_file(Filename, Mini),
+ {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
leex:file(Filename, [{includefile,"/ /"} | Ret]),
LeexPre = filename:join(Dir, "leexinc.hrl"),
- ?line ok = file:write_file(LeexPre, <<"syntax error.\n">>),
+ ok = file:write_file(LeexPre, <<"syntax error.\n">>),
PreErrors = run_test(Config, Mini, LeexPre),
- ?line {errors,
+ {errors,
[{1,_,["syntax error before: ","error"]},
{3,_,undefined_module}],
[]} =
@@ -138,19 +137,19 @@ file(Config) when is_list(Config) ->
Ret2 = [return, report_errors, report_warnings, verbose],
Scannerfile = filename:join(Dir, "file.erl"),
- ?line ok = file:write_file(Scannerfile, <<"nothing">>),
- ?line unwritable(Scannerfile),
- ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
+ ok = file:write_file(Scannerfile, <<"nothing">>),
+ unwritable(Scannerfile),
+ {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
leex:file(Filename, Ret2),
- ?line writable(Scannerfile),
+ writable(Scannerfile),
file:delete(Scannerfile),
Dotfile = filename:join(Dir, "file.dot"),
- ?line ok = file:write_file(Dotfile, <<"nothing">>),
- ?line unwritable(Dotfile),
- ?line {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
+ ok = file:write_file(Dotfile, <<"nothing">>),
+ unwritable(Dotfile),
+ {error,[{_,[{none,leex,{file_error,_}}]}],[]} =
leex:file(Filename, [dfa_graph | Ret2]),
- ?line writable(Dotfile),
+ writable(Dotfile),
file:delete(Dotfile),
ok = file:delete(Scannerfile),
@@ -186,8 +185,8 @@ compile(Config) when is_list(Config) ->
"Rules.\n"
"{L}+ : {token,{word,TokenLine,TokenChars}}.\n"
"Erlang code.\n">>,
- ?line ok = file:write_file(Filename, Mini),
- ?line ok = leex:compile(Filename, Scannerfile, #options{}),
+ ok = file:write_file(Filename, Mini),
+ ok = leex:compile(Filename, Scannerfile, #options{}),
file:delete(Scannerfile),
file:delete(Filename),
ok.
@@ -199,94 +198,94 @@ syntax(Config) when is_list(Config) ->
Dir = ?privdir,
Filename = filename:join(Dir, "file.xrl"),
Ret = [return, {report, true}],
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"%% comment\n"
"Rules.\n"
"{L}+ : {token,{word,TokenLine,TokenChars}}.\n
">>),
- ?line {error,[{_,[{7,leex,missing_code}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{7,leex,missing_code}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+ : \n">>),
- ?line {error,[{_,[{5,leex,missing_code}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{5,leex,missing_code}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"[] :">>),
- ?line {error,[{_,[{4,leex,{regexp,_}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,_}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+ : .\n"
"[] : ">>),
- ?line {error,[{_,[{5,leex,{regexp,_}}]}],[]} =
+ {error,[{_,[{5,leex,{regexp,_}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"[] : .\n">>),
- ?line {error,[{_,[{4,leex,{regexp,_}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,_}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+ ">>),
- ?line {error,[{_,[{5,leex,bad_rule}]}],[]} =
+ {error,[{_,[{5,leex,bad_rule}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+ ; ">>),
- ?line {error,[{_,[{4,leex,bad_rule}]}],[]} =
+ {error,[{_,[{4,leex,bad_rule}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"[] : '99\n">>),
- ?line {error,[{_,[{4,erl_scan,_}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{4,erl_scan,_}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n">>),
- ?line {error,[{_,[{3,leex,empty_rules}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{3,leex,empty_rules}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"Erlang code.\n">>),
- ?line {error,[{_,[{4,leex,empty_rules}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{4,leex,empty_rules}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n">>),
- ?line {error,[{_,[{2,leex,missing_rules}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{2,leex,missing_rules}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Erlang code.\n">>),
- ?line {error,[{_,[{3,leex,missing_rules}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{3,leex,missing_rules}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"">>),
%% This is a weird line:
- ?line {error,[{_,[{0,leex,missing_defs}]}],[]} = leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ {error,[{_,[{0,leex,missing_defs}]}],[]} = leex:file(Filename, Ret),
+ ok = file:write_file(Filename,
<<"Rules.\n">>),
- ?line {error,[{_,[{1,leex,missing_defs}]}],[]} = leex:file(Filename, Ret),
+ {error,[{_,[{1,leex,missing_defs}]}],[]} = leex:file(Filename, Ret),
%% Check that correct line number is used in messages.
ErlFile = filename:join(Dir, "file.erl"),
Ret1 = [{scannerfile,ErlFile}|Ret],
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
@@ -295,74 +294,74 @@ syntax(Config) when is_list(Config) ->
" DDDD}}.\n" % unbound
"Erlang code.\n"
"an error.\n">>), % syntax error
- ?line {ok, _, []} = leex:file(Filename, Ret1),
- ?line {error,
+ {ok, _, []} = leex:file(Filename, Ret1),
+ {error,
[{_,[{8,_,["syntax error before: ","error"]}]},
{_,[{6,_,{unbound_var,'DDDD'}}]}],
[]} =
compile:file(ErlFile, [basic_validation, return]),
%% Ignored characters
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions. D = [0-9]\n"
"Rules. [a-z] : .\n"
"1 : skip_token.\n"
"Erlang code. f() -> a.\n">>),
- ?line {ok,_,[{_,
+ {ok,_,[{_,
[{1,leex,ignored_characters},
{2,leex,ignored_characters},
{4,leex,ignored_characters}]}]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+\\ : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,{unterminated,"\\"}}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,{unterminated,"\\"}}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+\\x : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,{illegal_char,"\\x"}}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,{illegal_char,"\\x"}}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"{L}+\\x{ : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,{unterminated,"\\x{"}}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,{unterminated,"\\x{"}}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"[^ab : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,{unterminated,"["}}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,{unterminated,"["}}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"(a : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,{unterminated,"("}}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,{unterminated,"("}}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"[b-a] : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,{char_class,"b-a"}}}]}],[]} =
+ {error,[{_,[{4,leex,{regexp,{char_class,"b-a"}}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"D = [0-9]\n"
"Rules.\n"
"\\x{333333333333333333333333} : token.\n">>),
- ?line {error,[{_,[{4,leex,{regexp,
+ {error,[{_,[{4,leex,{regexp,
{illegal_char,
"\\x{333333333333333333333333}"}}}]}],[]} =
leex:file(Filename, Ret),
@@ -394,7 +393,7 @@ pt(Config) when is_list(Config) ->
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
unicode(suite) ->
@@ -412,7 +411,7 @@ unicode(Config) when is_list(Config) ->
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
man(doc) ->
@@ -456,7 +455,7 @@ man(Config) when is_list(Config) ->
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
ex(doc) ->
@@ -576,7 +575,7 @@ ex(Config) when is_list(Config) ->
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
ex2(doc) ->
@@ -736,10 +735,10 @@ escape_char(C) -> C.
">>,
Dir = ?privdir,
XrlFile = filename:join(Dir, "erlang_scan.xrl"),
- ?line ok = file:write_file(XrlFile, Xrl),
+ ok = file:write_file(XrlFile, Xrl),
ErlFile = filename:join(Dir, "erlang_scan.erl"),
- ?line {ok, _} = leex:file(XrlFile, []),
- ?line {ok, _} = compile:file(ErlFile, [{outdir,Dir}]),
+ {ok, _} = leex:file(XrlFile, []),
+ {ok, _} = compile:file(ErlFile, [{outdir,Dir}]),
code:purge(erlang_scan),
AbsFile = filename:rootname(ErlFile, ".erl"),
code:load_abs(AbsFile, erlang_scan),
@@ -882,7 +881,7 @@ Erlang code.
">>,
Dir = ?privdir,
XrlFile = filename:join(Dir, "test_line_wrap.xrl"),
- ?line ok = file:write_file(XrlFile, Xrl),
+ ok = file:write_file(XrlFile, Xrl),
ErlFile = filename:join(Dir, "test_line_wrap.erl"),
{ok, _} = leex:file(XrlFile, []),
{ok, _} = compile:file(ErlFile, [{outdir,Dir}]),
@@ -917,19 +916,19 @@ not_yet(Config) when is_list(Config) ->
Dir = ?privdir,
Filename = filename:join(Dir, "file.xrl"),
Ret = [return, {report, true}],
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"Rules.\n"
"$ : .\n"
"Erlang code.\n">>),
- ?line {error,[{_,[{3,leex,{regexp,_}}]}],[]} =
+ {error,[{_,[{3,leex,{regexp,_}}]}],[]} =
leex:file(Filename, Ret),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Definitions.\n"
"Rules.\n"
"^ : .\n"
"Erlang code.\n">>),
- ?line {error,[{_,[{3,leex,{regexp,_}}]}],[]} =
+ {error,[{_,[{3,leex,{regexp,_}}]}],[]} =
leex:file(Filename, Ret),
ok.
@@ -988,7 +987,7 @@ otp_10302(Config) when is_list(Config) ->
"{L}+ : {token,{word,TokenLine,TokenChars}}.\n"
"Erlang code.\n">>,
LeexPre = filename:join(Dir, "leexinc.hrl"),
- ?line ok = file:write_file(LeexPre, <<"%% coding: UTF-8\n ä">>),
+ ok = file:write_file(LeexPre, <<"%% coding: UTF-8\n ä">>),
PreErrors = run_test(Config, Mini, LeexPre),
{error,[{IncludeFile,[{2,leex,cannot_parse}]}],[]} = PreErrors,
"leexinc.hrl" = filename:basename(IncludeFile),
@@ -1123,12 +1122,11 @@ otp_13916(Config) when is_list(Config) ->
" ok.\n">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
otp_14285(Config) ->
Dir = ?privdir,
- Filename = filename:join(Dir, "file.xrl"),
Ts = [{otp_14285_1,
<<"%% encoding: latin-1\n"
diff --git a/lib/parsetools/test/yecc_SUITE.erl b/lib/parsetools/test/yecc_SUITE.erl
index 715e50c301..c9df46f407 100644
--- a/lib/parsetools/test/yecc_SUITE.erl
+++ b/lib/parsetools/test/yecc_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2005-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2005-2020. 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.
@@ -24,7 +24,6 @@
-include_lib("stdlib/include/erl_compile.hrl").
-ifdef(debug).
--define(line, put(line, ?LINE), ).
-define(config(X,Y), foo).
-define(datadir, "yecc_SUITE_data").
-define(privdir, "yecc_SUITE_priv").
@@ -56,7 +55,7 @@
-define(default_timeout, ?t:minutes(1)).
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?default_timeout),
+ Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
end_per_testcase(_Case, Config) ->
@@ -98,7 +97,7 @@ app_test(doc) ->
app_test(suite) ->
[];
app_test(Config) when is_list(Config) ->
- ?line ok=?t:app_test(parsetools),
+ ok=?t:app_test(parsetools),
ok.
@@ -108,51 +107,51 @@ file(suite) -> [];
file(Config) when is_list(Config) ->
Dir = ?privdir,
Ret = [return, {report, false}],
- ?line {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
yecc:file("not_a_file", Ret),
- ?line {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
yecc:file("not_a_file", [{return,true}]),
- ?line {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
yecc:file("not_a_file", [{report,false},return_errors]),
- ?line error = yecc:file("not_a_file"),
- ?line error = yecc:file("not_a_file", [{return,false},report]),
- ?line error = yecc:file("not_a_file", [return_warnings,{report,false}]),
+ error = yecc:file("not_a_file"),
+ error = yecc:file("not_a_file", [{return,false},report]),
+ error = yecc:file("not_a_file", [return_warnings,{report,false}]),
Filename = filename:join(Dir, "file.yrl"),
file:delete(Filename),
- ?line {'EXIT', {badarg, _}} = (catch yecc:file({foo})),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} = (catch yecc:file({foo})),
+ {'EXIT', {badarg, _}} =
(catch yecc:file(Filename, {parserfile,{foo}})),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch yecc:file(Filename, {includefile,{foo}})),
- ?line {'EXIT', {badarg, _}} = (catch yecc:file(Filename, no_option)),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} = (catch yecc:file(Filename, no_option)),
+ {'EXIT', {badarg, _}} =
(catch yecc:file(Filename, [return | report])),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch yecc:file(Filename, {return,foo})),
- ?line {'EXIT', {badarg, _}} =
+ {'EXIT', {badarg, _}} =
(catch yecc:file(Filename, includefile)),
Mini = <<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
nt -> t.">>,
- ?line ok = file:write_file(Filename, Mini),
- ?line {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
+ ok = file:write_file(Filename, Mini),
+ {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
yecc:file(Filename, [{parserfile,"//"} | Ret]),
- ?line {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
yecc:file(Filename, [{includefile,"//"} | Ret]),
- ?line {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
+ {error,[{_,[{none,yecc,{file_error,_}}]}],[]} =
yecc:file(Filename, [{includefile,"/ /"} | Ret]),
YeccPre = filename:join(Dir, "yeccpre.hrl"),
- ?line ok = file:write_file(YeccPre, <<"syntax error. ">>),
+ ok = file:write_file(YeccPre, <<"syntax error. ">>),
PreErrors1 = run_test(Config, Mini, YeccPre),
- ?line {errors,[_],[]} = extract(YeccPre, PreErrors1),
- ?line ok = file:write_file(YeccPre, my_yeccpre()),
- ?line {'EXIT', {undef,_}} = (catch run_test(Config, Mini, YeccPre)),
+ {errors,[_],[]} = extract(YeccPre, PreErrors1),
+ ok = file:write_file(YeccPre, my_yeccpre()),
+ {'EXIT', {undef,_}} = (catch run_test(Config, Mini, YeccPre)),
MiniCode = <<"
Nonterminals nt.
@@ -161,7 +160,7 @@ file(Config) when is_list(Config) ->
nt -> t.
Erlang code.
">>,
- ?line {'EXIT', {undef,_}} = (catch run_test(Config, MiniCode, YeccPre)),
+ {'EXIT', {undef,_}} = (catch run_test(Config, MiniCode, YeccPre)),
file:delete(YeccPre),
file:delete(Filename),
@@ -179,76 +178,76 @@ syntax(Config) when is_list(Config) ->
Parserfile = filename:join(Dir, "file.erl"),
Parserfile1 = filename:join(Dir, "a file"),
- ?line ok = file:write_file(Filename, <<"">>),
- ?line {error,[{_,[{none,yecc,no_grammar_rules},
+ ok = file:write_file(Filename, <<"">>),
+ {error,[{_,[{none,yecc,no_grammar_rules},
{none,yecc,nonterminals_missing},
{none,yecc,rootsymbol_missing},
{none,yecc,terminals_missing}]}],[]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"Nonterminals">>),
- ?line {error,[{_,[{_,yecc,{error,yeccparser,_}}]}],[]} =
+ ok = file:write_file(Filename, <<"Nonterminals">>),
+ {error,[{_,[{_,yecc,{error,yeccparser,_}}]}],[]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"Nonterminals nt.">>),
- ?line {error,[{_,[{none,yecc,no_grammar_rules},
+ ok = file:write_file(Filename, <<"Nonterminals nt.">>),
+ {error,[{_,[{none,yecc,no_grammar_rules},
{none,yecc,rootsymbol_missing},
{none,yecc,terminals_missing}]}],[]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"Nonterminals nt. Terminals t.">>),
- ?line {error,[{_,[{none,yecc,no_grammar_rules},
+ ok = file:write_file(Filename, <<"Nonterminals nt. Terminals t.">>),
+ {error,[{_,[{none,yecc,no_grammar_rules},
{none,yecc,rootsymbol_missing}]}],[]} =
yecc:file(Filename, Ret),
%% Nonterminals and terminals not disjoint.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt 't t'. Terminals t 't t'. Rootsymbol nt.">>),
- ?line {error,[{_,[{1,yecc,{symbol_terminal_and_nonterminal,'t t'}},
+ {error,[{_,[{1,yecc,{symbol_terminal_and_nonterminal,'t t'}},
{none,yecc,no_grammar_rules}]}],
[]} = yecc:file(Filename, Ret),
%% Rootsymbol is not a nonterminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t.
Rootsymbol t. nt -> t.">>),
- ?line {error,[{_,[{2,yecc,{bad_rootsymbol,t}}]}],[]} =
+ {error,[{_,[{2,yecc,{bad_rootsymbol,t}}]}],[]} =
yecc:file(Filename, Ret),
%% Rootsymbol is not a nonterminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t.
Rootsymbol t. nt -> t.">>),
- ?line {error,[{_,[{2,yecc,{bad_rootsymbol,t}}]}],[]} =
+ {error,[{_,[{2,yecc,{bad_rootsymbol,t}}]}],[]} =
yecc:file(Filename, Ret),
%% Endsymbol is a nonterminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt.
Endsymbol nt.
nt -> t.">>),
- ?line {error,[{_,[{2,yecc,{endsymbol_is_nonterminal,nt}}]}],[]} =
+ {error,[{_,[{2,yecc,{endsymbol_is_nonterminal,nt}}]}],[]} =
yecc:file(Filename, Ret),
%% Endsymbol is a terminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt.
Endsymbol t.
nt -> t.">>),
- ?line {error,[{_,[{2,yecc,{endsymbol_is_terminal,t}}]}],[]} =
+ {error,[{_,[{2,yecc,{endsymbol_is_terminal,t}}]}],[]} =
yecc:file(Filename, Ret),
%% No grammar rules.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt. Endsymbol e.">>),
- ?line {error,[{_,[{none,yecc,no_grammar_rules}]}],[]} =
+ {error,[{_,[{none,yecc,no_grammar_rules}]}],[]} =
yecc:file(Filename, Ret),
%% Bad declaration.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt. Endsymbol e.
nt -> t. e e.">>),
- ?line {ok,_,[{_,[{2,yecc,bad_declaration}]}]} =
+ {ok,_,[{_,[{2,yecc,bad_declaration}]}]} =
yecc:file(Filename, Ret),
%% Bad declaration with warnings_as_errors.
@@ -265,29 +264,29 @@ syntax(Config) when is_list(Config) ->
true = filelib:is_regular(Parserfile),
%% Bad declaration.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t.
Rootsymbol nt nt. Rootsymbol nt. Endsymbol e.
nt -> t.">>),
- ?line {ok,_,[{_,[{2,yecc,bad_declaration}]}]} =
+ {ok,_,[{_,[{2,yecc,bad_declaration}]}]} =
yecc:file(Filename, Ret),
%% Syntax error found by yeccparser.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt. Endsymbol e.
a - a.">>),
- ?line {error,[{_,[{2,yecc,{error,_yeccparser,_}}]}],[]} =
+ {error,[{_,[{2,yecc,{error,_yeccparser,_}}]}],[]} =
yecc:file(Filename, Ret),
%% Syntax error: unknown nonterminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt. Endsymbol e.
'unknown ' -> t.">>),
- ?line {error,[{_,[{2,yecc,{undefined_nonterminal,'unknown '}}]}],[]} =
+ {error,[{_,[{2,yecc,{undefined_nonterminal,'unknown '}}]}],[]} =
yecc:file(Filename, Ret),
%% Undefined rhs symbols. Note quotes in output.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals Nonterminals nt.
Terminals t Terminals.
Rootsymbol nt.
@@ -295,7 +294,7 @@ syntax(Config) when is_list(Config) ->
nt -> Nonterminals.
Nonterminals -> Terminals receive foo 45
'17' 'a b'.">>),
- ?line {error,[{_,[{6,yecc,{undefined_symbol,45}},
+ {error,[{_,[{6,yecc,{undefined_symbol,45}},
{6,yecc,{undefined_symbol,foo}},
{6,yecc,{undefined_symbol,'receive'}},
{7,yecc,{undefined_symbol,'17'}},
@@ -303,68 +302,68 @@ syntax(Config) when is_list(Config) ->
yecc:file(Filename, Ret),
%% '$empty' used early, before Terminals. OK.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
nt -> '$empty'.
Terminals t.
Rootsymbol nt.
Endsymbol e.">>),
- ?line {ok,_,[{_,[{3,yecc,{unused_terminal,t}}]}]} =
+ {ok,_,[{_,[{3,yecc,{unused_terminal,t}}]}]} =
yecc:file(Filename, Ret),
%% Illegal use of '$empty'.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt nt2.
Terminals t.
Rootsymbol nt.
Endsymbol e.
nt -> t.
nt2 -> t '$empty'.">>),
- ?line {error,[{_,[{6,yecc,illegal_empty}]}],[]} =
+ {error,[{_,[{6,yecc,illegal_empty}]}],[]} =
yecc:file(Filename, Ret),
ParserFile3 = [{parserfile, Parserfile1}],
%% Bad Erlang expression in action. Changed in OTP-7224.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
Endsymbol e.
nt -> t : a bad code.">>),
- ?line {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
+ {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
SzYeccPre = yeccpre_size(),
%% Note: checking the line numbers. Changes when yeccpre.hrl changes.
fun() ->
- ?line {error,[{_,[{5,_,["syntax error before: ","bad"]}]},
+ {error,[{_,[{5,_,["syntax error before: ","bad"]}]},
{_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
{L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
[]} = compile:file(Parserfile1, [basic_validation,return]),
- ?line L1 = 31 + SzYeccPre,
- ?line L2 = 39 + SzYeccPre
+ L1 = 31 + SzYeccPre,
+ L2 = 39 + SzYeccPre
end(),
%% Bad macro in action. OTP-7224.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
Endsymbol e.
nt -> t : ?F(3).">>),
- ?line {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
+ {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
%% Note: checking the line numbers. Changes when yeccpre.hrl changes.
fun() ->
- ?line {error,[{_,[{5,_,{undefined,'F',1}}]},
+ {error,[{_,[{5,_,{undefined,'F',1}}]},
{_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
{L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
[]} = compile:file(Parserfile1, [basic_validation,return]),
- ?line L1 = 31 + SzYeccPre,
- ?line L2 = 39 + SzYeccPre
+ L1 = 31 + SzYeccPre,
+ L2 = 39 + SzYeccPre
end(),
%% Check line numbers. OTP-7224.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Terminals t.
Nonterminals nt.
Rootsymbol nt.
@@ -374,24 +373,24 @@ syntax(Config) when is_list(Config) ->
-define(F(X), X).
t() ->
bad().">>),
- ?line {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
- ?line {error,[{_,[{9,_,{undefined_function,{bad,0}}}]}],
+ {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
+ {error,[{_,[{9,_,{undefined_function,{bad,0}}}]}],
[{_,[{8,_,{unused_function,{t,0}}}]}]}
= compile:file(Parserfile1, [basic_validation, return]),
%% Terminals defined before nonterminals. (One of many checks...)
%% Used to give an error message, but now allowed.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Terminals t.
Nonterminals nt.
Rootsymbol nt.
Endsymbol e.
nt -> t.
Erlang code.">>),
- ?line {ok, _, []} = yecc:file(Filename, Ret),
+ {ok, _, []} = yecc:file(Filename, Ret),
%% Precedence with swapped arguments. Bad declaration.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
@@ -399,33 +398,33 @@ syntax(Config) when is_list(Config) ->
nt -> t.
Right t.
Left nt 100.">>),
- ?line {ok,_,[{_,[{6,yecc,bad_declaration},{7,yecc,bad_declaration}]}]} =
+ {ok,_,[{_,[{6,yecc,bad_declaration},{7,yecc,bad_declaration}]}]} =
yecc:file(Filename, Ret),
%% Precedence with unknown operator.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
Endsymbol e.
nt -> t.
Unary 100 '-'.">>),
- ?line {error,[{_,[{6,yecc,{precedence_op_is_unknown,'-'}}]}],[]} =
+ {error,[{_,[{6,yecc,{precedence_op_is_unknown,'-'}}]}],[]} =
yecc:file(Filename, Ret),
%% Precedence with endsymbol operator.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
Endsymbol e.
nt -> t.
Unary 100 e.">>),
- ?line {error,[{_,[{6,yecc,{precedence_op_is_endsymbol,e}}]}],[]} =
+ {error,[{_,[{6,yecc,{precedence_op_is_endsymbol,e}}]}],[]} =
yecc:file(Filename, Ret),
%% Duplicated precedence.
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals nt.
Terminals t '+'.
Rootsymbol nt.
@@ -435,98 +434,98 @@ syntax(Config) when is_list(Config) ->
Left 200 '+'.
Left 200 '+'.
Right 200 t.">>),
- ?line {error,[{_,[{8,yecc,{duplicate_precedence,'+'}},
+ {error,[{_,[{8,yecc,{duplicate_precedence,'+'}},
{9,yecc,{duplicate_precedence,'+'}},
{10,yecc,{duplicate_precedence,t}}]}],
[]} = yecc:file(Filename, Ret),
%% Duplicated nonterminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals 'n t' 'n t'. Terminals t.
Rootsymbol 'n t'. 'n t' -> t.">>),
- ?line {ok, _, [{_,[{1,yecc,{duplicate_nonterminal,'n t'}}]}]} =
+ {ok, _, [{_,[{1,yecc,{duplicate_nonterminal,'n t'}}]}]} =
yecc:file(Filename, Ret),
- ?line {ok, _, [{_,[{1,yecc,{duplicate_nonterminal,'n t'}}]}]} =
+ {ok, _, [{_,[{1,yecc,{duplicate_nonterminal,'n t'}}]}]} =
yecc:file(Filename, [return_warnings, {report, false}]),
- ?line {ok, _} = yecc:file(Filename),
- ?line {ok, _} =
+ {ok, _} = yecc:file(Filename),
+ {ok, _} =
yecc:file(Filename, [{report,false}, {return_warnings,false}]),
%% Duplicated terminal.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals 't t' 't t'.
Rootsymbol nt. nt -> 't t'.">>),
- ?line {ok, _, [{_,[{1,yecc,{duplicate_terminal,'t t'}}]}]} =
+ {ok, _, [{_,[{1,yecc,{duplicate_terminal,'t t'}}]}]} =
yecc:file(Filename, Ret),
%% Two Nonterminals declarations.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t.
Nonterminals nt2.
Rootsymbol nt2. nt -> t. nt2 -> nt.">>),
- ?line {error,[{_,[{2,yecc,{duplicate_declaration,'Nonterminals'}}]}],
+ {error,[{_,[{2,yecc,{duplicate_declaration,'Nonterminals'}}]}],
[]} = yecc:file(Filename, Ret),
%% Three Terminals declarations.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t.
Terminals t1.
Terminals t1.
Rootsymbol nt. nt -> t t1.">>),
- ?line {error,[{_,[{2,yecc,{duplicate_declaration,'Terminals'}},
+ {error,[{_,[{2,yecc,{duplicate_declaration,'Terminals'}},
{3,yecc,{duplicate_declaration,'Terminals'}}]}],
[]} = yecc:file(Filename, Ret),
%% Two root symbols.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol t.
Rootsymbol nt. nt -> t.">>),
- ?line {error,[{_,[{2,yecc,{duplicate_declaration,'Rootsymbol'}}]}],[]} =
+ {error,[{_,[{2,yecc,{duplicate_declaration,'Rootsymbol'}}]}],[]} =
yecc:file(Filename, Ret),
%% Two end symbols.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol t.
Endsymbol e.
Endsymbol e. nt -> t.">>),
- ?line {error,[{_,[{3,yecc,{duplicate_declaration,'Endsymbol'}}]}],[]} =
+ {error,[{_,[{3,yecc,{duplicate_declaration,'Endsymbol'}}]}],[]} =
yecc:file(Filename, Ret),
%% Two end symbols.
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol t.
Expect 1.
Expect 0.
Endsymbol e. nt -> t.">>),
- ?line {error,[{_,[{3,yecc,{duplicate_declaration,'Expect'}}]}],[]} =
+ {error,[{_,[{3,yecc,{duplicate_declaration,'Expect'}}]}],[]} =
yecc:file(Filename, Ret),
%% Some words should not be used.
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Terminals '$empty' '$end'.
Nonterminals '$undefined'.
Rootsymbol '$undefined'.
Endsymbol '$end'.
'$undefined' -> '$empty'.
">>),
- ?line {error,[{_,[{2,yecc,{reserved,'$empty'}},
+ {error,[{_,[{2,yecc,{reserved,'$empty'}},
{2,yecc,{reserved,'$end'}},
{3,yecc,{reserved,'$undefined'}},
{5,yecc,{endsymbol_is_terminal,'$end'}}]}],[]} =
yecc:file(Filename, Ret),
%% Undefined pseudo variable.
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Nonterminals nt.
Terminals t.
Rootsymbol nt.
nt -> t : '$2'.
">>),
- ?line {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$2'}}]}],[]} =
+ {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$2'}}]}],[]} =
yecc:file(Filename, Ret),
%% Space in module name.
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals list.
Terminals element.
Rootsymbol list.
@@ -546,7 +545,7 @@ syntax(Config) when is_list(Config) ->
Parserfile2 = filename:join(Dir, "a \"file\""),
%% The parser (yeccgramm.yrl) allows many symbol names...
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals Nonterminals Rootsymbol ':' '->'.
Terminals Terminals.
Rootsymbol Rootsymbol.
@@ -556,9 +555,9 @@ syntax(Config) when is_list(Config) ->
':' -> '->'.
'->' -> Terminals.
">>),
- ?line {ok, _} = yecc:file(Filename, [{parserfile, Parserfile1}]),
- ?line {ok, _} = yecc:file(Filename, [{parserfile, Parserfile1},time]),
- ?line {ok,[]} = compile:file(Parserfile1, [basic_validation]),
+ {ok, _} = yecc:file(Filename, [{parserfile, Parserfile1}]),
+ {ok, _} = yecc:file(Filename, [{parserfile, Parserfile1},time]),
+ {ok,[]} = compile:file(Parserfile1, [basic_validation]),
Quotes = <<"
Nonterminals
@@ -614,8 +613,8 @@ syntax(Config) when is_list(Config) ->
">>,
- ?line ok = file:write_file(Filename, Quotes),
- ?line {ok,_,[{_,
+ ok = file:write_file(Filename, Quotes),
+ {ok,_,[{_,
[{3,yecc,{unused_nonterminal,42}},
{3,yecc,{unused_nonterminal,' unused '}},
{3,yecc,{unused_nonterminal,'42'}},
@@ -626,32 +625,32 @@ syntax(Config) when is_list(Config) ->
yecc:file(Filename, Ret),
Ts = [{quotes, Quotes, default, ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
%% Non-terminal has no rules, but is unused.
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Nonterminals nt bad.
Terminals t.
Rootsymbol nt.
nt -> t : something.
">>),
- ?line {ok,_,[{_,[{2,yecc,{unused_nonterminal,bad}}]}]} =
+ {ok,_,[{_,[{2,yecc,{unused_nonterminal,bad}}]}]} =
yecc:file(Filename, Ret),
%% Non-terminal has no rules and is used.
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Nonterminals nt bad.
Terminals t.
Rootsymbol nt.
nt -> t bad : something.
">>),
- ?line {error,[{_,[{2,yecc,{missing_syntax_rule,bad}}]}],[]} =
+ {error,[{_,[{2,yecc,{missing_syntax_rule,bad}}]}],[]} =
yecc:file(Filename, Ret),
%% Warning in Erlang code. With and without file attributes.
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Nonterminals nt.
Terminals t.
Rootsymbol nt.
@@ -663,14 +662,14 @@ syntax(Config) when is_list(Config) ->
t(A) ->
b.
">>),
- ?line {ok, _, []} =
+ {ok, _, []} =
yecc:file(Filename, [file_attributes | Ret]),
Opts = [basic_validation, return],
Erlfile = filename:join(Dir, "file.erl"),
- ?line {ok,[],[{_,[{10,_,_}]}]} = compile:file(Erlfile, Opts),
- ?line {ok, _, []} =
+ {ok,[],[{_,[{10,_,_}]}]} = compile:file(Erlfile, Opts),
+ {ok, _, []} =
yecc:file(Filename, [{file_attributes,false} | Ret]),
- ?line {ok,[],[{_,[{4,_,_}]}]} = compile:file(Erlfile, Opts),
+ {ok,[],[{_,[{4,_,_}]}]} = compile:file(Erlfile, Opts),
file:delete(Parserfile1 ++ ".erl"),
file:delete(Parserfile2 ++ ".erl"),
@@ -685,13 +684,13 @@ compile(Config) when is_list(Config) ->
Dir = ?privdir,
Filename = filename:join(Dir, "file.yrl"),
Parserfile = filename:join(Dir, "file.erl"),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt.
Terminals t.
Rootsymbol nt.
nt -> t.">>),
- ?line error = yecc:compile(Filename, "//", #options{}),
- ?line ok = yecc:compile(Filename, Parserfile, #options{}),
+ error = yecc:compile(Filename, "//", #options{}),
+ ok = yecc:compile(Filename, Parserfile, #options{}),
file:delete(Parserfile),
file:delete(Filename),
ok.
@@ -704,14 +703,14 @@ rules(Config) when is_list(Config) ->
Ret = [return, {report, false}],
Filename = filename:join(Dir, "file.yrl"),
- ?line ok = file:write_file(Filename,
+ ok = file:write_file(Filename,
<<"Nonterminals nt. Terminals t. Rootsymbol nt.
nt -> t. nt -> t.">>),
- ?line {error,[{_,[{none,yecc,{conflict,_}}]}],
+ {error,[{_,[{none,yecc,{conflict,_}}]}],
[{_,[{none,yecc,{conflicts,0,1}}]}]} =
yecc:file(Filename, [return, report]),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals A B E.
Terminals c d f x y.
Rootsymbol A.
@@ -721,28 +720,28 @@ rules(Config) when is_list(Config) ->
B -> x y.
E -> x y.
">>),
- ?line {error,[{_,[{none,yecc,{conflict,_}}]}],
+ {error,[{_,[{none,yecc,{conflict,_}}]}],
[{_,[{none,yecc,{conflicts,0,1}}]}]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Terminals t.
Nonterminals nt.
Rootsymbol nt.
nt -> '$empty' : '$1'.
nt -> t.
">>),
- ?line {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$1'}}]}],[]} =
+ {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$1'}}]}],[]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Terminals t.
Nonterminals nt.
Rootsymbol nt.
nt -> '$empty' : '$0'.
nt -> t.
">>),
- ?line {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$0'}}]}],[]} =
+ {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$0'}}]}],[]} =
yecc:file(Filename, Ret),
file:delete(Filename),
@@ -770,7 +769,7 @@ rules(Config) when is_list(Config) ->
">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
@@ -782,7 +781,7 @@ expect(Config) when is_list(Config) ->
Ret = [return, {report, true}],
Filename = filename:join(Dir, "file.yrl"),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals e.
Terminals i t else.
Rootsymbol e.
@@ -791,10 +790,10 @@ expect(Config) when is_list(Config) ->
e -> i e t e.
e -> i e t e else e.
">>),
- ?line {error,[{_,[{5,yecc,{bad_expect,a}}]}],[]} =
+ {error,[{_,[{5,yecc,{bad_expect,a}}]}],[]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals e.
Terminals i t else.
Rootsymbol e.
@@ -803,9 +802,9 @@ expect(Config) when is_list(Config) ->
e -> i e t e.
e -> i e t e else e.
">>),
- ?line {ok, _, []} = yecc:file(Filename, Ret),
+ {ok, _, []} = yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals e.
Terminals i t else.
Rootsymbol e.
@@ -814,10 +813,10 @@ expect(Config) when is_list(Config) ->
e -> i e t e.
e -> i e t e else e.
">>),
- ?line {ok, _, [{_,[{none,yecc,{conflicts,1,0}}]}]} =
+ {ok, _, [{_,[{none,yecc,{conflicts,1,0}}]}]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals e.
Terminals i t else.
Rootsymbol e.
@@ -826,26 +825,26 @@ expect(Config) when is_list(Config) ->
e -> i e t e.
e -> i e t e else e.
">>),
- ?line {error,[{_,[{5,yecc,{error,_yeccparser,_}}]}],[]} =
+ {error,[{_,[{5,yecc,{error,_yeccparser,_}}]}],[]} =
yecc:file(Filename, Ret),
%% States N. An undocumented declaration used for testing.
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals nt.
Terminals t.
Rootsymbol nt.
States 100.
nt -> t.">>),
- ?line {ok,_,[{_, [{none,yecc,{n_states,100,3}}]}]} =
+ {ok,_,[{_, [{none,yecc,{n_states,100,3}}]}]} =
yecc:file(Filename, Ret),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals nt.
Terminals t.
Rootsymbol nt.
States bad.
nt -> t.">>),
- ?line {error,[{_,[{5,yecc,{bad_states,bad}}]}],[]} =
+ {error,[{_,[{5,yecc,{bad_states,bad}}]}],[]} =
yecc:file(Filename, Ret),
file:delete(Filename),
@@ -859,7 +858,7 @@ conflicts(Config) when is_list(Config) ->
Ret = [return, {report, true}],
Filename = filename:join(Dir, "file.yrl"),
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals S List Tuple Elements Element.
Terminals '{' '}' '[' ']' ',' nil e.
Rootsymbol S.
@@ -883,11 +882,11 @@ conflicts(Config) when is_list(Config) ->
Element -> Tuple : '$1'.
Element -> e : '$1'.
">>),
- ?line {error,[{_,_}],[{_,[{none,yecc,{conflicts,1,5}}]}]} =
+ {error,[{_,_}],[{_,[{none,yecc,{conflicts,1,5}}]}]} =
yecc:file(Filename, Ret),
%% Can easily be resolved (but don't do it!).
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals S List Tuple Elements Element.
Terminals '{' '}' '[' ']' ',' nil e.
Rootsymbol S.
@@ -913,7 +912,7 @@ conflicts(Config) when is_list(Config) ->
Element -> Tuple : '$1'.
Element -> e : '$1'.
">>),
- ?line {ok, _, []} =
+ {ok, _, []} =
yecc:file(Filename, Ret),
file:delete(Filename),
@@ -970,7 +969,7 @@ empty(Config) when is_list(Config) ->
">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
prec(doc) ->
@@ -983,7 +982,7 @@ prec(Config) when is_list(Config) ->
%% Don't know what 'Unary' actually means, but this is how it has
%% always worked...
- ?line ok = file:write_file(Filename, <<"
+ ok = file:write_file(Filename, <<"
Nonterminals E.
Terminals '*' '+' '=' integer.
Rootsymbol E.
@@ -997,7 +996,7 @@ prec(Config) when is_list(Config) ->
Left 200 '+'.
Left 400 '*'.
">>),
- ?line {error,[{_,[{none,yecc,{conflict,_}}]}],
+ {error,[{_,[{none,yecc,{conflict,_}}]}],
[{_,[{none,yecc,{conflicts,1,0}}]}]} =
yecc:file(Filename, Ret),
@@ -1145,7 +1144,7 @@ prec(Config) when is_list(Config) ->
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
yeccpre(doc) ->
@@ -1213,7 +1212,7 @@ yeccpre(Config) when is_list(Config) ->
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
lalr(doc) ->
@@ -1269,7 +1268,7 @@ lalr(Config) when is_list(Config) ->
">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
old_yecc(doc) ->
@@ -1283,12 +1282,12 @@ old_yecc(Config) when is_list(Config) ->
Terminals t.
Rootsymbol nt.
nt -> t.">>,
- ?line ok = file:write_file(Filename, Mini),
- ?line {_, _} = yecc:yecc(Filename, Parserfile),
- ?line {_, _} = yecc:yecc(Filename, Parserfile, true),
- ?line {_, _} = yecc:yecc(Filename, Parserfile, true),
+ ok = file:write_file(Filename, Mini),
+ {_, _} = yecc:yecc(Filename, Parserfile),
+ {_, _} = yecc:yecc(Filename, Parserfile, true),
+ {_, _} = yecc:yecc(Filename, Parserfile, true),
TE = process_flag(trap_exit, true),
- ?line {'EXIT', error} =
+ {'EXIT', error} =
(catch yecc:yecc(Filename, Parserfile, false, Parserfile)),
_ = process_flag(trap_exit, TE),
ok.
@@ -1321,7 +1320,7 @@ other_examples(Config) when is_list(Config) ->
">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
@@ -1386,7 +1385,7 @@ otp_5369(Config) when is_list(Config) ->
">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
otp_6362(doc) ->
@@ -1415,7 +1414,7 @@ otp_6362(Config) when is_list(Config) ->
">>,
default,
ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
Dir = ?privdir,
%% Report errors. Very simple test of format_error/1.
@@ -1424,7 +1423,7 @@ otp_6362(Config) when is_list(Config) ->
%% An error introduced due to this ticket. Terminals can be
%% assigned conflicting precedences, which cannot be resolved.
- ?line ok = file:write_file(Filename,<<"
+ ok = file:write_file(Filename,<<"
Nonterminals cmp compare expr fopp.
Terminals string '>' '='.
Rootsymbol compare.
@@ -1443,7 +1442,7 @@ otp_6362(Config) when is_list(Config) ->
fopp -> '>' : '>'.">>),
Ret = [return, {report, true}],
- ?line {error,[{_,[{none,yecc,{conflict,_}}]}],[]} =
+ {error,[{_,[{none,yecc,{conflict,_}}]}],[]} =
yecc:file(Filename, Ret),
file:delete(Filename),
ok.
@@ -1541,9 +1540,9 @@ otp_8483(Config) when is_list(Config) ->
elem -> seq.
seq -> elem.
seq -> seq elem.">>,
- ?line ok = file:write_file(Input, Bug1),
+ ok = file:write_file(Input, Bug1),
Ret = [return, {report, true}],
- ?line {error,[{_,[{none,yecc,{conflict,_}},
+ {error,[{_,[{none,yecc,{conflict,_}},
{none,yecc,{conflict,_}},
{none,yecc,{conflict,_}}]}],
[{_,[{none,yecc,{conflicts,1,3}}]}]} =
@@ -1578,7 +1577,7 @@ otp_8486(Config) when is_list(Config) ->
{'then',1},{'skip',1},{'else',1},{'skip',1}]),
ok.
">>,default,ok}],
- ?line run(Config, Ts),
+ run(Config, Ts),
ok.
otp_7292(doc) ->
@@ -1608,15 +1607,15 @@ otp_7292(Config) when is_list(Config) ->
bar. ">>,
%% Check that correct line number is used in messages.
- ?line ok = file:write_file(Filename, Contents),
+ ok = file:write_file(Filename, Contents),
ParserFile3 = [{parserfile, Parserfile1}],
Ret = [return, {report, true}],
- ?line {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
+ {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Ret),
%% Note: checking the line numbers. Changes when yeccpre.hrl changes.
fun() ->
SzYeccPre = yeccpre_size(),
- ?line {error,
+ {error,
[{_,[{5,_,["syntax error before: ","bad"]}]},
{_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
{L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
@@ -1627,21 +1626,21 @@ otp_7292(Config) when is_list(Config) ->
end(),
YeccPre = filename:join(Dir, "yeccpre.hrl"),
- ?line ok = file:write_file(YeccPre,
+ ok = file:write_file(YeccPre,
[<<"-export([parse/1, parse_and_scan/1, format_error/1]).\n">>,
yeccpre_v1_2()]),
Inc = [{includefile,YeccPre}],
- ?line {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Inc ++ Ret),
+ {ok, _, []} = yecc:file(Filename, ParserFile3 ++ Inc ++ Ret),
fun() ->
SzYeccPre = yeccpre_size(YeccPre),
- ?line {error,
+ {error,
[{_,[{5,_,["syntax error before: ","bad"]}]},
{_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
{L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
[{_,[{16,_,{unused_function,{foo,0}}}]}]} =
compile:file(Parserfile1, [basic_validation, return]),
- ?line L1 = 40 + SzYeccPre,
- ?line L2 = 48 + SzYeccPre
+ L1 = 40 + SzYeccPre,
+ L2 = 48 + SzYeccPre
end(),
file:delete(YeccPre),
@@ -1774,26 +1773,26 @@ otp_7969(doc) ->
"OTP-7969. Interface to the I/O protocol..";
otp_7969(suite) -> [];
otp_7969(Config) when is_list(Config) ->
- ?line {ok,Ts1,_} =
+ {ok,Ts1,_} =
erl_scan:string("'foo\nbar'", {1,1}, [text]),
- ?line {error,{2,_,["syntax error before: ",[]]}} = erl_parse:parse(Ts1),
+ {error,{2,_,["syntax error before: ",[]]}} = erl_parse:parse(Ts1),
- ?line {ok,Ts1_1,_} = erl_scan:string("'foo\nbar'", 1, [text]),
- ?line {error,{2,_,["syntax error before: ",[]]}} = erl_parse:parse(Ts1_1),
+ {ok,Ts1_1,_} = erl_scan:string("'foo\nbar'", 1, [text]),
+ {error,{2,_,["syntax error before: ",[]]}} = erl_parse:parse(Ts1_1),
- ?line {ok,Ts2,_EndLocation} =
+ {ok,Ts2,_EndLocation} =
erl_scan:string("'foo\nbar'", {1,1}, []),
%% Can't do better than report possibly wrong line:
- ?line {error,{1,_,["syntax error before: ",[]]}} = erl_parse:parse(Ts2),
+ {error,{1,_,["syntax error before: ",[]]}} = erl_parse:parse(Ts2),
- ?line {ok, Ts11, _}=R1 = erl_scan:string("f() -> a."),
- ?line F1 = fun() -> {ok,Ts11 ++ [{'$end',2}],2} end,
+ {ok, Ts11, _}=R1 = erl_scan:string("f() -> a."),
+ F1 = fun() -> {ok,Ts11 ++ [{'$end',2}],2} end,
A1 = erl_anno:new(1),
{ok,{function,A1,f,0,[{clause,A1,[],[],[{atom,A1,a}]}]}} =
erl_parse:parse_and_scan({F1, []}),
- ?line F2 = fun() -> erl_scan:string("f() -> ,") end,
- ?line {error,{1,erl_parse,_}} = erl_parse:parse_and_scan({F2, []}),
- ?line F3 = fun() -> case erase(foo) of
+ F2 = fun() -> erl_scan:string("f() -> ,") end,
+ {error,{1,erl_parse,_}} = erl_parse:parse_and_scan({F2, []}),
+ F3 = fun() -> case erase(foo) of
bar ->
{ok,[{'$end',2}],3};
undefined ->
@@ -1803,13 +1802,13 @@ otp_7969(Config) when is_list(Config) ->
{ok,{function,A1,f,0,[{clause,A1,[],[],[{atom,A1,a}]}]}} =
erl_parse:parse_and_scan({F3,[]}),
F4 = fun() -> {error, {1, ?MODULE, bad}, 2} end,
- ?line {error, {1,?MODULE,bad}} = erl_parse:parse_and_scan({F4, []}),
+ {error, {1,?MODULE,bad}} = erl_parse:parse_and_scan({F4, []}),
F5 = fun() -> {eof, 3} end,
- ?line {error,{3,erl_parse,_}} = erl_parse:parse_and_scan({F5, []}),
- ?line {error,{999999,erl_parse,_}} = erl_parse:parse([]),
- ?line {ok, Ts21, EL} = erl_scan:string("f() -> a; g() -> b. ", {1,1}),
- ?line F6 = fun() -> {ok, Ts21, EL} end,
- ?line {error,{{1,11},erl_parse,_}} = erl_parse:parse_and_scan({F6, []}),
+ {error,{3,erl_parse,_}} = erl_parse:parse_and_scan({F5, []}),
+ {error,{999999,erl_parse,_}} = erl_parse:parse([]),
+ {ok, Ts21, EL} = erl_scan:string("f() -> a; g() -> b. ", {1,1}),
+ F6 = fun() -> {ok, Ts21, EL} end,
+ {error,{{1,11},erl_parse,_}} = erl_parse:parse_and_scan({F6, []}),
ok.
otp_8919(doc) ->
@@ -2050,7 +2049,7 @@ otp_11286(Config) when is_list(Config) ->
otp_14285(Config) ->
Dir = ?privdir,
YeccPre = filename:join(Dir, "yeccpre.hrl"),
- ?line ok = file:write_file(YeccPre,
+ ok = file:write_file(YeccPre,
[<<"-export([t/0]).\n">>,my_yeccpre()]),
T0 = <<"
--
2.26.2