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

« back to all changes in this revision

Viewing changes to lib/cosEvent/src/CosEventChannelAdmin_ProxyPullConsumer_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:
84
84
%% Returns    : any (ignored by gen_server)
85
85
%% Description: Shutdown the server
86
86
%%----------------------------------------------------------------------
87
 
terminate(Reason, #state{client = undefined}) ->
88
 
    ?DBG("Terminating ~p; no client connected.~n", [Reason]),
 
87
terminate(_Reason, #state{client = undefined}) ->
 
88
    ?DBG("Terminating ~p; no client connected.~n", [_Reason]),
89
89
    ok;
90
 
terminate(Reason, #state{client = Client} = State) ->
 
90
terminate(_Reason, #state{client = Client} = State) ->
91
91
    stop_timer(State),
92
 
    ?DBG("Terminating ~p~n", [Reason]),
 
92
    ?DBG("Terminating ~p~n", [_Reason]),
93
93
    cosEventApp:disconnect('CosEventComm_PullSupplier', 
94
94
                           disconnect_pull_supplier, Client),
95
95
    ok.
99
99
%% Returns    : {ok, NewState}
100
100
%% Description: Convert process state when code is changed
101
101
%%----------------------------------------------------------------------
102
 
code_change(OldVsn, State, Extra) ->
 
102
code_change(_OldVsn, State, _Extra) ->
103
103
    {ok, State}.
104
104
 
105
105
%%---------------------------------------------------------------------%
111
111
%%----------------------------------------------------------------------
112
112
handle_info({'EXIT', Pid, Reason}, #state{admin_pid = Pid} = State) ->
113
113
    ?DBG("Parent Admin terminated ~p~n", [Reason]),
114
 
    orber:debug_level_print("[~p] CosEventChannelAdmin_ProxyPullConsumer:handle_info(~p); 
115
 
My Admin terminated and so will I.", [?LINE, Reason], ?DEBUG_LEVEL),
 
114
    orber:dbg("[~p] CosEventChannelAdmin_ProxyPullConsumer:handle_info(~p);~n"
 
115
              "My Admin terminated and so will I.", [?LINE, Reason], ?DEBUG_LEVEL),
116
116
    {stop, Reason, State};
117
117
handle_info(try_pull_event, State) ->
118
118
    try_pull_event(State);
119
 
handle_info(Info, State) ->
120
 
    ?DBG("Unknown Info ~p~n", [Info]),
 
119
handle_info(_Info, State) ->
 
120
    ?DBG("Unknown Info ~p~n", [_Info]),
121
121
    {noreply, State}.
122
122
 
123
123
%%----------------------------------------------------------------------
126
126
%% Returns    : 
127
127
%% Description: 
128
128
%%----------------------------------------------------------------------
129
 
connect_pull_supplier(OE_This, #state{client = undefined, 
130
 
                                         typecheck = TypeCheck} = State, NewClient) ->
 
129
connect_pull_supplier(_OE_This, #state{client = undefined, 
 
130
                                       typecheck = TypeCheck} = State, NewClient) ->
131
131
    case corba_object:is_nil(NewClient) of
132
132
        true ->
133
133
            ?DBG("A NIL client supplied.~n", []),
134
 
            orber:debug_level_print("[~p] CosEventChannelAdmin_ProxyPullConsumer:connect_pull_supplier(..); 
135
 
Supplied a NIL reference which is not allowed.", [?LINE], ?DEBUG_LEVEL),
 
134
            orber:dbg("[~p] CosEventChannelAdmin_ProxyPullConsumer:connect_pull_supplier(..);~n"
 
135
                      "Supplied a NIL reference which is not allowed.", 
 
136
                      [?LINE], ?DEBUG_LEVEL),
136
137
            corba:raise(#'BAD_PARAM'{completion_status = ?COMPLETED_NO});
137
138
        false ->
138
139
            cosEventApp:type_check(NewClient, 'CosEventComm_PullSupplier', TypeCheck),
149
150
%% Returns    : 
150
151
%% Description: 
151
152
%%----------------------------------------------------------------------
152
 
disconnect_pull_consumer(OE_This, State) ->
 
153
disconnect_pull_consumer(_OE_This, State) ->
153
154
    NewState = stop_timer(State),
154
155
    ?DBG("Disconnect invoked ~p~n", [NewState]),
155
156
    {stop, normal, ok, NewState#state{client = undefined}}.
186
187
            {noreply, State}; 
187
188
        {'EXCEPTION', #'CosEventComm_Disconnected'{}} ->
188
189
            ?DBG("Client claims we are disconnectedwhen trying to pull event.~n", []),
189
 
            orber:debug_level_print("[~p] CosEventChannelAdmin_ProxyPullConsumer:try_pull_event(); 
190
 
Client claims we are disconnected when trying to pull event so I terminate.", [?LINE], ?DEBUG_LEVEL),
 
190
            orber:dbg("[~p] CosEventChannelAdmin_ProxyPullConsumer:try_pull_event();~n"
 
191
                      "Client claims we are disconnected when trying to pull event so I terminate.", 
 
192
                      [?LINE], ?DEBUG_LEVEL),
191
193
            {stop, normal, State#state{client = undefined}};
192
194
        What ->
193
 
            orber:debug_level_print("[~p] CosEventChannelAdmin_ProxyPullConsumer:try_pull_event(~p); 
194
 
My Client behaves badly so I terminate.", [?LINE, What], ?DEBUG_LEVEL),
 
195
            orber:dbg("[~p] CosEventChannelAdmin_ProxyPullConsumer:try_pull_event(~p);~n"
 
196
                      "My Client behaves badly so I terminate.", 
 
197
                      [?LINE, What], ?DEBUG_LEVEL),
195
198
            {stop, normal, State}
196
199
    end.
197
200