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

« back to all changes in this revision

Viewing changes to lib/cosNotification/test/notify_test_impl.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
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1999-2010. 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
%%
 
20
%%----------------------------------------------------------------------
 
21
%% File    : notify_test_impl.erl
 
22
%%----------------------------------------------------------------------
 
23
 
 
24
-module(notify_test_impl).
 
25
 
 
26
-include_lib("orber/include/corba.hrl").
 
27
-include("idl_output/notify_test.hrl").
 
28
 
 
29
%%--------------- specified functions ------------------------
 
30
-export([stop_normal/2, 
 
31
         stop_brutal/2, 
 
32
         print/2, 
 
33
         doAction/3,
 
34
         delay/5,
 
35
         %% Exports from CosNotifyComm::StructuredPushConsumer
 
36
         push_structured_event/3, disconnect_structured_push_consumer/2,
 
37
         %% Exports from "CosNotifyComm::SequencePushConsumer"
 
38
         push_structured_events/3, disconnect_sequence_push_consumer/2,
 
39
         %% Exports from CosEventComm::PushConsumer
 
40
         push/3, disconnect_push_consumer/2,
 
41
         %% Exports from CosNotifyComm::NotifyPublish
 
42
         disconnect_sequence_pull_consumer/2,
 
43
         %% Exports from CosNotifyComm::StructuredPullConsumer
 
44
         disconnect_structured_pull_consumer/2,
 
45
         %% Exports from CosEventComm::PullConsumer
 
46
         disconnect_pull_consumer/2,
 
47
         %% Exports from CosNotifyComm::SequencePushSupplier
 
48
         disconnect_sequence_push_supplier/2,
 
49
         %% Exports from CosNotifyComm::StructuredPushSupplier
 
50
         disconnect_structured_push_supplier/2,
 
51
         %% Exports from CosEventComm::PushSupplier
 
52
         disconnect_push_supplier/2,
 
53
         %% Exports from CosNotifyComm::SequencePullSupplier
 
54
         pull_structured_events/3, 
 
55
         try_pull_structured_events/3, 
 
56
         disconnect_sequence_pull_supplier/2,
 
57
         %% Exports from CosNotifyComm::StructuredPullSupplier
 
58
         pull_structured_event/2, 
 
59
         try_pull_structured_event/2, 
 
60
         disconnect_structured_pull_supplier/2,
 
61
         %% Exports from CosEventComm::PullSupplier
 
62
         pull/2, 
 
63
         try_pull/2, 
 
64
         disconnect_pull_supplier/2,
 
65
         %% Exports from CosNotifyComm::SequencePullConsumer
 
66
         offer_change/4,
 
67
         %% Exports from CosNotifyComm::NotifySubscribe
 
68
         subscription_change/4]).
 
69
 
 
70
%%--------------- gen_server specific ------------------------
 
71
-export([init/1, terminate/2]).
 
72
-export([handle_call/3, handle_cast/2, handle_info/2, code_change/3]).
 
73
%% Data structures
 
74
-record(state, {myType, proxy, data, action}).
 
75
 
 
76
%%--------------- LOCAL DATA ---------------------------------
 
77
 
 
78
%%------------------------------------------------------------
 
79
%% function : init, terminate
 
80
%%------------------------------------------------------------
 
81
init([MyType, Proxy]) ->
 
82
    process_flag(trap_exit,true),
 
