Skip to content

Commit

Permalink
small edits
Browse files Browse the repository at this point in the history
  • Loading branch information
vladdu committed Mar 17, 2017
1 parent e4b4af4 commit ea87f27
Show file tree
Hide file tree
Showing 22 changed files with 26 additions and 39 deletions.
3 changes: 1 addition & 2 deletions common/apps/erlide_builder/src/erlide_builder.app.src
Expand Up @@ -4,7 +4,6 @@
{erlide_context, builder},
{registered, []},
{applications, [kernel, stdlib, erlide_common]},
{env, []},
{mod, {erlide_builder_app, []}}
{env, []}
]}
.
1 change: 1 addition & 0 deletions common/apps/erlide_builder/src/erlide_builder_app.erl
Expand Up @@ -5,6 +5,7 @@
]).

init(MaxParallelBuilds) ->
io:format("Start builder app~n"),
spawn(fun()->
erlide_pool:start(erlide_builder, MaxParallelBuilds),
ok
Expand Down
8 changes: 2 additions & 6 deletions common/apps/erlide_common/src/erlide_backend.erl
Expand Up @@ -30,7 +30,6 @@
compile_string/1,
start_tracer/1,

get_system_info/0,
get_module_info/1
]).

Expand All @@ -44,7 +43,7 @@ parse_term(Str) ->

parse_term_raw(Str) ->
%% erlide_log:logp(Str),
%% use the OTP erl_scan here!
%% use the OTP erl_scan here!
{ok, Tokens, _} = erl_scan:string(Str),
%% erlide_log:logp(Tokens),
R=erl_parse:parse_term(Tokens),
Expand Down Expand Up @@ -121,7 +120,7 @@ execute(StrFun, Args) ->
catch case parse_string(StrMod) of
{ok, Mod} ->
{ok, erlide_execute_tmp,Bin} = compile:forms(Mod, [report,binary]),
code:load_binary(erlide_execute_tmp, "erlide_execute_tmp.erl", Bin),
_ = code:load_binary(erlide_execute_tmp, "erlide_execute_tmp.erl", Bin),
Res = erlide_execute_tmp:exec(Args),
code:delete(erlide_execute_tmp),
code:purge(erlide_execute_tmp),
Expand Down Expand Up @@ -210,6 +209,3 @@ print_opts({K, V}) ->
print_opts(X) ->
io_lib:format(" ~p~n", [X]).

get_system_info() ->
lists:flatten(io_lib:format("~p~n", [erlide_monitor:get_state()])).

3 changes: 1 addition & 2 deletions common/apps/erlide_common/src/erlide_common.app.src
Expand Up @@ -4,7 +4,6 @@
{erlide_context, common},
{registered, []},
{applications, [kernel, stdlib]},
{env, []},
{mod, {erlide_common_app, []}}
{env, []}
]}
.
1 change: 1 addition & 0 deletions common/apps/erlide_common/src/erlide_common_app.erl
Expand Up @@ -5,6 +5,7 @@
]).

init(JRex, Kill, HeapWarnLimit, HeapKillLimit) ->
io:format("Start common app~n"),
spawn(fun () ->
startup(JRex, Kill, HeapWarnLimit, HeapKillLimit)
end).
Expand Down
12 changes: 6 additions & 6 deletions common/apps/erlide_common/src/erlide_shell.erl
Expand Up @@ -113,7 +113,7 @@ handle_input(Client, State, Input) ->
{done, Result, []} ->
#io_request{from = From,
reply_as = ReplyAs} = FirstReq,
io_reply(From, ReplyAs, Result),
_ = io_reply(From, ReplyAs, Result),
case length(RestReqs) of
0 ->
{ok, idle};
Expand All @@ -126,7 +126,7 @@ handle_input(Client, State, Input) ->
{done, Result, RestChars} ->
#io_request{from = From,
reply_as = ReplyAs} = FirstReq,
io_reply(From, ReplyAs, Result),
_ = io_reply(From, ReplyAs, Result),
case length(RestReqs) of
0 ->
{ok, {pending_input, RestChars}};
Expand All @@ -150,7 +150,7 @@ put_chars(From, ReplyAs, State, Encoding, Mod, Fun, Args) ->
end,
FlatText = string_flatten(Text),
send_event(FlatText, From, Encoding),
io_reply(From, ReplyAs, ok),
_ = io_reply(From, ReplyAs, ok),
{ok, State}.


Expand Down Expand Up @@ -181,7 +181,7 @@ get_until(From, ReplyAs, Client, State, _Encoding, Prompt, Mod, Fun, Args) ->
put_chars(From, ReplyAs, State, Encoding, Text) ->
FlatText = string_flatten(Text),
send_event(FlatText, From, Encoding),
io_reply(From, ReplyAs, ok),
_ = io_reply(From, ReplyAs, ok),
{ok, State}.


Expand Down Expand Up @@ -213,13 +213,13 @@ handle_io_request(Client, State, From, ReplyAs, IoRequest) ->
handle_io_requests(Client, State, From, ReplyAs, IoReqests);

getopts ->
io_reply(From, ReplyAs, [{encoding, latin1}]),
_ = io_reply(From, ReplyAs, [{encoding, latin1}]),
{ok, State};

