~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%%-------------------------------------------------------------------
 
19
%%% File    : wxe_util.erl
 
20
%%% Author  : Dan Gudmundsson <dgud@erix.ericsson.se>
 
21
%%% Description : 
 
22
%%%
 
23
%%% Created :  9 Feb 2007 by Dan Gudmundsson <dgud@erix.ericsson.se>
 
24
%%%-------------------------------------------------------------------
 
25
%% @hidden
 
26
-module(wxe_util).
 
27
 
 
28
-export([call/2,cast/2,construct/2,
 
29
         destroy/2, register_pid/1,
 
30
         connect_cb/2,disconnect_cb/2,
 
31
         send_bin/1, get_cbId/1,
 
32
         get_const/1,colour_bin/1,datetime_bin/1,
 
33
         to_bool/1,from_bool/1]).
 
34
 
 
35
-include("wxe.hrl").
 
36
 
 
37
 
 
38
to_bool(0) -> false;
 
39
to_bool(_) -> true.
 
40
 
 
41
from_bool(true) -> 1;
 
42
from_bool(false) -> 0.
 
43
 
 
44
colour_bin({R,G,B}) ->
 
45
    <<R:32/?UI,G:32/?UI, B:32/?UI,255:32/?UI>>;
 
46
colour_bin({R,G,B,A}) ->
 
47
    <<R:32/?UI,G:32/?UI, B:32/?UI,A:32/?UI>>.
 
48
 
 
49
datetime_bin({{Y,Mo,D},{H,Mi,S}}) ->
 
50
    %% DMY fits wxDaytime constructor
 
51
    %% Also wxDaytime:Month is enum from zero
 
52
    <<D:32/?UI,(Mo-1):32/?UI,Y:32/?UI,H:32/?UI,Mi:32/?UI,S:32/?UI>>.
 
53
 
 
54
get_const(Id) ->
 
55
    [{Id, Data}] = ets:lookup(wx_non_consts, Id),
 
56
    Data.
 
57
 
 
58
cast(Op,Args) ->
 
59
    #wx_env{port=Port,debug=Dbg} = wx:get_env(),
 
60
    erlang:port_control(Port,Op,Args),
 
61
    case Dbg > 0 of
 
62
        true ->  debug_cast(Dbg band 15, Op,Args,Port);
 
63
        false -> ok
 
64
    end,
 
65
    ok.
 
66
 
 
67
call(Op, Args) ->
 
68
    #wx_env{port=Port,debug=Dbg} = wx:get_env(),
 
69
    case Dbg > 0 of
 
70
        false ->            
 
71
            erlang:port_control(Port,Op,Args),
 
72
            rec(Op);
 
73
        true ->
 
74
            debug_call(Dbg band 15, Op, Args, Port)
 
75
    end.
 
76
            
 
77
rec(Op) ->
 
78
    receive 
 
79
        {'_wxe_result_', Res} -> Res;
 
80
        {'_wxe_error_', Op, Error} -> 
 
81
            [{_,MF}] = ets:lookup(wx_debug_info,Op),
 
82
            erlang:error({Error, MF});
 
83
        {'_wxe_error_', Old, Error} -> 
 
84
            [{_,MF}] = ets:lookup(wx_debug_info,Old),
 
85
            erlang:exit({Error, MF})
 
86
    end.
 
87
 
 
88
construct(Op, Args) ->
 
89
    call(Op,Args).
 