83
    {ok, #state{myType=MyType, proxy=Proxy, data=[]}}.
 
84
 
 
85
terminate(Reason, State) ->
 
86
    io:format("notify_test:terminate(~p  ~p)~n",[Reason, State#state.myType]),
 
87
    ok.
 
88
 
 
89
code_change(_OldVsn, State, _Extra) ->
 
90
    {ok, State}.
 
91
handle_call(_,_, State) ->
 
92
    {noreply, State}.
 
93
handle_cast(_, State) ->
 
94
    {noreply, State}.
 
95
handle_info(_Info, State) ->
 
96
    {noreply, State}.
 
97
 
 
98
%%--------------- SERVER FUNCTIONS ---------------------------
 
99
 
 
100
print(Self, State) ->
 
101
    io:format("notify_test:print(~p  ~p)~n",[Self, State]),
 
102
    {reply, ok, State}.
 
103
 
 
104
doAction(_Self, State, {set_data, Data}) ->
 
105
    io:format("notify_test:doAction(add_data)  ~p~n",[Data]),
 
106
    {reply, ok, State#state{data=Data}};
 
107
doAction(_Self, State, {add_data, Data}) ->
 
108
    io:format("notify_test:doAction(add_data)  ~p~n",[Data]),
 
109
    {reply, ok, State#state{data=State#state.data++Data}};
 
110
doAction(_Self, State, return_data) ->
 
111
    io:format("notify_test:doAction(return_data)~n",[]),
 
112
    {reply, State#state.data, State#state{data=[]}};
 
113
doAction(_Self, State, clear_data) ->
 
114
    io:format("notify_test:doAction(return_data)~n",[]),
 
115
    {reply, ok, State#state{data=[]}};
 
116
doAction(_Self, State, pull_any) ->
 
117
    io:format("notify_test:doAction(pull_any)~n",[]),
 
118
    Event='CosNotifyChannelAdmin_ProxyPullSupplier':pull(State#state.proxy),
 
119
    {reply, Event, State};
 
120
doAction(_Self, State, {pull_seq, Max}) ->
 
121
    io:format("notify_test:doAction(pull_sequence)~n",[]),
 
122
    Event='CosNotifyChannelAdmin_SequenceProxyPullSupplier':pull_structured_events(State#state.proxy, Max),
 
123
    {reply, Event, State};
 
124
doAction(_Self, State, pull_str) ->
 
125
    Event='CosNotifyChannelAdmin_StructuredProxyPullSupplier':pull_structured_event(State#state.proxy),
 
126
    io:format("notify_test:doAction(pull_structured)~n",[]),
 
127
    {reply, Event, State};
 
128
doAction(_Self, State, try_pull_any) ->
 
129
    io:format("notify_test:doAction(try_pull_any)~n",[]),
 
130
    Event='CosNotifyChannelAdmin_ProxyPullSupplier':try_pull(State#state.proxy),
 
131
    {reply, Event, State};
 
132
doAction(_Self, State, {try_pull_seq, Max}) ->
 
133
    io:format("notify_test:doAction(try_pull_sequence)~n",[]),
 
134
    Event='CosNotifyChannelAdmin_SequenceProxyPullSupplier':try_pull_structured_events(State#state.proxy, Max),
 
135
    {reply, Event, State};
 
136
doAction(_Self, State, try_pull_str) ->
 
137
    Event='CosNotifyChannelAdmin_StructuredProxyPullSupplier':try_pull_structured_event(State#state.proxy),
 
138
    io:format("notify_test:doAction(try_pull_structured)~n",[]),
 
139
    {reply, Event, State};
 
140
doAction(_Self, State, {action, Action}) ->
 
141
    io:format("notify_test:doAction(~p)~n",[Action]),
 
142
    {reply, ok, State#state{action = Action}};
 
143
 
 
144
doAction(_, State, _) ->
 
145
    {reply, nop, State}.
 
146
 
 
147
stop_normal(_Self, State) ->
 
148
    {stop, normal, ok, State}.
 
149
 
 
150
stop_brutal(_Self, _State) ->
 
151
    exit("killed_brutal").
 
152
 
 
153
 
 
154
 
 
155
%%--------------- CosNotifyComm::NotifyPublish --------
 
156
offer_change(_Self, State, Added, Removed) ->
 
157
    ND=loop(Removed, State#state.data),
 
158
    ND2=Added++ND,
 
159
    {reply, ok, State#state{data=ND2}}.
 
160
 
 
161
loop([],Data) ->
 
162
    Data;
 
163
loop([H|T], Data) ->
 
164
    ND=lists:delete(H,Data),
 
165
    loop(T, ND).
 
166
 
 
167
%%--------------- CosNotifyComm::NotifySubscribe --------
 
168
subscription_change(_Self, State, Added, Removed) ->
 
169
    ND=loop(Removed, State#state.data),
 
170
    ND2=Added++ND,
 
171
    {reply, ok, State#state{data=ND2}}.
 
172
 
 
173
%%--------------- CosNotifyComm::SequencePushConsumer --------
 
174
push_structured_events(_Self, #state{action = undefined} = State, Event) ->
 
175
    io:format("notify_test:push_structured_events(~p)~n",[Event]),
 
176
    {reply, ok, State#state{data=State#state.data++Event}};
 
177
push_structured_events(_Self, #state{action = Action} = State, Event) ->
 
178
    io:format("notify_test:push_structured_events(~p)~nAction: ~p~n",
 
179
              [Event, Action]),
 
180
    corba:raise(#'INTERNAL'{completion_status=?COMPLETED_NO}),
 
181
    {reply, ok, State#state{data=State#state.data++Event}}.
 
182
disconnect_sequence_push_consumer(_Self, State) ->
 
183
    io:format("disconnect_sequence_push_consumer~n",[]),
 
184
    {stop, normal, ok, State}.
 
185
 
 
186
%%--------------- CosNotifyComm::StructuredPushConsumer --------
 
187
push_structured_event(_Self, State, Event) ->
 
188
    io:format("notify_test:push_structured_event(~p)~n",[Event]),
 
189
    {reply, ok, State#state{data=State#state.data++[Event]}}.
 
190
disconnect_structured_push_consumer(_Self, State) ->
 
191
    io:format("disconnect_structured_push_consumer~n",[]),
 
192
    {stop, normal, ok, State}.
 
193
 
 
194
%%--------------- CosEventComm::PushConsumer --------
 
195
push(_Self, State, Event) ->
 
196
    io:format("notify_test:push(~p)~n",[Event]),
 
197
    {reply, ok, State#state{data=State#state.data++[Event]}}.
 
198
disconnect_push_consumer(_Self, State) ->
 
199
    io:format("disconnect_push_consumer~n",[]),
 
200
    {stop, normal, ok, State}.
 
201
 
 
202
%%--------------- CosNotifyComm::SequencePullConsumer --------
 
203
disconnect_sequence_pull_consumer(_Self, State) ->
 
204
    io:format("disconnect_sequence_pull_consumer~n",[]),
 
205
    {stop, normal, ok, State}.
 
206
 
 
207
%%--------------- CosNotifyComm::StructuredPullConsumer --------
 
208
disconnect_structured_pull_consumer(_Self, State) ->
 
209
    io:format("disconnect_structured_pull_consumer~n",[]),
 
210
    {stop, normal, ok, State}.
 
211
 
 
212
%%--------------- CosEventComm::PullConsumer --------
 
213
disconnect_pull_consumer(_Self, State) ->
 
214
    io:format("disconnect_pull_consumer~n",[]),
 
215
    {stop, normal, ok, State}.
 
216
 
 
217
%%--------------- CosNotifyComm::SequencePushSupplier --------
 
218
disconnect_sequence_push_supplier(_Self, State) ->
 
219
    io:format("disconnect_sequence_push_supplier~n",[]),
 
220
    {stop, normal, ok, State}.
 
221
 
 
222
%%--------------- CosNotifyComm::StructuredPushSupplier --------
 
223
disconnect_structured_push_supplier(_Self, State) ->
 
224
    io:format("disconnect_structured_push_supplier~n",[]),
 
225
    {stop, normal, ok, State}.
 
226
 
 
227
%%--------------- CosEventComm::PushSupplier --------
 
228
disconnect_push_supplier(_Self, State) ->
 
229
    io:format("disconnect_push_supplier~n",[]),
 
230
    {stop, normal, ok, State}.
 
231
 
 
232
%%--------------- CosNotifyComm::SequencePullSupplier --------
 
233
pull_structured_events(_Self, State, _Max) ->
 
234
    io:format("notify_test:pullstructured_events()~n",[]),
 
235
    {reply, ok, State}.
 
236
try_pull_structured_events(_Self, State, Max) ->
 
237
    io:format("notify_test:try_pull_structured_events()~n",[]),
 
238
    case State#state.data of
 
239
        [] ->
 
240
            {reply, {[],false}, State};
 
241
        List ->
 
242
            R = split(List,Max),
 
243
            {reply, {lists:sublist(List, Max), true}, State#state{data=R}}
 
244
    end.
 
245
 
 
246
split([],_) ->
 
247
    [];
 
248
split(R,0) ->
 
249
    R;
 
250
split([_H|T],Max) ->
 
251
    split(T, Max-1).
 
252
 
 
253
disconnect_sequence_pull_supplier(_Self, State) ->
 
254
    io:format("disconnect_sequence_pull_supplier~n",[]),
 
255
    {stop, normal, ok, State}.
 
256
 
 
257
%%--------------- CosNotifyComm::StructuredPullSupplier --------
 
258
pull_structured_event(_Self, State) ->
 
259
    io:format("notify_test:pull_structured_event()~n",[]),
 
260
    {reply, ok, State}.
 
261
try_pull_structured_event(_Self, State) ->
 
262
    io:format("notify_test:try_pull_structured_event()~n",[]),
 
263
    case State#state.data of
 
264
        [] ->
 
265
            {reply, {[],false}, State};
 
266
        [H|T] ->
 
267
            {reply, {H, true}, State#state{data=T}}
 
268
    end.
 
269
disconnect_structured_pull_supplier(_Self, State) ->
 
270
    io:format("disconnect_structured_pull_supplier~n",[]),
 
271
    {stop, normal, ok, State}.
 
272
 
 
273
%%--------------- CosEventComm::PullSupplier --------
 
274
pull(_Self, State) ->
 
275
    io:format("notify_test:pull()~n",[]),
 
276
    {reply, 'CosEventComm_PullSupplier':pull(State#state.proxy), State}.
 
277
try_pull(_Self, State) ->
 
278
    io:format("notify_test:try_pull()~n",[]),
 
279
    case State#state.data of
 
280
        [] ->
 
281
            {reply, {[],false}, State};
 
282
        [H|T] ->
 
283
            {reply, {H, true}, State#state{data=T}}
 
284
    end.
 
285
disconnect_pull_supplier(_Self, State) ->
 
286
    io:format("disconnect_pull_supplier~n",[]),
 
287
    {stop, normal, ok, State}.
 
288
 
 
289
%%--------------- LOCAL FUNCTIONS ----------------------------
 
290
 
 
291
delay(Obj, Event, Time, Mod, F) ->
 
292
    io:format("notify_test:delay(~p)  TIME: ~p~n",[Event, now()]),
 
293
    timer:sleep(Time),
 
294
    Mod:F(Obj, Event),
 
295
    io:format("notify_test:delay() DONE: ~p~n",[now()]),
 
296
    ok.
 
297
 
 
298
%%--------------- END OF MODULE ------------------------------
 
299