Skip to content

Commit

Permalink
Merge pull request #2054 from tolbrino/fix-parallel-edoc-test
Browse files Browse the repository at this point in the history
Fix duplicate module naming in edoc test suite data
  • Loading branch information
ferd authored Apr 18, 2019
2 parents 45aaba2 + 33e4c8a commit ec224b7
Show file tree
Hide file tree
Showing 14 changed files with 26 additions and 25 deletions.
6 changes: 3 additions & 3 deletions src/rebar_compiler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -140,14 +140,14 @@ compile_queue(Targets, Pids, Opts, Config, Outs, CompilerMod) ->
Worker ! {compile, hd(Targets)},
compile_queue(tl(Targets), Pids, Opts, Config, Outs, CompilerMod);
{ok, Source} ->
?DEBUG("~sCompiled ~s", [rebar_utils:indent(1), filename:basename(Source)]),
?DEBUG("~sCompiled ~s", [rebar_utils:indent(1), Source]),
compile_queue(Targets, Pids, Opts, Config, Outs, CompilerMod);
{{ok, Warnings}, Source} ->
report(Warnings),
?DEBUG("~sCompiled ~s", [rebar_utils:indent(1), filename:basename(Source)]),
?DEBUG("~sCompiled ~s", [rebar_utils:indent(1), Source]),
compile_queue(Targets, Pids, Opts, Config, Outs, CompilerMod);
{skipped, Source} ->
?DEBUG("~sSkipped ~s", [rebar_utils:indent(1), filename:basename(Source)]),
?DEBUG("~sSkipped ~s", [rebar_utils:indent(1), Source]),
compile_queue(Targets, Pids, Opts, Config, Outs, CompilerMod);
{Error, Source} ->
NewSource = format_error_source(Source, Config),
Expand Down
2 changes: 1 addition & 1 deletion test/rebar_edoc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ error_survival(Config) ->
RebarConfig = [],
rebar_test_utils:run_and_check(
Config, RebarConfig, ["edoc"],
{error,{rebar_prv_edoc,{app_failed,"bar2"}}}
{error,{rebar_prv_edoc,{app_failed,"bad_bar2"}}}
),
ok.

Expand Down
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{application, bar1,
{application, bad_bar1,
[{description, "An OTP application"},
{vsn, "0.1.0"},
{registered, []},
{mod, { bar1_app, []}},
{mod, { bad_bar1_app, []}},
{applications,
[kernel,
stdlib
Expand Down
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
-module(bar1).
-module(bad_bar1).
-export([bar1/0]).
-export_type([barer1/0]).

-type barer1() :: string().

% @doc Bar1 bars the bar.
-spec bar1() -> barer1().
bar1() -> "Barer1".
bar1() -> "Barer1".
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
%% @end
%%%-------------------------------------------------------------------

-module(bar1_app).
-module(bad_bar1_app).

-behaviour(application).

Expand All @@ -15,7 +15,7 @@
%%====================================================================

start(_StartType, _StartArgs) ->
bar1_sup:start_link().
bad_bar1_sup:start_link().

%%--------------------------------------------------------------------
stop(_State) ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
%% @end
%%%-------------------------------------------------------------------

-module(bar1_sup).
-module(bad_bar1_sup).

-behaviour(supervisor).

Expand Down
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
{application, bar2,
{application, bad_bar2,
[{description, "An OTP application"},
{vsn, "0.1.0"},
{registered, []},
{mod, { bar2_app, []}},
{mod, { bad_bar2_app, []}},
{applications,
[kernel,
stdlib
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
%% @doc one docline is fine
%% @doc a second docline causes a failure
%% @doc if not, then a & causes a bad ref error.
-module(bar2).
-module(bad_bar2).
-export([bar2/0]).
-export_type([barer2/0]).

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
%% @end
%%%-------------------------------------------------------------------

-module(bar2_app).
-module(bad_bar2_app).

-behaviour(application).

Expand All @@ -15,7 +15,7 @@
%%====================================================================

start(_StartType, _StartArgs) ->
bar2_sup:start_link().
bad_bar2_sup:start_link().

%%--------------------------------------------------------------------
stop(_State) ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
%% @end
%%%-------------------------------------------------------------------

-module(bar2_sup).
-module(bad_bar2_sup).

-behaviour(supervisor).

Expand Down
Original file line number Diff line number Diff line change
@@ -1,12 +1,13 @@
{application, foo,
{application, bad_foo,
[{description, "An OTP application"},
{vsn, "0.1.0"},
{registered, []},
{mod, { foo_app, []}},
{mod, { bad_foo_app, []}},
{applications,
[kernel,
stdlib,
bar1, bar2
bad_bar1,
bad_bar2
]},
{env,[]},
{modules, []},
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
-module(foo).
-module(bad_foo).

-export([foo/0, bar1/0, bar2/0]).

Expand All @@ -16,4 +16,4 @@ bar1() -> bar1:bar1().

% @doc Bar2 functions returns barer2.
-spec bar2() -> bar2:barer2().
bar2() -> bar2:bar2().
bar2() -> bar2:bar2().
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
%% @end
%%%-------------------------------------------------------------------

-module(foo_app).
-module(bad_foo_app).

-behaviour(application).

Expand All @@ -15,7 +15,7 @@
%%====================================================================

start(_StartType, _StartArgs) ->
foo_sup:start_link().
bad_foo_sup:start_link().

%%--------------------------------------------------------------------
stop(_State) ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
%% @end
%%%-------------------------------------------------------------------

-module(foo_sup).
-module(bad_foo_sup).

-behaviour(supervisor).

Expand Down

0 comments on commit ec224b7

Please sign in to comment.