Skip to content

Commit

Permalink
Merge branch 'nox/compile-column-numbers' into pu
Browse files Browse the repository at this point in the history
  • Loading branch information
proxyles committed Oct 11, 2012
2 parents e06c4cc + e869e22 commit 98bf395
Show file tree
Hide file tree
Showing 19 changed files with 1,127 additions and 940 deletions.
178 changes: 90 additions & 88 deletions erts/doc/src/absform.xml

Large diffs are not rendered by default.

22 changes: 5 additions & 17 deletions lib/compiler/doc/src/compile.xml
Expand Up @@ -108,6 +108,11 @@
See the <em>Efficiency Guide</em> for further information.</p> See the <em>Efficiency Guide</em> for further information.</p>
</item> </item>


<tag><c>column</c></tag>
<item>
<p>The compiler will keep the column numbers while parsing.</p>
</item>

<tag><c>compressed</c></tag> <tag><c>compressed</c></tag>
<item> <item>
<p>The compiler will compress the generated object code, <p>The compiler will compress the generated object code,
Expand Down Expand Up @@ -823,23 +828,6 @@ pi() -> 3.1416.
code is then transformed into other Erlang code.</p> code is then transformed into other Erlang code.</p>
</section> </section>


<section>
<title>Error Information</title>

<p>The <c>ErrorInfo</c> mentioned above is the standard
<c>ErrorInfo</c> structure which is returned from all IO modules.
It has the following format:</p>
<code>
{ErrorLine, Module, ErrorDescriptor}
</code>

<p>A string describing the error is obtained with the following
call:</p>
<code>
Module:format_error(ErrorDescriptor)
</code>
</section>

<section> <section>
<title>See Also</title> <title>See Also</title>
<p> <p>
Expand Down
11 changes: 9 additions & 2 deletions lib/compiler/src/compile.erl
Expand Up @@ -41,7 +41,7 @@


-type option() :: atom() | {atom(), term()} | {'d', atom(), term()}. -type option() :: atom() | {atom(), term()} | {'d', atom(), term()}.


