~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/wx/src/wxe_master.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2008-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%%-------------------------------------------------------------------
19
19
%%% File    : wxe_server.erl
28
28
-behaviour(gen_server).
29
29
 
30
30
%% API
31
 
-export([start/0, init_port/0]).
 
31
-export([start/0, init_port/0, init_opengl/0]).
32
32
 
33
33
%% gen_server callbacks
34
34
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
35
35
         terminate/2, code_change/3]).
36
 
-compile(export_all).
37
36
 
38
37
-record(state, {cb_port,  %% Callback port and to erlang messages goes via it.
39
38
                users,    %% List of wx servers, needed ??
40
39
                driver}). %% Driver name so wx_server can create it's own port
41
40
 
 
41
-include("wxe.hrl").
42
42
-include("gen/wxe_debug.hrl").
43
 
-include("gen/gl_debug.hrl").
44
43
 
45
44
-define(DRIVER, "wxe_driver").
46
45
 
75
74
    receive wx_port_initiated -> ok end,
76
75
    {Port, CBport}.
77
76
 
 
77
 
 
78
%%--------------------------------------------------------------------
 
79
%% Initlizes the opengl library
 
80
%%--------------------------------------------------------------------
 
81
init_opengl() ->
 
82
    GLLib = wxe_util:wxgl_dl(),
 
83
    wxe_util:call(?WXE_INIT_OPENGL, <<(list_to_binary(GLLib))/binary, 0:8>>).
 
84
 
78
85
%%====================================================================
79
86
%% gen_server callbacks
80
87
%%====================================================================
88
95
%%--------------------------------------------------------------------
89
96
init([]) ->
90
97
    DriverName = ?DRIVER,
91
 
    PrivDir = priv_dir(),
 
98
    PrivDir = wxe_util:priv_dir(?DRIVER),
92
99
    erlang:group_leader(whereis(init), self()),
93
100
    case catch erlang:system_info(smp_support) of
94
101
        true -> ok;
121
128
    process_flag(trap_exit, true),
122
129
    DriverWithArgs = DriverName ++ " " ++ code:priv_dir(wx) ++ [0],
123
130
    
124
 
    case catch open_port({spawn, DriverWithArgs},[binary]) of
125
 
        {'EXIT', Err} -> 
126
 
            erlang:error({open_port,Err});
127
 
        Port ->
128
 
            wx_debug_info = ets:new(wx_debug_info, [named_table]),
129
 
            wx_non_consts = ets:new(wx_non_consts, [named_table]),
130
 
            true = ets:insert(wx_debug_info, wxdebug_table()),
131
 
            true = ets:insert(wx_debug_info, gldebug_table()),
132
 
            spawn_link(fun() -> debug_ping(Port) end),
133
 
            receive 
134
 
                {wx_consts, List} ->
135
 
                    true = ets:insert(wx_non_consts, List)
136
 
            end,
