~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/cosEvent/src/oe_CosEventComm_PusherS_impl.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
83
83
%% Returns    : any (ignored by gen_server)
84
84
%% Description: Shutdown the server
85
85
%%----------------------------------------------------------------------
86
 
terminate(Reason, #state{client = undefined}) ->
87
 
    ?DBG("Terminating ~p; no client connected.~n", [Reason]),
 
86
terminate(_Reason, #state{client = undefined}) ->
 
87
    ?DBG("Terminating ~p; no client connected.~n", [_Reason]),
88
88
    ok;
89
 
terminate(Reason, #state{client = Client} = State) ->
90
 
    ?DBG("Terminating ~p~n", [Reason]),
 
89
terminate(_Reason, #state{client = Client} = _State) ->
 
90
    ?DBG("Terminating ~p~n", [_Reason]),
91
91
    cosEventApp:disconnect('CosEventComm_PushConsumer', 
92
92
                           disconnect_push_consumer, Client),
93
93
    ok.
97
97
%% Returns    : {ok, NewState}
98
98
%% Description: Convert process state when code is changed
99
99
%%----------------------------------------------------------------------
100
 
code_change(OldVsn, State, Extra) ->
 
100
code_change(_OldVsn, State, _Extra) ->
101
101
    {ok, State}.
102
102
 
103
103
%%---------------------------------------------------------------------%
109
109
%%----------------------------------------------------------------------
110
110
handle_info({'EXIT', Pid, Reason}, #state{admin_pid = Pid} = State) ->
111
111
    ?DBG("Parent Admin terminated ~p~n", [Reason]),
112
 
    orber:debug_level_print("[~p] oe_CosEventComm_PusherS_impl:handle_info(~p); 
113
 
My Admin terminated and so will I.", [?LINE, Reason], ?DEBUG_LEVEL),
 
112
    orber:dbg("[~p] oe_CosEventComm_PusherS_impl:handle_info(~p);~n"
 
113
              "My Admin terminated and so will I.", 
 
114
              [?LINE, Reason], ?DEBUG_LEVEL),
114
115
    {stop, Reason, State};
115
 
handle_info(Info, State) ->
116
 
    ?DBG("Unknown Info ~p~n", [Info]),
 
116
handle_info(_Info, State) ->
 
117
    ?DBG("Unknown Info ~p~n", [_Info]),
117
118
    {noreply, State}.
118
119
 
119
120
%%---------------------------------------------------------------------%
122
123
%% Returns    : 
123
124
%% Description: 
124
125
%%----------------------------------------------------------------------
125
 
connect_push_consumer(OE_This, _, #state{client = undefined, 
126
 
                                      typecheck = TypeCheck} = State, NewClient) ->
 
126
connect_push_consumer(_OE_This, _, #state{client = undefined, 
 
127
                                          typecheck = TypeCheck} = State, NewClient) ->
127
128
    case corba_object:is_nil(NewClient) of
128
129
        true ->
129
 
            ?DBG("A NIL client supplied.~n", []),
130
 
            orber:debug_level_print("[~p] oe_CosEventComm_PusherS_impl:connect_push_consumer(..); 
131
 
Supplied a NIL reference which is not allowed.", [?LINE], ?DEBUG_LEVEL),
 
130
            orber:dbg("[~p] oe_CosEventComm_PusherS_impl:connect_push_consumer(..);~n"
 
131
                      "Supplied a NIL reference which is not allowed.", 
 
132
                      [?LINE], ?DEBUG_LEVEL),
132
133
            corba:raise(#'BAD_PARAM'{completion_status = ?COMPLETED_NO});
133
134
        false ->
134
135
            cosEventApp:type_check(NewClient, 'CosEventComm_PushConsumer', TypeCheck),
145
146
%% Returns    : 
146
147
%% Description: 
147
148
%%----------------------------------------------------------------------
148
 
disconnect_push_supplier(OE_This, _, State) ->
 
149
disconnect_push_supplier(_OE_This, _, State) ->
149
150
    ?DBG("Disconnect invoked ~p ~n", [State]),
150
151
    {stop, normal, ok, State#state{client = undefined}}.
151
152
 
158
159
%% Returns    : 
159
160
%% Description: 
160
161
%%----------------------------------------------------------------------
161
 
send(OE_This, #state{client = undefined} = State, Any) ->
 
162
send(_OE_This, #state{client = undefined} = State, _Any) ->
162
163
    %% No consumer connected.
163
 
    ?DBG("Received event ~p but have no client.~n", [Any]),
 
164
    ?DBG("Received event ~p but have no client.~n", [_Any]),
164
165
    {noreply, State};
165
 
send(OE_This, #state{client = Client} = State, Any) ->
 
166
send(_OE_This, #state{client = Client} = State, Any) ->
166
167
    %% Push Data
167
168
    case catch 'CosEventComm_PushConsumer':push(Client, Any) of
168
169
        ok ->
173
174
            {stop, normal, State#state{client = undefined}};
174
175
        Other ->
175
176
            ?DBG("Received event ~p but failed to deliver it to client.~n", [Any]),
176
 
            orber:debug_level_print("[~p] oe_CosEventComm_PusherS_impl:send(~p); 
177
 
My Client behaves badly, returned ~p, so I will terminate.", 
178
 
                                    [?LINE, Any, Other], ?DEBUG_LEVEL),
 
177
            orber:dbg("[~p] oe_CosEventComm_PusherS_impl:send(~p);~n"
 
178
                      "My Client behaves badly, returned ~p, so I will terminate.", 
 
179
                      [?LINE, Any, Other], ?DEBUG_LEVEL),
179
180
            {stop, normal, State}
180
181
    end.
181
182
 
186
187
%% Returns    : 
187
188
%% Description: 
188
189
%%----------------------------------------------------------------------
189
 
send_sync(OE_This, OE_From, #state{client = undefined} = State, Any) ->
 
190
send_sync(_OE_This, _OE_From, #state{client = undefined} = State, _Any) ->
190
191
    %% No consumer connected.
191
 
    ?DBG("Received event ~p but have no client.~n", [Any]),
 
192
    ?DBG("Received event ~p but have no client.~n", [_Any]),
192
193
    {reply, ok, State};
193
 
send_sync(OE_This, OE_From, #state{client = Client} = State, Any) ->
 
194
send_sync(_OE_This, OE_From, #state{client = Client} = State, Any) ->
194
195
    corba:reply(OE_From, ok),
195
196
    %% Push Data
196
197
    case catch 'CosEventComm_PushConsumer':push(Client, Any) of
202
203
            {stop, normal, State#state{client = undefined}};
203
204
        Other ->
204
205
            ?DBG("Received event ~p but failed to deliver (sync) it to client.~n", [Any]),
205
 
            orber:debug_level_print("[~p] oe_CosEventComm_PusherS_impl:send_sync(~p); 
206
 
My Client behaves badly, returned ~p, so I will terminate.", 
207
 
                                    [?LINE, Any, Other], ?DEBUG_LEVEL),
 
206
            orber:dbg("[~p] oe_CosEventComm_PusherS_impl:send_sync(~p);~n"
 
207
                      "My Client behaves badly, returned ~p, so I will terminate.", 
 
208
                      [?LINE, Any, Other], ?DEBUG_LEVEL),
208
209
            {stop, normal, State}
209
210
    end.
210
211