UnexpectedIORequest ->
loginfo("~p:handle_io_request: Unexpected IORequest:~p~n",
[?MODULE, UnexpectedIORequest]),
io_reply(From, ReplyAs, ok),
_ = io_reply(From, ReplyAs, ok),
{ok, State}
end.

Expand Down
1 change: 0 additions & 1 deletion common/apps/erlide_tools/src/erlide_dialyze.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 17 feb 2010
%% Description: TODO: Add description to erlide_dialyze
-module(erlide_dialyze).

%%
Expand Down
3 changes: 1 addition & 2 deletions common/apps/erlide_tools/src/erlide_tools.app.src
Expand Up @@ -4,7 +4,6 @@
{erlide_context, common},
{registered, []},
{applications, [kernel, stdlib, erlide_common]},
{env, []},
{mod, {erlide_tools_app, []}}
{env, []}
]}
.
1 change: 1 addition & 0 deletions common/apps/erlide_tools/src/erlide_tools_app.erl
Expand Up @@ -5,5 +5,6 @@
]).

init() ->
io:format("Start tools app~n"),
ok.

1 change: 0 additions & 1 deletion ide/apps/erlide_ide/src/erlide_comment.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: Mar 23, 2006
%% Description: TODO: Add description to erlide_comment

-module(erlide_comment).

Expand Down
3 changes: 1 addition & 2 deletions ide/apps/erlide_ide/src/erlide_ide.app.src
Expand Up @@ -4,7 +4,6 @@
{erlide_context, ide},
{registered, []},
{applications, [kernel, stdlib, erlide_common, erlide_server]},
{env, []},
{mod, {erlide_ide_app, []}}
{env, []}
]}
.
1 change: 1 addition & 0 deletions ide/apps/erlide_ide/src/erlide_ide_app.erl
Expand Up @@ -5,5 +5,6 @@
]).

init() ->
io:format("Start ide app~n"),
ok.

1 change: 0 additions & 1 deletion ide/apps/erlide_ide/test/erlide_indent_tests.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 24 nov 2009
%% Description: TODO: Add description to erlide_indent_tests
-module(erlide_indent_tests).

%%
Expand Down
1 change: 0 additions & 1 deletion ide/apps/erlide_ide/test/erlide_search_tests.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 20 dec 2010
%% Description: TODO: Add description to erlide_search_tests
-module(erlide_search_tests).

%%
Expand Down
1 change: 0 additions & 1 deletion ide/apps/erlide_server/src/erlide_np_records.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 18 dec 2010
%% Description: TODO: Add description to erlide_np_records
-module(erlide_np_records).

%%
Expand Down
1 change: 0 additions & 1 deletion ide/apps/erlide_server/src/erlide_np_util.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 7 nov 2010
%% Description: TODO: Add description to erlide_np_util
-module(erlide_np_util).

%% -define(DEBUG, 1).
Expand Down
3 changes: 1 addition & 2 deletions ide/apps/erlide_server/src/erlide_server.app.src
Expand Up @@ -4,7 +4,6 @@
{erlide_context, ide},
{registered, []},
{applications, [kernel, stdlib, erlide_common]},
{env, []},
{mod, {erlide_server_app, []}}
{env, []}
]}
.
1 change: 1 addition & 0 deletions ide/apps/erlide_server/src/erlide_server_app.erl
Expand Up @@ -5,5 +5,6 @@
]).

init() ->
io:format("Start server app~n"),
ok.

1 change: 0 additions & 1 deletion ide/apps/erlide_server/test/erlide_parsing_tests.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 30 aug 2010
%% Description: TODO: Add description to erlide_parsing_test
-module(erlide_parsing_tests).

%%
Expand Down
1 change: 0 additions & 1 deletion ide/apps/erlide_server/test/erlide_scan_tests.erl
@@ -1,5 +1,4 @@
%% coding: utf-8
%% Description: TODO: Add description to erlide_scanner_tests
-module(erlide_scan_tests).

%%
Expand Down
1 change: 0 additions & 1 deletion ide/apps/erlide_server/test/erlide_scanner_tests.erl
@@ -1,6 +1,5 @@
%% Author: jakob
%% Created: 12 okt 2009
%% Description: TODO: Add description to erlide_scanner_tests
-module(erlide_scanner_tests).

%%
Expand Down
16 changes: 8 additions & 8 deletions ide/rebar.config
Expand Up @@ -44,14 +44,14 @@
deprecated_functions
]}.

{dialyzer,
[
%% Store PLT locally inside the project in .rebar (Default)
%% {plt_location, local},
%% Store PLT in custom directory
%% {plt_location, "custom_dir"},
{warnings, [unmatched_returns, error_handling, unknown]}
]}.
{dialyzer, [
%% Store PLT locally inside the project in .rebar (Default)
%% {plt_location, local},
%% Store PLT in custom directory
%% {plt_location, "custom_dir"},
{warnings, [unmatched_returns, error_handling, unknown]},
{base_plt_apps, [erts, kernel, stdlib, syntax_tools, tools]}
]}.

{cover_export_enabled, true}.
{cover_enabled, true}.
Expand Down

0 comments on commit ea87f27

Please sign in to comment.