Skip to content

Commit

Permalink
Merge branch 'hm/wx-silent_start' into pu
Browse files Browse the repository at this point in the history
  • Loading branch information
proxyles committed Jul 18, 2012
2 parents 0ad7b27 + 571ba06 commit f008f7a
Show file tree
Hide file tree
Showing 5 changed files with 75 additions and 37 deletions.
36 changes: 24 additions & 12 deletions lib/wx/src/wx.erl
Original file line number Diff line number Diff line change
Expand Up @@ -102,12 +102,18 @@ new() ->

%% @doc Starts a wx server.
%% Option may be {debug, Level}, see debug/1.
-spec new([Option]) -> wx_object() when Option :: {debug, list() | atom()}.
%% Or {silent_start, Bool}, which causes error messages at startup to
%% be suppressed. The latter can be used as a silent test of whether
%% wx is properly installed or not.
-spec new([Option]) -> wx_object() when Option :: {debug, list() | atom()} |
{silent_start, boolean()}.
new(Options) when is_list(Options) ->
#wx_env{port=Port} = wxe_server:start(),
put(opengl_port, Port),
Debug = proplists:get_value(debug, Options, 0),
debug(Debug),
SilentStart = proplists:get_value(silent_start, Options, false),
Level = calc_level(Debug),
#wx_env{port=Port} = wxe_server:start(SilentStart andalso Level =/= 0),
put(opengl_port, Port),
set_debug(Level),
null().

%% @doc Stops a wx server.
Expand Down Expand Up @@ -282,13 +288,16 @@ release_memory(Bin) when is_binary(Bin) ->
-spec debug(Level | [Level]) -> ok
when Level :: none | verbose | trace | driver | integer().

debug(none) -> debug(0);
debug(verbose) -> debug(1);
debug(trace) -> debug(2);
debug(driver) -> debug(16);
debug([]) -> debug(0);
debug(Debug) ->
Level = calc_level(Debug),
set_debug(Level).

debug(List) when is_list(List) ->
calc_level(none) -> calc_level(0);
calc_level(verbose) -> calc_level(1);
calc_level(trace) -> calc_level(2);
calc_level(driver) -> calc_level(16);
calc_level([]) -> calc_level(0);
calc_level(List) when is_list(List) ->
{Drv,Erl} =
lists:foldl(fun(verbose, {Drv,_Erl}) ->
{Drv,1};
Expand All @@ -297,8 +306,11 @@ debug(List) when is_list(List) ->
(driver, {_Drv,Erl}) ->
{16, Erl}
end, {0,0}, List),
debug(Drv + Erl);
debug(Level) when is_integer(Level) ->
Drv + Erl;
calc_level(Level) when is_integer(Level) ->
Level.

set_debug(Level) when is_integer(Level) ->
case get(?WXE_IDENTIFIER) of
undefined -> erlang:error({wxe,unknown_port});
#wx_env{debug=Old} when Old =:= Level -> ok;
Expand Down
28 changes: 16 additions & 12 deletions lib/wx/src/wxe_master.erl
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@
-behaviour(gen_server).

%% API
-export([start/0, init_port/0, init_opengl/0]).
-export([start/1, init_port/1, init_opengl/0]).

%% gen_server callbacks
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
Expand All @@ -47,20 +47,20 @@
%% API
%%====================================================================
%%--------------------------------------------------------------------
%% Function: start_link() -> {ok,Pid} | ignore | {error,Error}
%% Function: start(SilentStart) -> {ok,Pid} | ignore | {error,Error}
%% Description: Starts the server
%%--------------------------------------------------------------------
start() ->
gen_server:start({local, ?MODULE}, ?MODULE, [], []).
start(SilentStart) ->
gen_server:start({local, ?MODULE}, ?MODULE, [SilentStart], []).

%%--------------------------------------------------------------------
%% Function: init_port() -> {UserPort,CallBackPort} | error(Error)
%% Function: init_port(SilentStart) -> {UserPort,CallBackPort} | error(Error)
%% Description: Creates the port
%%--------------------------------------------------------------------
init_port() ->
init_port(SilentStart) ->
case whereis(?MODULE) of
undefined ->
case start() of
case start(SilentStart) of
{ok,Pid} -> Pid;
{error,{already_started,Pid}} -> Pid;
{error, {Reason,Stack}} ->
Expand Down Expand Up @@ -93,14 +93,17 @@ init_opengl() ->
%% {stop, Reason}
%% Description: Initiates the server
%%--------------------------------------------------------------------
init([]) ->
init([SilentStart]) ->
DriverName = ?DRIVER,
PrivDir = wxe_util:priv_dir(?DRIVER),
PrivDir = wxe_util:priv_dir(?DRIVER, SilentStart),
erlang:group_leader(whereis(init), self()),
case catch erlang:system_info(smp_support) of
true -> ok;
_ ->
error_logger:format("WX ERROR: SMP emulator required (start with erl -smp)", []),
wxe_util:opt_error_log(SilentStart,
"WX ERROR: SMP emulator required"
" (start with erl -smp)",
[]),
erlang:error(not_smp)
end,