137
 
            {ok, #state{cb_port=Port, driver=DriverName, users=gb_sets:empty()}}
 
131
    try
 
132
        Port = open_port({spawn, DriverWithArgs},[binary]),
 
133
        wx_debug_info = ets:new(wx_debug_info, [named_table]),
 
134
        wx_non_consts = ets:new(wx_non_consts, [named_table]),
 
135
        true = ets:insert(wx_debug_info, wxdebug_table()),
 
136
        spawn_link(fun() -> debug_ping(Port) end),
 
137
        receive
 
138
            {wx_consts, List} ->
 
139
                true = ets:insert(wx_non_consts, List)
 
140
        end,
 
141
        {ok, #state{cb_port=Port, driver=DriverName, users=gb_sets:empty()}}
 
142
    catch _:Err ->
 
143
            error({Err, "Could not initiate graphics"})
138
144
    end.
139
145
 
140
146
%%--------------------------------------------------------------------
206
212
 
207
213
%%%%%%%%%%%% INTERNAL %%%%%%%%%%%%%%%%%%%%%%%%
208
214
 
209
 
%% If you want anything done, do it yourself. 
210
 
 
211
 
priv_dir() ->
212
 
    Type = erlang:system_info(system_architecture),
213
 
    {file, Path} = code:is_loaded(?MODULE),
214
 
    Priv = case filelib:is_regular(Path) of
215
 
               true ->
216
 
                   Beam = filename:join(["ebin/",atom_to_list(?MODULE) ++ ".beam"]),
217
 
                   filename:join(strip(Path, Beam), "priv");
218
 
               false ->
219
 
                   code:priv_dir(wx)
220
 
           end,
221
 
    try 
222
 
        {ok, Dirs0} = file:list_dir(Priv),
223
 
        Dirs1 = split_dirs(Dirs0),
224
 
        Dirs  = lists:reverse(lists:sort(Dirs1)),    
225
 
        
226
 
        Best = best_dir(hd(split_dirs([Type])),Dirs, Priv),
227
 
        filename:join(Priv, Best)
228
 
    catch _:_ ->
229
 
            error_logger:format("WX ERROR: Could not find suitable \'~s\' for ~s in: ~s~n", 
230
 
                                [?DRIVER, Type, Priv]),
231
 
            erlang:error({load_driver, "No driver found"})
232
 
    end.
233
 
    
234
 
best_dir(Dir, Dirs0, Priv) ->
235
 
    Dirs = [{D,D} || D <- Dirs0],
236
 
    best_dir(Dir, Dirs, [], Priv).
237
 
 
238
 
best_dir(Pre, [{[],_}|R], Acc, Priv) -> %% Empty skip'em
239
 
    best_dir(Pre, R, Acc, Priv);
240
 
best_dir(Pre, [{Pre,Dir}|R], Acc, Priv) -> 
241
 
    Real = dir_app(lists:reverse(Dir)),
242
 
    case file:list_dir(filename:join(Priv,Real)) of
243
 
        {ok, Fs} ->
244
 
            case lists:any(fun(File) -> filename:rootname(File) =:= ?DRIVER end, Fs) of
245
 
                true ->  Real; %% Found dir and it contains a driver
246
 
                false -> best_dir(Pre, R, Acc, Priv)
247
 
            end;
248
 
        _ ->
249
 
            best_dir(Pre, R, Acc, Priv)
250
 
    end;
251
 
best_dir(Pre, [{[_|F],Dir}|R], Acc, Priv) ->
252
 
    best_dir(Pre, R, [{F,Dir}|Acc], Priv);
253
 
best_dir(_Pre, [], [],_) -> throw(no_dir);  %% Nothing found
254
 
best_dir([_|Pre], [], Acc, Priv) ->
255
 
    best_dir(Pre, lists:reverse(Acc), [], Priv);
256
 
best_dir([], _, _,_) -> throw(no_dir).  %% Nothing found
257
 
 
258
 
split_dirs(Dirs0) ->
259
 
    ToInt = fun(Str) ->
260
 
                    try 
261
 
                        list_to_integer(Str)
262
 
                    catch _:_ -> Str
263
 
                    end
264
 
            end,
265
 
    Split = fun(Dir) ->
266
 
                    Toks = tokens(Dir,".-"),
267
 
                    lists:reverse([ToInt(Str) || Str <- Toks])
268
 
            end,
269
 
    lists:map(Split,Dirs0).
270
 
 
271
 
dir_app([]) -> [];
272
 
dir_app([Dir]) -> Dir;
273
 
dir_app(Dir) ->
274
 
    dir_app2(Dir).
275
 
dir_app2([Int]) when is_integer(Int) ->
276
 
    integer_to_list(Int);
277
 
dir_app2([Str]) when is_list(Str) ->
278
 
    Str;
279
 
dir_app2([Head|Rest]) when is_integer(Head) ->
280
 
    integer_to_list(Head) ++ dir_app2(Rest);
281
 
dir_app2([Head|Rest]) when is_list(Head) ->
282
 
    Head ++ dir_app2(Rest).
283
 
    
284
 
strip(Src, Src) ->
285
 
    [];
286
 
strip([H|R], Src) ->
287
 
    [H| strip(R, Src)].
288
 
 
289
 
 
290
215
debug_ping(Port) ->
291
216
    timer:sleep(1*333),    
292
217
    _R = (catch erlang:port_call(Port, 0, [])),
293
218
%%    io:format("Erlang ping ~p ~n", [_R]),
294
219
    debug_ping(Port).
295
220
 
296
 
tokens(S,Seps) ->
297
 
    tokens1(S, Seps, []).
298
 
 
299
 
tokens1([C|S], Seps, Toks) ->
300
 
    case lists:member(C, Seps) of
301
 
        true -> tokens1(S, Seps, [[C]|Toks]);
302
 
        false -> tokens2(S, Seps, Toks, [C])
303
 
    end;
304
 
tokens1([], _Seps, Toks) ->
305
 
    lists:reverse(Toks).
306
 
 
307
 
tokens2([C|S], Seps, Toks, Cs) ->
308
 
    case lists:member(C, Seps) of
309
 
        true -> tokens1(S, Seps, [[C], lists:reverse(Cs) |Toks]);
310
 
        false -> tokens2(S, Seps, Toks, [C|Cs])
311
 
    end;
312
 
tokens2([], _Seps, Toks, Cs) ->
313
 
    lists:reverse([lists:reverse(Cs)|Toks]).