90
 
 
91
destroy(Op, #wx_ref{ref=Ref}) -> 
 
92
    cast(Op,<<Ref:32/?UI>>).
 
93
 
 
94
register_pid(#wx_ref{ref=Ref}) ->
 
95
    send_bin(term_to_binary(self())),
 
96
    call(?WXE_REGISTER_OBJECT, <<Ref:32/?UI>>).
 
97
   
 
98
send_bin(Bin) when is_binary(Bin) ->    
 
99
    #wx_env{port=Port,debug=Dbg} = wx:get_env(),
 
100
    case Dbg > 0 of
 
101
        false ->            
 
102
            erlang:port_command(Port, Bin);
 
103
        true ->
 
104
            io:format("WX binary ~p(~p) ~n",[self(), Port]),
 
105
            erlang:port_command(Port, Bin)
 
106
    end.
 
107
 
 
108
get_cbId(Fun) ->
 
109
    gen_server:call((wx:get_env())#wx_env.sv,{register_cb, Fun}).   
 
110
 
 
111
connect_cb(Object,EvData) ->
 
112
    handle_listener(connect_cb, Object, EvData).
 
113
 
 
114
disconnect_cb(Object,EvData) ->
 
115
    handle_listener(disconnect_cb, Object, EvData).
 
116
 
 
117
handle_listener(Op,Object,EvData) ->
 
118
    Listener = gen_server:call((wx:get_env())#wx_env.sv, {Op,Object,EvData}),
 
119
    case Listener of
 
120
        {call_impl, connect_cb, EvtList} ->
 
121
            wxEvtHandler:connect_impl(EvtList,Object,EvData);
 
122
        Res ->
 
123
            Res
 
124
    end.
 
125
 
 
126
debug_cast(1, Op, _Args, _Port) ->
 
127
    check_previous(),
 
128
    case ets:lookup(wx_debug_info,Op) of
 
129
        [{_,{M,F,_}}] ->
 
130
            io:format("WX ~p: ~s:~s(~p) -> ok~n", [self(),M,F,Op]);
 
131
        [] -> 
 
132
            io:format("WX ~p: unknown(~p) -> ok~n", [self(),Op])
 
133
    end;
 
134
debug_cast(2, Op, Args, Port) ->
 
135
    check_previous(),
 
136
    case ets:lookup(wx_debug_info,Op) of
 
137
        [{_,{M,F,_}}] ->
 
138
            io:format("WX ~p(~p): ~s:~s(~p) (~p) -> ok~n", 
 
139
                      [self(),Port,M,F,Op,Args]);
 
140
        [] ->
 
141
            io:format("WX ~p(~p): unknown(~p) (~p) -> ok~n", 
 
142
                      [self(),Port,Op,Args])
 
143
    end;
 
144
debug_cast(_, _Op, _Args, _Port) ->
 
145
    check_previous(),
 
146
    ok.
 
147
 
 
148
debug_call(1, Op, Args, Port) ->
 
149
    check_previous(),
 
150
    case ets:lookup(wx_debug_info,Op) of
 
151
        [{_,{M,F,_}}] ->
 
152
            io:format("WX ~p: ~s:~s(~p) -> ",[self(),M,F,Op]);
 
153
        [] ->
 
154
            io:format("WX ~p: unknown(~p) -> ",[self(),Op])
 
155
    end,
 
156
    erlang:port_control(Port,Op,Args),    
 
157
    debug_rec(1);
 
158
 
 
159
debug_call(2, Op, Args, Port) ->
 
160
    check_previous(),
 
161
    case ets:lookup(wx_debug_info,Op) of
 
162
        [{_,{M,F,_}}] ->
 
163
            io:format("WX ~p(~p): ~s:~s(~p) (~p) -> ",
 
164
                      [self(), Port, M, F, Op, Args]);
 
165
        [] -> 
 
166
            io:format("WX ~p(~p): unknown(~p) (~p) -> ",
 
167
                      [self(), Port, Op, Args])
 
168
    end,
 
169
    erlang:port_control(Port,Op,Args),
 
170
    debug_rec(2);
 
171
debug_call(_, Op, Args, Port) ->
 
172
    check_previous(),
 
173
    erlang:port_control(Port,Op,Args),
 
174
    rec(Op).
 
175
 
 
176
    
 
177
 
 
178
debug_rec(1) ->
 
179
    receive 
 
180
        {'_wxe_result_', Res} -> 
 
181
            io:format("complete ~n", []),
 
182
            Res;
 
183
        {'_wxe_error_', Op2, Error} -> 
 
184
            [{_,MF2}] = ets:lookup(wx_debug_info,Op2),
 
185
            erlang:error({Error, MF2})
 
186
    end;
 
187
debug_rec(2) ->
 
188
    receive 
 
189
        {'_wxe_result_', Res} -> 
 
190
            io:format("~p ~n", [Res]),
 
191
            Res;
 
192
        {'_wxe_error_', Op, Error} -> 
 
193
            io:format("Error ~p ~n", [Error]),
 
194
            [{_,MF}] = ets:lookup(wx_debug_info,Op),
 
195
            erlang:error({Error, MF})
 
196
    end.
 
197
 
 
198
check_previous() ->
 
199
    receive 
 
200
        {'_wxe_error_', Op, Error} -> 
 
201
            [{_,MF={M,F,_}}] = ets:lookup(wx_debug_info,Op),
 
202
            io:format("WX ~p: ERROR in previous command ~s:~s~n",[self(), M,F]),
 
203
            erlang:error({Error, MF})    
 
204
    after 0 -> ok
 
205
    end.