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

« back to all changes in this revision

Viewing changes to lib/cosEvent/src/oe_CosEventComm_CAdmin_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:
81
81
%% Returns    : any (ignored by gen_server)
82
82
%% Description: Shutdown the server
83
83
%%----------------------------------------------------------------------
84
 
terminate(Reason, State) ->
85
 
    ?DBG("Terminating ~p~n", [Reason]),
 
84
terminate(_Reason, _State) ->
 
85
    ?DBG("Terminating ~p~n", [_Reason]),
86
86
    ok.
87
87
 
88
88
%%----------------------------------------------------------------------
90
90
%% Returns    : {ok, NewState}
91
91
%% Description: Convert process state when code is changed
92
92
%%----------------------------------------------------------------------
93
 
code_change(OldVsn, State, Extra) ->
 
93
code_change(_OldVsn, State, _Extra) ->
94
94
    {ok, State}.
95
95
 
96
96
%%---------------------------------------------------------------------%
102
102
%%----------------------------------------------------------------------
103
103
handle_info({'EXIT', Pid, Reason}, #state{channel_pid = Pid} = State) ->
104
104
    ?DBG("Parent Channel terminated ~p~n", [Reason]),
105
 
    orber:debug_level_print("[~p] oe_CosEventComm_PullerS_impl:handle_info(~p); 
106
 
My Channel terminated and so will I which will cause my children to do the same thing.", 
107
 
                            [?LINE, Reason], ?DEBUG_LEVEL),
 
105
    orber:dbg("[~p] oe_CosEventComm_PullerS_impl:handle_info(~p);~n"
 
106
              "My Channel terminated and so will I which will cause"
 
107
              " my children to do the same thing.", 
 
108
              [?LINE, Reason], ?DEBUG_LEVEL),
108
109
    {stop, Reason, State};
109
 
handle_info({'EXIT', Pid, Reason}, #state{proxies = Proxies} = State) ->
 
110
handle_info({'EXIT', Pid, _Reason}, #state{proxies = Proxies} = State) ->
110
111
    %% A child terminated which is normal. Hence, no logging.
111
 
    ?DBG("Probably a child terminated ~p~n", [Reason]),
 
112
    ?DBG("Probably a child terminated ~p~n", [_Reason]),
112
113
    {noreply, State#state{proxies = lists:keydelete(Pid, 2, Proxies)}};
113
 
handle_info(Info, State) ->
114
 
    ?DBG("Unknown Info ~p~n", [Info]),
 
114
handle_info(_Info, State) ->
 
115
    ?DBG("Unknown Info ~p~n", [_Info]),
115
116
    {noreply, State}.
116
117
 
117
118
%%----------------------------------------------------------------------
128
129
            ?DBG("Started a new oe_CosEventComm_PusherS.~n", []),
129
130
            {reply, Proxy, State#state{proxies = [{Proxy, Pid}|State#state.proxies]}};
130
131
        Other ->
131
 
            orber:debug_level_print("[~p] oe_CosEventComm_CAdmin:obtain_push_supplier(); Error: ~p", 
132
 
                                    [?LINE, Other], ?DEBUG_LEVEL),
 
132
            orber:dbg("[~p] oe_CosEventComm_CAdmin:obtain_push_supplier();~nError: ~p", 
 
133
                      [?LINE, Other], ?DEBUG_LEVEL),
133
134
            corba:raise(#'INTERNAL'{completion_status=?COMPLETED_NO})
134
135
    end.
135
136
 
148
149
            ?DBG("Started a new oe_CosEventComm_PullerS.~n", []),
149
150
            {reply, Proxy, State#state{proxies = [{Proxy, Pid}|State#state.proxies]}};
150
151
        Other ->
151
 
            orber:debug_level_print("[~p] oe_CosEventComm_CAdmin:obtain_pull_supplier(); Error: ~p", 
152
 
                                    [?LINE, Other], ?DEBUG_LEVEL),
 
152
            orber:dbg("[~p] oe_CosEventComm_CAdmin:obtain_pull_supplier();~nError: ~p", 
 
153
                      [?LINE, Other], ?DEBUG_LEVEL),
153
154
            corba:raise(#'INTERNAL'{completion_status=?COMPLETED_NO})
154
155
    end.
155
156
 
204
205
        ok ->
205
206
            send_helper(T, Event, Dropped, false);
206
207
        What ->
207
 
            orber:debug_level_print("[~p] oe_CosEventComm_CAdmin:send_helper(~p, ~p); 
208
 
Bad return value ~p. Closing connection.", 
209
 
                                    [?LINE, ObjRef, Event, What], ?DEBUG_LEVEL),
 
208
            orber:dbg("[~p] oe_CosEventComm_CAdmin:send_helper(~p, ~p);~n"
 
209
                      "Bad return value ~p. Closing connection.", 
 
210
                      [?LINE, ObjRef, Event, What], ?DEBUG_LEVEL),
210
211
            send_helper(T, Event, [{ObjRef, Pid}|Dropped], false)
211
212
    end;
212
213
send_helper([{ObjRef, Pid}|T], Event, Dropped, Sync) ->
214
215
        ok ->
215
216
            send_helper(T, Event, Dropped, Sync);
216
217
        What ->
217
 
            orber:debug_level_print("[~p] oe_CosEventComm_CAdmin:send_helper(~p, ~p); 
218
 
Bad return value ~p. Closing connection.", 
219
 
                                    [?LINE, ObjRef, Event, What], ?DEBUG_LEVEL),
 
218
            orber:dbg("[~p] oe_CosEventComm_CAdmin:send_helper(~p, ~p);~n"
 
219
                      "Bad return value ~p. Closing connection.", 
 
220
                      [?LINE, ObjRef, Event, What], ?DEBUG_LEVEL),
220
221
            send_helper(T, Event, [{ObjRef, Pid}|Dropped], Sync)
221
222
    end.
222
223