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

« back to all changes in this revision

Viewing changes to lib/megaco/src/engine/megaco_messenger_misc.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:
79
79
            ?SIM({ok, Bin}, encode_trans);
80
80
        Error ->
81
81
            incNumErrors(CD#conn_data.conn_handle),         
82
 
            {error,{EM, encode_transaction, [EC, Trans], Error}}
 
82
            {error, {EM, encode_trans, [EC, Trans], Error}}
83
83
    end.
84
84
 
85
85
 
96
96
    case (catch EM:encode_action_requests(EC, V, ARs)) of
97
97
        {ok, Bin} when binary(Bin) ->
98
98
            ?SIM({ok, Bin}, encode_actions);
 
99
        {error, Reason} ->
 
100
            incNumErrors(CD#conn_data.conn_handle),         
 
101
            {error, {EM, encode_actions, [EC, ARs], Reason}};
99
102
        Error ->
100
103
            incNumErrors(CD#conn_data.conn_handle),         
101
 
            {error, {EM, encode_action_requests, [EC, ARs], Error}}
 
104
            {error, {EM, encode_actions, [EC, ARs], Error}}
102
105
    end.
103
106
 
104
107
 
111
114
    %% Create the message envelope
112
115
    MegaMsg = compose_message(ConnData, V, Body),
113
116
 
114
 
    %% p("encode_body -> ~n~p", [MegaMsg]),
115
117
    ?report_debug(ConnData, TraceLabel, [MegaMsg]),
116
118
 
117
119
    %% Encode the message
118
 
    EncodingMod    = ConnData#conn_data.encoding_mod,
119
 
    EncodingConfig = ConnData#conn_data.encoding_config,
120
 
    case (catch EncodingMod:encode_message(EncodingConfig, V, MegaMsg)) of
 
120
    EM = ConnData#conn_data.encoding_mod,
 
121
    EC = ConnData#conn_data.encoding_config,
 
122
    case (catch EM:encode_message(EC, V, MegaMsg)) of
121
123
        {ok, Bin} when binary(Bin) ->
122
124
            ?SIM({ok, Bin}, encode_body);
 
125
        {error, Reason} ->
 
126
            incNumErrors(ConnData#conn_data.conn_handle),           
 
127
            {error, {EM, [EC, MegaMsg], Reason}};
123
128
        Error ->
124
129
            incNumErrors(ConnData#conn_data.conn_handle),           
125
 
            {error,{EncodingMod,encode_message,[EncodingConfig,MegaMsg],Error}}
 
130
            {error, {EM, [EC, MegaMsg], Error}}
126
131
    end.
127
132
 
128
133
 
171
176
    case (catch SendMod:send_message(SendHandle, Bin)) of
172
177
        ok ->
173
178
            ?SIM({ok, Bin}, send_message);
 
179
        {cancel, Reason} ->
 
180
            ?report_trace(ConnData, "<CANCEL> send_message callback",
 
181
                          [{bytes, Bin}, {cancel, Reason}]),
 
182
            {error, {send_message_cancelled, Reason}};
174
183
        {error, Reason} ->
175
184
            incNumErrors(ConnData#conn_data.conn_handle),
176
185
            ?report_important(ConnData, "<ERROR> send_message callback",
177
186
                              [{bytes, Bin}, {error, Reason}]),
178
 
            error_msg("error sending message on ~w: ~w", [SendHandle, Reason]),
 
187
            error_msg("failed (error) sending message (~p):"
 
188
                      "~n~w", [SendHandle, Reason]),
179
189
            {error, {send_message_failed, Reason}};
 
190
        {'EXIT', Reason} = Error ->
 
191
            incNumErrors(ConnData#conn_data.conn_handle),
 
192
            ?report_important(ConnData, "<ERROR> send_message callback",
 
193
                              [{bytes, Bin}, {exit, Reason}]),
 
194
            error_msg("failed (exit) sending message (~p):"
 
195
                      "~n~w", [SendHandle, Reason]),
 
196
            {error, {send_message_failed, Error}};
180
197
        Reason ->
181
198
            incNumErrors(ConnData#conn_data.conn_handle),
182
199
            ?report_important(ConnData, "<ERROR> send_message callback",
183
200
                              [{bytes, Bin}, {error, Reason}]),
184
 
            error_msg("failed sending message on ~w: ~w", 
185
 
                      [SendHandle, Reason]),
 
201
            error_msg("failed sending message on (~p): "
 
202
                      "~n~w", [SendHandle, Reason]),
186
203
            {error, {send_message_failed, Reason}}
187
204
    end.
188
205
 
196
213
%% Func: error_msg/2
197
214
%% Description: Send an error message
198
215
%%-----------------------------------------------------------------
 
216
 
199
217
error_msg(F, A) ->
200
 
    (catch error_logger:error_msg(F ++ "~n", A)).
 
218
    ?megaco_error(F, A).
201
219
 
202
220
 
203
221
%%-----------------------------------------------------------------
216
234
            Old
217
235
    end.
218
236
            
219
 
% p(F, A) ->
220
 
%     print(now(), F, A).
221
 
 
222
 
% print(Ts, F, A) ->
223
 
%     io:format("*** [~s] ~p ***"
224
 
%               "~n   " ++ F ++ "~n", 
225
 
%               [format_timestamp(Ts), self() | A]).
226
 
 
227
 
% format_timestamp(Now) ->
228
 
%     {N1, N2, N3}   = Now,
229
 
%     {Date, Time}   = calendar:now_to_datetime(Now),
230
 
%     {YYYY,MM,DD}   = Date,
231
 
%     {Hour,Min,Sec} = Time,
232
 
%     FormatDate = 
233
 
%         io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
234
 
%                       [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),  
235
 
%     lists:flatten(FormatDate).
 
237
%% p(F, A) ->
 
238
%%     print(now(), F, A).
 
239
%% 
 
240
%% print(Ts, F, A) ->
 
241
%%     io:format("*** [~s] ~p ***"
 
242
%%               "~n   " ++ F ++ "~n", 
 
243
%%               [format_timestamp(Ts), self() | A]).
 
244
%% 
 
245
%% format_timestamp(Now) ->
 
246
%%     {_N1, _N2, N3}   = Now,
 
247
%%     {Date, Time}   = calendar:now_to_datetime(Now),
 
248
%%     {YYYY,MM,DD}   = Date,
 
249
%%     {Hour,Min,Sec} = Time,
 
250
%%     FormatDate = 
 
251
%%         io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
252
%%                       [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),  
 
253
%%     lists:flatten(FormatDate).