Giter Club home page Giter Club logo

Comments (6)

ferd avatar ferd commented on May 24, 2024

The {bad_name, AppName} error is something that can be returned when the app name is looked up in code paths but is not found because it has not been built.

In this case it looks like the compile step was running, mostly completed, was running its post-hooks, one of which is "run escriptize on setup" at which point there's an error encountered around

Name ->
AllApps = rebar_state:all_deps(State)++rebar_state:project_apps(State),
case rebar_app_utils:find(rebar_utils:to_binary(Name), AllApps) of
{ok, AppInfo} ->
AppInfo;
_ ->
?PRV_ERROR({bad_name, Name})
end
end,
-- this error is because setup is configured as the main app for the escript but it is not found as fully built either within the deps or main applications.

Without access to the code it's difficult to go further, but one of my debugging steps would be to look into the ebin directory of the app within the test profile after encountering a failure. You can also run with DEBUG=1 to see if there are any issues during the compilation step.

from rebar3.

tothlac avatar tothlac commented on May 24, 2024

The previous log was created with DEBUG=1 option, without that I would have only

===> Errors loading plugin {rplug_lib,
                                   {git,
                                    "ssh://[email protected]:7999/erfidt/rplug_lib.git",
                                    {branch,"master"}}}. Run rebar3 with DEBUG=1 set to see errors.

which I still don't understand, setup and this plugins are not related to each other. Actually the same scenario is repeated for all other plugins. After this error report rebar3 tries to compile everything again and again, and the same error is printed , but for a different plugin.

Unfortunately I can't upload the code, because it happens on a repository containing business logic.
ebin directory contains the following:

[otp00231916@erldepupgr01 setup]$ pwd
/home/otp00231916/work/myapp/_build/test/lib/setup
[otp00231916@erldepupgr01 setup]$ ls -al ebin/
total 133
drwxr-x---. 2 otp00231916 otp00231916     9 Aug 23 13:16 .
drwxr-x---. 4 otp00231916 otp00231916    12 Aug 23 13:16 ..
-rw-r-----. 1 otp00231916 otp00231916   793 Aug 23 13:16 setup.app
-rw-r-----. 1 otp00231916 otp00231916  1492 Aug 23 13:16 setup_app.beam
-rw-r-----. 1 otp00231916 otp00231916 61036 Aug 23 13:16 setup.beam
-rw-r-----. 1 otp00231916 otp00231916 39180 Aug 23 13:16 setup_gen.beam
-rw-r-----. 1 otp00231916 otp00231916  8964 Aug 23 13:16 setup_lib.beam
-rw-r-----. 1 otp00231916 otp00231916  3288 Aug 23 13:16 setup_srv.beam
-rw-r-----. 1 otp00231916 otp00231916  1592 Aug 23 13:16 setup_sup.beam

But , as I mentioned earlier rebar3 eunit was successful, and eunit also runs with the test profile. So the two questions are:

  • how is it related to being not able to build a plugin
  • how is it possible it was able run eunit tests, but during a ct compiling a dependency does not work? Are there any differences between compilation before ct and eunit?

If I go into the directory of setup and call a rebar3 as test compile it works.

from rebar3.

ferd avatar ferd commented on May 24, 2024

Is it possible one of the plugins or libraries has a specific hook to the ct task and triggers rebuilds out of it somehow?

from rebar3.

tothlac avatar tothlac commented on May 24, 2024

You were right. There is a task hooked to ct. We need it because otherwise the top level application when it starts up does not have the necessary configuration read by application:get_env.
So, that's how it is hooked:

{provider_hooks,[
                       {ct,load_apps},

and the implementation of the load_apps command is the following:

-module(rebar3_load_apps).

-include("rebar3_reload.hrl").

-export([init/1, do/1, format_error/1]).

-define(PROVIDER, load_apps).
-define(DEPS, [compile]).

%%==============================================================================
%% Public API
%%==============================================================================

-spec init(State) -> Res when
    State :: rebar_state:t(),
    Res :: {ok, rebar_state:t()}.
init(State) ->
  Provider = providers:create([
                 {namespace, rebar_state:namespace(State)},
                 {name, ?PROVIDER},
                 {module, ?MODULE},
                 {bare, true},
                 {deps, ?DEPS},
                 {example, "rebar3 load_apps"},
                 {opts, []},
                 {profiles, [test]},
                 {short_desc, "Load all apps"},
                 {desc,
                    "."}]),
  {ok, rebar_state:add_provider(State, Provider)}.

-spec do(State) -> Res when
    State :: rebar_state:t(),
    Res :: {ok, rebar_state:t()} | {error, string()}.
do(State0) ->
  case rebar3_reload_lib:is_main_app(State0) of
    true ->
      erlang:system_flag(backtrace_depth, 32),
      ?INFO("Loading applications...", []),
      {ok, State} = rebar_prv_app_discovery:do(State0),
      do_(State),
      {ok, State0};
    false ->
      {ok, State0}
  end.

-spec format_error(Error) ->  Res when
    Error :: term(),
    Res :: iolist().
format_error(Reason) ->
  io_lib:format("~p", [Reason]).

%%==============================================================================
%% Internal functions
%%==============================================================================

-spec do_(State) -> Res when
    State :: rebar_state:t(),
    Res :: ok.
do_(State) ->
  Apps = rebar3_reload_lib:get_app_names(State),
  ?DEBUG("Apps: ~p", [Apps]),
  [application:load(App) || App <- Apps],
  ok.

If I delete the {ct,load_apps}, from rebar.config I don't have the errors related to the compile of other plugins, but then there will be problems during common tests, since the config of the top level application is missing. Do you have an idea how can this very simple module cause this problem? Is it related to calling rebar_prv_app_discovery:do(State0),, or something else? How else can I get the list of applications without calling rebar_prv_app_discovery:do/1 (as I remember I had to call this otherwise the list of applications was empty, or it was missing some apps). Implementation of rebar3_reload_lib:get_app_names looks like this:

get_app_names(State) ->
    AppInfos =
        case rebar_state:current_app(State) of
            undefined ->
                rebar_state:project_apps(State);
            I ->
                [I]
        end,
    [list_to_atom(binary_to_list(rebar_app_info:name(I))) || I <- AppInfos].

from rebar3.

tothlac avatar tothlac commented on May 24, 2024

Unfortunately if I don't call {ok, State} = rebar_prv_app_discovery:do(State0), in the plugin the list of applications returned by the above mentioned get_app_names will contain only the top level app. In this case I don't have those errors related to plugin recompilation, but not all applications are reloaded, and because of that ct will fail.

from rebar3.

ferd avatar ferd commented on May 24, 2024

if you want the full list of apps you also need to have depended on the lock task (which ct does) and fetch both rebar_state:all_deps(State) and rebar_state:project_apps(State) to get both the deps and the source apps.

There's also generally already something in the CT provider to load deps if they have any config value to apply:

[application:load(Application) || Config <- Configs, {Application, _} <- Config],

from rebar3.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.