Expand All @@ -114,7 +117,9 @@ init([]) ->
case erl_ddll:load_driver(PrivDir,DriverName) of
ok -> ok;
{error, What} ->
error_logger:format("WX Failed loading ~p@~p ~n", [DriverName,PrivDir]),
wxe_util:opt_error_log(SilentStart,
"WX Failed loading ~p@~p ~n",
[DriverName,PrivDir]),
Str = erl_ddll:format_error(What),
erlang:error({load_driver,Str})
end,
Expand Down Expand Up @@ -210,4 +215,3 @@ debug_ping(Port) ->
_R = (catch erlang:port_call(Port, 0, [])),
%% io:format("Erlang ping ~p ~n", [_R]),
debug_ping(Port).

14 changes: 7 additions & 7 deletions lib/wx/src/wxe_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@
-behaviour(gen_server).

%% API
-export([start/0, stop/0, register_me/1, set_debug/2, invoke_callback/1]).
-export([start/1, stop/0, register_me/1, set_debug/2, invoke_callback/1]).

%% gen_server callbacks
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
Expand All @@ -49,13 +49,13 @@
%% API
%%====================================================================
%%--------------------------------------------------------------------
%% Function: start() -> #wx_env{}
%% Function: start(SilentStart) -> #wx_env{}
%% Description: Starts the server
%%--------------------------------------------------------------------
start() ->
start(SilentStart) ->
case get(?WXE_IDENTIFIER) of
undefined ->
case gen_server:start(?MODULE, [], []) of
case gen_server:start(?MODULE, [SilentStart], []) of
{ok, Pid} ->
{ok, Port} = gen_server:call(Pid, get_port, infinity),
wx:set_env(Env = #wx_env{port=Port,sv=Pid}),
Expand All @@ -69,7 +69,7 @@ start() ->
Env;
false -> %% Ok we got an old wx env, someone forgot
erase(?WXE_IDENTIFIER), %% to call wx:destroy()
start()
start(SilentStart)
end
end.

Expand All @@ -88,8 +88,8 @@ set_debug(Pid, Level) ->
%% gen_server callbacks
%%====================================================================

init([]) ->
{Port,CBPort} = wxe_master:init_port(),
init([SilentStart]) ->
{Port,CBPort} = wxe_master:init_port(SilentStart),
put(?WXE_IDENTIFIER, #wx_env{port=Port,sv=self()}),
{ok,#state{port=Port, cb_port=CBPort,
users=gb_trees:empty(), cb=gb_trees:empty(), cb_cnt=1}}.
Expand Down
15 changes: 10 additions & 5 deletions lib/wx/src/wxe_util.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@
get_const/1,colour_bin/1,datetime_bin/1,
to_bool/1,from_bool/1]).

-export([wxgl_dl/0, priv_dir/1]).
-export([wxgl_dl/0, priv_dir/2, opt_error_log/3]).

-include("wxe.hrl").

Expand Down Expand Up @@ -205,7 +205,7 @@ check_previous() ->

wxgl_dl() ->
DynLib0 = "erl_gl",
PrivDir = priv_dir(DynLib0),
PrivDir = priv_dir(DynLib0, false),
DynLib = case os:type() of
{win32,_} ->
DynLib0 ++ ".dll";
Expand All @@ -214,7 +214,7 @@ wxgl_dl() ->
end,
filename:join(PrivDir, DynLib).

priv_dir(Driver0) ->
priv_dir(Driver0, Silent) ->
{file, Path} = code:is_loaded(?MODULE),
Priv = case filelib:is_regular(Path) of
true ->
Expand All @@ -234,8 +234,9 @@ priv_dir(Driver0) ->
{ok, _} ->
Priv;
{error, _} ->
error_logger:format("ERROR: Could not find \'~s\' in: ~s~n",
[Driver, Priv]),
opt_error_log(Silent,
"ERROR: Could not find \'~s\' in: ~s~n",
[Driver, Priv]),
erlang:error({load_driver, "No driver found"})
end.

Expand All @@ -244,3 +245,7 @@ strip(Src, Src) ->
strip([H|R], Src) ->
[H| strip(R, Src)].

opt_error_log(true, Format, Args) ->
error_logger:format(Format, Args);
opt_error_log(false, _Format, _Args) ->
ok.
19 changes: 18 additions & 1 deletion lib/wx/test/wx_basic_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ end_per_testcase(Func,Config) ->
suite() -> [{ct_hooks,[ts_install_cth]}].

all() ->
[create_window, several_apps, wx_api, wx_misc,
[silent_start, create_window, several_apps, wx_api, wx_misc,
data_types, wx_object].

groups() ->
Expand All @@ -62,6 +62,23 @@ end_per_group(_GroupName, Config) ->

%% The test cases

%% test silent start of wx
silent_start(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
silent_start(Config) ->
?mr(wx_ref, wx:new([])),
wx:destroy(),

?mr(wx_ref, wx:new([{silent_start, true}])),
wx:destroy(),

?mr(wx_ref, wx:new([{silent_start, true}, {debug, verbose}])),
wx:destroy(),

?mr(wx_ref, wx:new([{silent_start, false}])),
wx:destroy(),

?mr('EXIT', wx:new([{silent_start, foo}])).

%% create and test creating a window
create_window(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
create_window(Config) ->
Expand Down

0 comments on commit f008f7a

Please sign in to comment.