-type err_info() :: {erl_scan:line(), module(), term()}. %% ErrorDescriptor -type err_info() :: erl_scan:error_info(). %% ErrorDescriptor
-type errors() :: [{file:filename(), [err_info()]}]. -type errors() :: [{file:filename(), [err_info()]}].
-type warnings() :: [{file:filename(), [err_info()]}]. -type warnings() :: [{file:filename(), [err_info()]}].
-type mod_ret() :: {'ok', module()} -type mod_ret() :: {'ok', module()}
Expand Down Expand Up @@ -773,7 +773,8 @@ parse_module(St) ->
Opts = St#compile.options, Opts = St#compile.options,
Cwd = ".", Cwd = ".",
IncludePath = [Cwd, St#compile.dir|inc_paths(Opts)], IncludePath = [Cwd, St#compile.dir|inc_paths(Opts)],
R = epp:parse_file(St#compile.ifile, IncludePath, pre_defs(Opts)), AtPos = initial_position(Opts),
R = epp:parse_file(St#compile.ifile, AtPos, IncludePath, pre_defs(Opts)),
case R of case R of
{ok,Forms} -> {ok,Forms} ->
{ok,St#compile{code=Forms}}; {ok,St#compile{code=Forms}};
Expand Down Expand Up @@ -1486,6 +1487,12 @@ objfile(Base, St) ->
tmpfile(Ofile) -> tmpfile(Ofile) ->
reverse([$#|tl(reverse(Ofile))]). reverse([$#|tl(reverse(Ofile))]).


initial_position(Opts) ->
case lists:member(column, Opts) of
true -> {1, 1};
false -> 1
end.

%% pre_defs(Options) %% pre_defs(Options)
%% inc_paths(Options) %% inc_paths(Options)
%% Extract the predefined macros and include paths from the option list. %% Extract the predefined macros and include paths from the option list.
Expand Down
6 changes: 5 additions & 1 deletion lib/compiler/src/v3_core.erl
Expand Up @@ -2158,6 +2158,10 @@ format_error(nomatch) ->
format_error(bad_binary) -> format_error(bad_binary) ->
"binary construction will fail because of a type mismatch". "binary construction will fail because of a type mismatch".


add_warning(Line, Term, #core{ws=Ws,file=[{file,File}]}=St) when Line >= 0 -> add_warning({Line,_}=Loc, Term, #core{ws=Ws,file=[{file,File}]}=St)
when Line >= 0 ->
St#core{ws=[{File,[{location(Loc),?MODULE,Term}]}|Ws]};
add_warning(Line, Term, #core{ws=Ws,file=[{file,File}]}=St)
when is_integer(Line), Line >= 0 ->
St#core{ws=[{File,[{location(Line),?MODULE,Term}]}|Ws]}; St#core{ws=[{File,[{location(Line),?MODULE,Term}]}|Ws]};
add_warning(_, _, St) -> St. add_warning(_, _, St) -> St.
15 changes: 13 additions & 2 deletions lib/compiler/test/error_SUITE.erl
Expand Up @@ -22,13 +22,15 @@


-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2, init_per_group/2,end_per_group/2,
head_mismatch_line/1,warnings_as_errors/1, bif_clashes/1]). head_mismatch_line/1,warnings_as_errors/1, bif_clashes/1,
column_number/1
]).


suite() -> [{ct_hooks,[ts_install_cth]}]. suite() -> [{ct_hooks,[ts_install_cth]}].


all() -> all() ->
test_lib:recompile(?MODULE), test_lib:recompile(?MODULE),
[head_mismatch_line, warnings_as_errors, bif_clashes]. [head_mismatch_line, warnings_as_errors, bif_clashes, column_number].


groups() -> groups() ->
[]. [].
Expand Down Expand Up @@ -166,6 +168,15 @@ bif_clashes(Config) when is_list(Config) ->






%% Tests that messages are correctly reported with column numbers
%% if the column option is set.
column_number(Config) when is_list(Config) ->
Ts1 = [{column_number_warning,
<<"\nt(X) -> ok.">>,
[return_warnings, export_all, column],
{warning, [{{2, 3}, erl_lint, {unused_var, 'X'}}]}}],
?line [] = run(Config, Ts1),
ok.


%% Tests that a head mismatch is reported on the correct line (OTP-2125). %% Tests that a head mismatch is reported on the correct line (OTP-2125).
head_mismatch_line(Config) when is_list(Config) -> head_mismatch_line(Config) when is_list(Config) ->
Expand Down
6 changes: 4 additions & 2 deletions lib/stdlib/doc/src/epp.xml
Expand Up @@ -51,6 +51,7 @@
<func> <func>
<name name="open" arity="2"/> <name name="open" arity="2"/>
<name name="open" arity="3"/> <name name="open" arity="3"/>
<name name="open" arity="4"/>
<fsummary>Open a file for preprocessing</fsummary> <fsummary>Open a file for preprocessing</fsummary>
<desc> <desc>
<p>Opens a file for preprocessing.</p> <p>Opens a file for preprocessing.</p>
Expand All @@ -68,17 +69,18 @@
<fsummary>Return the next Erlang form from the opened Erlang source file</fsummary> <fsummary>Return the next Erlang form from the opened Erlang source file</fsummary>
<desc> <desc>
<p>Returns the next Erlang form from the opened Erlang source file. <p>Returns the next Erlang form from the opened Erlang source file.
The tuple <c>{eof, <anno>Line</anno>}</c> is returned at end-of-file. The first The tuple <c>{eof, <anno>Loc</anno>}</c> is returned at end-of-file. The first
form corresponds to an implicit attribute <c>-file(File,1).</c>, where form corresponds to an implicit attribute <c>-file(File,1).</c>, where
<c>File</c> is the name of the file.</p> <c>File</c> is the name of the file.</p>
</desc> </desc>
</func> </func>
<func> <func>
<name name="parse_file" arity="3"/> <name name="parse_file" arity="3"/>
<name name="parse_file" arity="4"/>
<fsummary>Preprocess and parse an Erlang source file</fsummary> <fsummary>Preprocess and parse an Erlang source file</fsummary>
<desc> <desc>
<p>Preprocesses and parses an Erlang source file. <p>Preprocesses and parses an Erlang source file.
Note that the tuple <c>{eof, <anno>Line</anno>}</c> returned at end-of-file is Note that the tuple <c>{eof, <anno>Loc</anno>}</c> returned at end-of-file is
included as a "form".</p> included as a "form".</p>
</desc> </desc>
</func> </func>
Expand Down
28 changes: 4 additions & 24 deletions lib/stdlib/doc/src/erl_lint.xml
Expand Up @@ -60,14 +60,6 @@
functions separately unless you have written your own Erlang functions separately unless you have written your own Erlang
compiler.</p> compiler.</p>
</description> </description>
<datatypes>
<datatype>
<name name="error_info"/>
</datatype>
<datatype>
<name name="error_description"/>
</datatype>
</datatypes>
<funcs> <funcs>
<func> <func>
<name name="module" arity="1"/> <name name="module" arity="1"/>
Expand Down Expand Up @@ -125,29 +117,17 @@
<p>Takes an <c><anno>ErrorDescriptor</anno></c> and returns a string which <p>Takes an <c><anno>ErrorDescriptor</anno></c> and returns a string which
describes the error or warning. This function is usually describes the error or warning. This function is usually
called implicitly when processing an <c>ErrorInfo</c> called implicitly when processing an <c>ErrorInfo</c>
structure (see below).</p> structure (see
<seealso marker="erl_scan#error_information">erl_scan(3)</seealso>).
</p>
</desc> </desc>
</func> </func>
</funcs> </funcs>


<section>
<title>Error Information</title>
<p>The <c>ErrorInfo</c> mentioned above is the standard
<c>ErrorInfo</c> structure which is returned from all IO
modules. It has the following format:
</p>
<code type="none">
{ErrorLine, Module, ErrorDescriptor} </code>
<p>A string which describes the error is obtained with the following call:
</p>
<code type="none">
Module:format_error(ErrorDescriptor) </code>
</section>

<section> <section>
<title>See Also</title> <title>See Also</title>
<p><seealso marker="erl_parse">erl_parse(3)</seealso>, <p><seealso marker="erl_parse">erl_parse(3)</seealso>,
<seealso marker="epp">epp(3)</seealso></p> <seealso marker="epp">epp(3)</seealso>, <seealso marker="erl_scan">erl_scan(3)</seealso></p>
</section> </section>
</erlref> </erlref>


26 changes: 4 additions & 22 deletions lib/stdlib/doc/src/erl_parse.xml
Expand Up @@ -57,12 +57,6 @@
<desc><p>Parse tree for Erlang form.</p> <desc><p>Parse tree for Erlang form.</p>
</desc> </desc>
</datatype> </datatype>
<datatype>
<name name="error_description"></name>
</datatype>
<datatype>
<name name="error_info"></name>
</datatype>
<datatype> <datatype>
<name name="token"></name> <name name="token"></name>
</datatype> </datatype>
Expand Down Expand Up @@ -130,14 +124,16 @@
<fsummary>Format an error descriptor</fsummary> <fsummary>Format an error descriptor</fsummary>
<type> <type>
<v>ErrorDescriptor = <seealso <v>ErrorDescriptor = <seealso
marker="#type-error_info">error_description()</seealso></v> marker="erl_scan#type-error_description">erl_scan:error_description()</seealso></v>
<v>Chars = [char() | Chars]</v> <v>Chars = [char() | Chars]</v>
</type> </type>
<desc> <desc>
<p>Uses an <c>ErrorDescriptor</c> and returns a string <p>Uses an <c>ErrorDescriptor</c> and returns a string
which describes the error. This function is usually called which describes the error. This function is usually called
implicitly when an <c>ErrorInfo</c> structure is processed implicitly when an <c>ErrorInfo</c> structure is processed
(see below).</p> (see
<seealso marker="erl_scan#error_information">erl_scan(3)</seealso>).
</p>
</desc> </desc>
</func> </func>
<func> <func>
Expand Down Expand Up @@ -171,20 +167,6 @@
</func> </func>
</funcs> </funcs>


<section>
<title>Error Information</title>
<p>The <c>ErrorInfo</c> mentioned above is the standard
<c>ErrorInfo</c> structure which is returned from all IO
modules. It has the format:
</p>
<code type="none">
{ErrorLine, Module, ErrorDescriptor} </code>
<p>A string which describes the error is obtained with the following call:
</p>
<code type="none">
Module:format_error(ErrorDescriptor) </code>
</section>

<section> <section>
<title>See Also</title> <title>See Also</title>
<p><seealso marker="io">io(3)</seealso>, <p><seealso marker="io">io(3)</seealso>,
Expand Down
18 changes: 14 additions & 4 deletions lib/stdlib/doc/src/erl_scan.xml
Expand Up @@ -284,6 +284,9 @@
column()</seealso>}</c></tag> column()</seealso>}</c></tag>
<item><p>The column where the token begins.</p> <item><p>The column where the token begins.</p>
</item> </item>
<tag><c>{file, string()}</c></tag>
<item><p>The file in which the token is.</p>
</item>
<tag><c>{length, integer() > 0}</c></tag> <tag><c>{length, integer() > 0}</c></tag>
<item><p>The length of the token's text.</p> <item><p>The length of the token's text.</p>
</item> </item>
Expand Down Expand Up @@ -351,6 +354,9 @@
column()</seealso>}</c></tag> column()</seealso>}</c></tag>
<item><p>The column where the token begins.</p> <item><p>The column where the token begins.</p>
</item> </item>
<tag><c>{file, string()}</c></tag>
<item><p>The file in which the token is.</p>
</item>
<tag><c>{length, integer() > 0}</c></tag> <tag><c>{length, integer() > 0}</c></tag>
<item><p>The length of the token's text.</p> <item><p>The length of the token's text.</p>
</item> </item>
Expand All @@ -373,11 +379,14 @@
<name name="set_attribute" arity="3"/> <name name="set_attribute" arity="3"/>
<fsummary>Set a token attribute value</fsummary> <fsummary>Set a token attribute value</fsummary>
<desc> <desc>
<p>Sets the value of the <c>line</c> attribute of the token <p>Sets the value of the <c>line</c> or <c>file</c> attribute of the
attributes <c><anno>Attributes</anno></c>.</p> token attributes <c><anno>Attributes</anno></c>.</p>
<p>The <c><anno>SetAttributeFun</anno></c> is called with the value of <p>The <c><anno>SetAttributeFun</anno></c> is called with the value of
the <c>line</c> attribute, and is to return the new value of the <c>line</c> or <c>file</c> attribute, and is to return its new
the <c>line</c> attribute.</p> value.</p>
<p>When setting the value of the <c>file</c> attribute,
<c><anno>SetAttributeFun</anno></c> may be given or return
<c>undefined</c> as an absence of value.</p>
</desc> </desc>
</func> </func>
<func> <func>
Expand All @@ -394,6 +403,7 @@
</funcs> </funcs>


<section> <section>
<marker id="error_information"/>
<title>Error Information</title> <title>Error Information</title>
<p>The <c>ErrorInfo</c> mentioned above is the standard <p>The <c>ErrorInfo</c> mentioned above is the standard
<c>ErrorInfo</c> structure which is returned from all IO <c>ErrorInfo</c> structure which is returned from all IO
Expand Down

0 comments on commit 98bf395

Please sign in to comment.