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

« back to all changes in this revision

Viewing changes to lib/megaco/src/engine/megaco_config.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2000-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
46
46
 
47
47
         %% Verification functions
48
48
         verify_val/2,
49
 
         verify_strict_uint/1,
50
 
         verify_strict_int/1, verify_strict_int/2, 
51
 
         verify_uint/1,
52
 
         verify_int/1, verify_int/2,
 
49
%%       verify_strict_uint/1,
 
50
%%       verify_strict_int/1, verify_strict_int/2, 
 
51
%%       verify_uint/1,
 
52
%%       verify_int/1, verify_int/2,
53
53
         
54
54
 
55
55
         %% Reply limit counter
224
224
update_user_info(UserMid, Item, Val) ->
225
225
    call({update_user_info, UserMid, Item, Val}).
226
226
 
227
 
conn_info(CH, Item) 
228
 
  when is_record(CH, megaco_conn_handle) andalso (Item /= cancel) ->
229
 
    case Item of
230
 
        conn_handle ->
231
 
            CH;
232
 
        mid ->
233
 
            CH#megaco_conn_handle.local_mid;
234
 
        local_mid ->
235
 
            CH#megaco_conn_handle.local_mid;
236
 
        remote_mid ->
237
 
            CH#megaco_conn_handle.remote_mid;
238
 
        conn_data ->
239
 
            case lookup_local_conn(CH) of
240
 
                [] ->
241
 
                    exit({no_such_connection, CH});
242
 
                [ConnData] ->
243
 
                    ConnData
244
 
            end;
245
 
        _ ->
246
 
            case lookup_local_conn(CH) of
247
 
                [] ->
248
 
                    exit({no_such_connection, CH});
249
 
                [ConnData] ->
250
 
                    conn_info(ConnData, Item)
251
 
            end
252
 
    end;
253
 
conn_info(#conn_data{conn_handle = CH}, cancel) ->
254
 
    %% To minimise raise-condition propabillity,
255
 
    %% we always look in the table instead of
256
 
    %% in the record for this one
257
 
    ets:lookup_element(megaco_local_conn, CH, #conn_data.cancel);
258
 
 
259
 
conn_info(CD, Item) when is_record(CD, conn_data) ->
260
 
    case Item of
261
 
        all ->
262
 
            Tags0 = record_info(fields, conn_data),
263
 
            Tags1 = replace(serial, trans_id, Tags0),
264
 
            Tags  = [mid, local_mid, remote_mid] ++ 
265
 
                replace(max_serial, max_trans_id, Tags1),
266
 
            [{Tag, conn_info(CD,Tag)} || Tag <- Tags, 
267
 
                                         Tag /= conn_data, 
268
 
                                         Tag /= trans_sender,
269
 
                                         Tag /= cancel];
270
 
        conn_data          -> CD;
271
 
        conn_handle        -> CD#conn_data.conn_handle;
272
 
        mid                -> (CD#conn_data.conn_handle)#megaco_conn_handle.local_mid;
273
 
        local_mid          -> (CD#conn_data.conn_handle)#megaco_conn_handle.local_mid;
274
 
        remote_mid         -> (CD#conn_data.conn_handle)#megaco_conn_handle.remote_mid;
275
 
        trans_id           -> CH       = CD#conn_data.conn_handle, 
276
 
                              LocalMid = CH#megaco_conn_handle.local_mid,
277
 
                              Item2    = {LocalMid, trans_id_counter},
278
 
                              case (catch ets:lookup(megaco_config, Item2)) of
279
 
                                  {'EXIT', _} ->
280
 
                                      undefined_serial;
281
 
                                  [] ->
282
 
                                      user_info(LocalMid, min_trans_id);
283
 
                                  [{_, Serial}] ->
284
 
                                      Max = CD#conn_data.max_serial,
285
 
                                      if
286
 
                                          ((Max =:= infinity) andalso 
287
 
                                           is_integer(Serial) andalso 
288
 
                                           (Serial < 4294967295)) ->
289
 
                                              Serial + 1;
290
 
                                          (Max =:= infinity) andalso  
291
 
                                          is_integer(Serial) andalso 
292
 
                                          (Serial =:= 4294967295) ->
293
 
                                              user_info(LocalMid, 
294
 
                                                        min_trans_id);
295
 
                                          Serial < Max ->
296
 
                                              Serial  + 1;
297
 
                                          Serial =:= Max ->
298
 
                                              user_info(LocalMid, 
299
 
                                                        min_trans_id);
300
 
                                          Serial =:= 4294967295 ->
301
 
                                              user_info(LocalMid, 
302
 
                                                        min_trans_id);
303
 
                                          true ->
304
 
                                              undefined_serial
305
 
                                      end
306
 
                              end;
307
 
        max_trans_id         -> CD#conn_data.max_serial;
308
 
        request_timer        -> CD#conn_data.request_timer;
309
 
        long_request_timer   -> CD#conn_data.long_request_timer;
310
 
 
311
 
        auto_ack             -> CD#conn_data.auto_ack;
312
 
 
313
 
        trans_ack            -> CD#conn_data.trans_ack;
314
 
        trans_ack_maxcount   -> CD#conn_data.trans_ack_maxcount;
315
 
 
316
 
        trans_req            -> CD#conn_data.trans_req;
317
 
        trans_req_maxcount   -> CD#conn_data.trans_req_maxcount;
318
 
        trans_req_maxsize    -> CD#conn_data.trans_req_maxsize;
319
 
 
320
 
        trans_timer          -> CD#conn_data.trans_timer;
321
 
 
322
 
        pending_timer        -> CD#conn_data.pending_timer;
323
 
        orig_pending_limit   -> CD#conn_data.sent_pending_limit;
324
 
        sent_pending_limit   -> CD#conn_data.sent_pending_limit;
325
 
        recv_pending_limit   -> CD#conn_data.recv_pending_limit;
326
 
        reply_timer          -> CD#conn_data.reply_timer;
327
 
        control_pid          -> CD#conn_data.control_pid;
328
 
        monitor_ref          -> CD#conn_data.monitor_ref;
329
 
        send_mod             -> CD#conn_data.send_mod;
330
 
        send_handle          -> CD#conn_data.send_handle;
331
 
        encoding_mod         -> CD#conn_data.encoding_mod;
332
 
        encoding_config      -> CD#conn_data.encoding_config;
333
 
        protocol_version     -> CD#conn_data.protocol_version;
334
 
        auth_data            -> CD#conn_data.auth_data;
335
 
        user_mod             -> CD#conn_data.user_mod;
336
 
        user_args            -> CD#conn_data.user_args;
337
 
        reply_action         -> CD#conn_data.reply_action;
338
 
        reply_data           -> CD#conn_data.reply_data;
339
 
        threaded             -> CD#conn_data.threaded;
340
 
        strict_version       -> CD#conn_data.strict_version;
341
 
        long_request_resend  -> CD#conn_data.long_request_resend;
342
 
        call_proxy_gc_timeout -> CD#conn_data.call_proxy_gc_timeout;
343
 
        cancel               -> CD#conn_data.cancel;
344
 
        resend_indication    -> CD#conn_data.resend_indication;
345
 
        segment_reply_ind    -> CD#conn_data.segment_reply_ind;
346
 
        segment_recv_acc     -> CD#conn_data.segment_recv_acc;
347
 
        segment_recv_timer   -> CD#conn_data.segment_recv_timer;
348
 
        segment_send         -> CD#conn_data.segment_send;
349
 
        segment_send_timer   -> CD#conn_data.segment_send_timer;
350
 
        max_pdu_size         -> CD#conn_data.max_pdu_size;
351
 
        request_keep_alive_timeout -> CD#conn_data.request_keep_alive_timeout;
352
 
        receive_handle       ->
353
 
            LocalMid = (CD#conn_data.conn_handle)#megaco_conn_handle.local_mid,
354
 
            #megaco_receive_handle{local_mid       = LocalMid,
355
 
                                   encoding_mod    = CD#conn_data.encoding_mod,
356
 
                                   encoding_config = CD#conn_data.encoding_config,
357
 
                                   send_mod        = CD#conn_data.send_mod};
358
 
        _ ->
359
 
            exit({no_such_item, Item})
360
 
    end;
361
 
conn_info(BadHandle, _Item) ->
362
 
    {error, {no_such_connection, BadHandle}}.
363
 
 
364
 
replace(_, _, []) ->
365
 
    [];
366
 
replace(Item, WithItem, [Item|List]) ->
367
 
    [WithItem|List];
368
 
replace(Item, WithItem, [OtherItem|List]) ->
369
 
    [OtherItem | replace(Item, WithItem, List)].
 
227
 
 
228
conn_info(Data, Item) ->
 
229
    %% The purpose of this is a compiler optimization...
 
230
    %% Args are processed from left to right.
 
231
    do_conn_info(Item, Data).
 
232
 
 
233
do_conn_info(mid = _Item, #megaco_conn_handle{local_mid = Mid}) ->
 
234
    Mid;
 
235
do_conn_info(local_mid = _Item, #megaco_conn_handle{local_mid = LMid}) ->
 
236
    LMid;
 
237
do_conn_info(remote_mid = _Item, #megaco_conn_handle{remote_mid = RMid}) ->
 
238
    RMid;
 
239
do_conn_info(conn_handle = _Item, CH) when is_record(CH, megaco_conn_handle) ->
 
240
    CH;
 
241
do_conn_info(conn_data = _Item, CH) when is_record(CH, megaco_conn_handle) ->
 
242
    case lookup_local_conn(CH) of
 
243
        [] ->
 
244
            exit({no_such_connection, CH});
 
245
        [ConnData] ->
 
246
            ConnData
 
247
    end;
 
248
do_conn_info(Item, CH) when is_record(CH, megaco_conn_handle) ->
 
249
    case lookup_local_conn(CH) of
 
250
        [] ->
 
251
            exit({no_such_connection, CH});
 
252
        [ConnData] ->
 
253
            do_conn_info(Item, ConnData)
 
254
    end;
 
255
 
 
256
do_conn_info(cancel = _Item, #conn_data{conn_handle = CH}) ->
 
257
    %% To minimise raise-condition propabillity,
 
258
    %% we always look in the table instead of
 
259
    %% in the record for this one
 
260
    ets:lookup_element(megaco_local_conn, CH, #conn_data.cancel);
 
261
do_conn_info(cancel = _Item, CH) when is_record(CH, megaco_conn_handle) ->
 
262
    %% To minimise raise-condition propabillity,
 
263
    %% we always look in the table instead of
 
264
    %% in the record for this one
 
265
    ets:lookup_element(megaco_local_conn, CH, #conn_data.cancel);
 
266
 
 
267
do_conn_info(all = _Item, 
 
268
             #conn_data{conn_handle                = CH,
 
269
                        serial                     = TransId,
 
270
                        max_serial                 = MaxTransId,
 
271
                        request_timer              = ReqTmr,
 
272
                        long_request_timer         = LongReqTmr,
 
273
                        auto_ack                   = AutoAck,
 
274
                        trans_ack                  = TransAck,
 
275
                        trans_ack_maxcount         = TransAckMaxCount,
 
276
                        trans_req                  = TransReq, 
 
277
                        trans_req_maxcount         = TransReqMaxCount, 
 
278
                        trans_req_maxsize          = TransReqMaxSz, 
 
279
                        trans_timer                = TransTmr, 
 
280
                        %% trans_sender,   
 
281
                        pending_timer              = PendingTmr,
 
282
                        sent_pending_limit         = SentPendingLimit, 
 
283
                        recv_pending_limit         = RecvPendingLimit, 
 
284
                        reply_timer                = ReplyTmr,
 
285
                        control_pid                = CtrlPid,
 
286
                        monitor_ref                = MonRef,
 
287
                        send_mod                   = SendMod,
 
288
                        send_handle                = SendHandle,
 
289
                        encoding_mod               = EncodingMod,
 
290
                        encoding_config            = EncodingConf,
 
291
                        protocol_version           = ProtoVersion,
 
292
                        auth_data                  = AuthData,
 
293
                        user_mod                   = UserMod,
 
294
                        user_args                  = UserArgs,
 
295
                        reply_action               = ReplyAction, 
 
296
                        reply_data                 = ReplyData, 
 
297
                        threaded                   = Threaded, 
 
298
                        strict_version             = StrictVersion, 
 
299
                        long_request_resend        = LongReqResend, 
 
300
                        call_proxy_gc_timeout      = CallProxyGCTimeout, 
 
301
                        %% cancel, 
 
302
                        resend_indication          = ResendInd, 
 
303
                        segment_reply_ind          = SegReplyInd, 
 
304
                        segment_recv_acc           = SegRecvAcc, 
 
305
                        segment_recv_timer         = SegRecvTmr, 
 
306
                        segment_send               = SegSend, 
 
307
                        segment_send_timer         = SegSendTmr, 
 
308
                        max_pdu_size               = MaxPduSz, 
 
309
                        request_keep_alive_timeout = RequestKeepAliveTmr}) ->
 
310
    [{conn_handle,                CH}, 
 
311
     {trans_id,                   TransId}, 
 
312
     {max_trans_id,               MaxTransId},
 
313
     {request_timer,              ReqTmr},
 
314
     {long_request_timer,         LongReqTmr},
 
315
     {mid,                        CH#megaco_conn_handle.local_mid},
 
316
     {local_mid,                  CH#megaco_conn_handle.local_mid},
 
317
     {remote_mid,                 CH#megaco_conn_handle.remote_mid},
 
318
     {auto_ack,                   AutoAck},
 
319
     {trans_ack,                  TransAck},
 
320
     {trans_ack_maxcount,         TransAckMaxCount},
 
321
     {trans_req,                  TransReq}, 
 
322
     {trans_req_maxcount,         TransReqMaxCount}, 
 
323
     {trans_req_maxsize,          TransReqMaxSz}, 
 
324
     {trans_timer,                TransTmr}, 
 
325
     {pending_timer,              PendingTmr},
 
326
     {sent_pending_limit,         SentPendingLimit}, 
 
327
     {recv_pending_limit,         RecvPendingLimit}, 
 
328
     {reply_timer,                ReplyTmr},
 
329
     {control_pid,                CtrlPid},
 
330
     {monitor_ref,                MonRef},
 
331
     {send_mod,                   SendMod},
 
332
     {send_handle,                SendHandle},
 
333
     {encoding_mod,               EncodingMod},
 
334
     {encoding_config,            EncodingConf},
 
335
     {protocol_version,           ProtoVersion},
 
336
     {auth_data,                  AuthData},
 
337
     {user_mod,                   UserMod},
 
338
     {user_args,                  UserArgs},
 
339
     {reply_action,               ReplyAction}, 
 
340
     {reply_data,                 ReplyData}, 
 
341
     {threaded,                   Threaded}, 
 
342
     {strict_version,             StrictVersion}, 
 
343
     {long_request_resend,        LongReqResend}, 
 
344
     {call_proxy_gc_timeout,      CallProxyGCTimeout}, 
 
345
     {resend_indication,          ResendInd}, 
 
346
     {segment_reply_ind,          SegReplyInd}, 
 
347
     {segment_recv_acc,           SegRecvAcc}, 
 
348
     {segment_recv_timer,         SegRecvTmr}, 
 
349
     {segment_send,               SegSend}, 
 
350
     {segment_send_timer,         SegSendTmr}, 
 
351
     {max_pdu_size,               MaxPduSz}, 
 
352
     {request_keep_alive_timeout, RequestKeepAliveTmr}];
 
353
 
 
354
do_conn_info(conn_data = _Item, CD) ->
 
355
    CD;
 
356
do_conn_info(conn_handle = _Item, #conn_data{conn_handle = Val}) ->
 
357
    Val;
 
358
do_conn_info(mid = _Item, 
 
359
             #conn_data{conn_handle = #megaco_conn_handle{local_mid = Val}}) ->
 
360
    Val;
 
361
do_conn_info(local_mid = _Item, 
 
362
             #conn_data{conn_handle = #megaco_conn_handle{local_mid = Val}}) ->
 
363
    Val;
 
364
do_conn_info(remote_mid = _Item, 
 
365
             #conn_data{conn_handle = #megaco_conn_handle{remote_mid = Val}}) ->
 
366
    Val;
 
367
do_conn_info(trans_id = _Item, 
 
368
             #conn_data{conn_handle = #megaco_conn_handle{local_mid = LMid},
 
369
                        max_serial  = Max}) ->
 
370
    Item2 = {LMid, trans_id_counter},
 
371
    case (catch ets:lookup(megaco_config, Item2)) of
 
372
        {'EXIT', _} ->
 
373
            undefined_serial;
 
374
        [] ->
 
375
            user_info(LMid, min_trans_id);
 
376
        [{_, Serial}] ->
 
377
            if
 
378
                ((Max =:= infinity) andalso 
 
379
                 is_integer(Serial) andalso 
 
380
                 (Serial < 4294967295)) ->
 
381
                    Serial + 1;
 
382
                ((Max =:= infinity) andalso  
 
383
                 is_integer(Serial) andalso 
 
384
                 (Serial =:= 4294967295)) ->
 
385
                    user_info(LMid, min_trans_id);
 
386
                Serial < Max ->
 
387
                    Serial  + 1;
 
388
                Serial =:= Max ->
 
389
                    user_info(LMid, min_trans_id);
 
390
                Serial =:= 4294967295 ->
 
391
                    user_info(LMid, min_trans_id);
 
392
                true ->
 
393
                    undefined_serial
 
394
            end
 
395
    end;
 
396
do_conn_info(max_trans_id = _Item, #conn_data{max_serial = Val}) ->
 
397
    Val;
 
398
do_conn_info(request_timer = _Item, #conn_data{request_timer = Val}) ->
 
399
    Val;
 
400
do_conn_info(long_request_timer = _Item, #conn_data{long_request_timer = Val}) ->
 
401
    Val;
 
402
do_conn_info(auto_ack = _Item, #conn_data{auto_ack = Val}) ->
 
403
    Val;
 
404
do_conn_info(trans_ack = _Item, #conn_data{trans_ack = Val}) ->
 
405
    Val;
 
406
do_conn_info(trans_ack_maxcount = _Item, #conn_data{trans_ack_maxcount = Val}) ->
 
407
    Val;
 
408
do_conn_info(trans_req = _Item, #conn_data{trans_req = Val}) ->
 
409
    Val;
 
410
do_conn_info(trans_req_maxcount = _Item, #conn_data{trans_req_maxcount = Val}) ->
 
411
    Val;
 
412
do_conn_info(trans_req_maxsize = _Item, #conn_data{trans_req_maxsize = Val}) ->
 
413
    Val;
 
414
do_conn_info(trans_timer = _Item, #conn_data{trans_timer = Val}) ->
 
415
    Val;
 
416
do_conn_info(pending_timer = _Item, #conn_data{pending_timer = Val}) ->
 
417
    Val;
 
418
do_conn_info(orig_pending_limit = _Item, #conn_data{sent_pending_limit = Val}) ->
 
419
    Val;
 
420
do_conn_info(sent_pending_limit = _Item, #conn_data{sent_pending_limit = Val}) ->
 
421
    Val;
 
422
do_conn_info(recv_pending_limit = _Item, #conn_data{recv_pending_limit = Val}) ->
 
423
    Val;
 
424
do_conn_info(reply_timer = _Item, #conn_data{reply_timer = Val}) ->
 
425
    Val;
 
426
do_conn_info(control_pid = _Item, #conn_data{control_pid = Val}) ->
 
427
    Val;
 
428
do_conn_info(send_mod = _Item, #conn_data{send_mod = Val}) ->
 
429
    Val;
 
430
do_conn_info(send_handle = _Item, #conn_data{send_handle = Val}) ->
 
431
    Val;
 
432
do_conn_info(encoding_mod = _Item, #conn_data{encoding_mod = Val}) ->
 
433
    Val;
 
434
do_conn_info(encoding_config = _Item, #conn_data{encoding_config = Val}) ->
 
435
    Val;
 
436
do_conn_info(protocol_version = _Item, #conn_data{protocol_version = Val}) ->
 
437
    Val;
 
438
do_conn_info(auth_data = _Item, #conn_data{auth_data = Val}) ->
 
439
    Val;
 
440
do_conn_info(user_mod = _Item, #conn_data{user_mod = Val}) ->
 
441
    Val;
 
442
do_conn_info(user_args = _Item, #conn_data{user_args = Val}) ->
 
443
    Val;
 
444
do_conn_info(reply_action = _Item, #conn_data{reply_action = Val}) ->
 
445
    Val;
 
446
do_conn_info(reply_data = _Item, #conn_data{reply_data = Val}) ->
 
447
    Val;
 
448
do_conn_info(threaded = _Item, #conn_data{threaded = Val}) ->
 
449
    Val;
 
450
do_conn_info(strict_version = _Item, #conn_data{strict_version = Val}) ->
 
451
    Val;
 
452
do_conn_info(long_request_resend = _Item, 
 
453
             #conn_data{long_request_resend = Val}) ->
 
454
    Val;
 
455
do_conn_info(call_proxy_gc_timeout = _Item, 
 
456
             #conn_data{call_proxy_gc_timeout = Val}) ->
 
457
    Val;
 
458
do_conn_info(resend_indication = _Item, #conn_data{resend_indication = Val}) ->
 
459
    Val;
 
460
do_conn_info(segment_reply_ind = _Item, #conn_data{segment_reply_ind = Val}) ->
 
461
    Val;
 
462
do_conn_info(segment_recv_acc = _Item, #conn_data{segment_recv_acc = Val}) ->
 
463
    Val;
 
464
do_conn_info(segment_recv_timer = _Item, 
 
465
             #conn_data{segment_recv_timer = Val}) ->
 
466
    Val;
 
467
do_conn_info(segment_send = _Item, #conn_data{segment_send = Val}) ->
 
468
    Val;
 
469
do_conn_info(segment_send_timer = _Item, 
 
470
             #conn_data{segment_send_timer = Val}) ->
 
471
    Val;
 
472
do_conn_info(max_pdu_size = _Item, #conn_data{max_pdu_size = Val}) ->
 
473
    Val;
 
474
do_conn_info(request_keep_alive_timeout = _Item, 
 
475
             #conn_data{request_keep_alive_timeout = Val}) ->
 
476
    Val;
 
477
do_conn_info(receive_handle = _Item, 
 
478
             #conn_data{conn_handle = #megaco_conn_handle{local_mid = LMid},
 
479
                        encoding_mod    = EM,
 
480
                        encoding_config = EC,
 
481
                        send_mod        = SM}) ->
 
482
    #megaco_receive_handle{local_mid       = LMid,
 
483
                           encoding_mod    = EM,
 
484
                           encoding_config = EC,
 
485
                           send_mod        = SM};
 
486
do_conn_info(Item, Data) 
 
487
  when is_record(Data, conn_data) orelse is_record(Data, megaco_conn_handle) ->
 
488
    exit({no_such_item, Item});
 
489
do_conn_info(_Item, BadData) ->
 
490
    {error, {no_such_connection, BadData}}.
 
491
 
 
492
 
 
493
%% replace(_, _, []) ->
 
494
%%     [];
 
495
%% replace(Item, WithItem, [Item|List]) ->
 
496
%%     [WithItem|List];
 
497
%% replace(Item, WithItem, [OtherItem|List]) ->
 
498
%%     [OtherItem | replace(Item, WithItem, List)].
370
499
 
371
500
 
372
501
update_conn_info(#conn_data{conn_handle = CH}, Item, Val) ->
499
628
        end
500
629
    catch
501
630
        error:_ ->
 
631
            %% Counter does not exist, so try creat it
502
632
            try
503
633
                begin
504
634
                    cre_counter(Item, Incr)
505
635
                end
506
636
            catch
507
637
                exit:_ ->
508
 
                    %% Ok, some other process got there before us,
509
 
                    %% so try again
 
638
                    %% This is a raise condition. 
 
639
                    %% When we tried to update the counter above, it
 
640
                    %% did not exist, but now it does...
510
641
                    ets:update_counter(megaco_config, Item, Incr)
511
642
            end
512
643
    end.
513
 
%% incr_counter(Item, Incr) ->
514
 
%%     case (catch ets:update_counter(megaco_config, Item, Incr)) of
515
 
%%         {'EXIT', _} ->
516
 
%%          case (catch cre_counter(Item, Incr)) of
517
 
%%              {'EXIT', _} ->
518
 
%%                  %% Ok, some other process got there before us,
519
 
%%                  %% so try again
520
 
%%                  ets:update_counter(megaco_config, Item, Incr);
521
 
%%              NewVal ->
522
 
%%                  NewVal
523
 
%%          end;
524
 
%%         NewVal ->
525
 
%%             NewVal
526
 
%%     end.
527
644
 
528
645
cre_counter(Item, Initial) ->
529
646
    case whereis(?SERVER) =:= self() of
531
648
            case call({cre_counter, Item, Initial}) of
532
649
                {ok, Value} ->
533
650
                    Value;
534
 
                Error ->
535
 
                    exit(Error)
 
651
                {error, Reason} ->
 
652
                    exit({failed_creating_counter, Item, Initial, Reason})
536
653
            end;
537
654
        true ->
538
655
            %% Check that the counter does not already exists
542
659
                    ets:insert(megaco_config, {Item, Initial}),
543
660
                    {ok, Initial};
544
661
                [_] ->
545
 
                    %% Ouch, now what?
 
662
                    %% Possibly a raise condition
546
663
                    {error, already_exists}
547
664
                
548
665
                end
1384
1501
        mid                    -> true;
1385
1502
        local_mid              -> true;
1386
1503
        remote_mid             -> true;
1387
 
        min_trans_id           -> verify_strict_uint(Val, 4294967295); % uint32
1388
 
        max_trans_id           -> verify_uint(Val, 4294967295);        % uint32
 
1504
        min_trans_id           -> 
 
1505
            megaco_config_misc:verify_strict_uint(Val, 4294967295); % uint32
 
1506
        max_trans_id           -> 
 
1507
            megaco_config_misc:verify_uint(Val, 4294967295);        % uint32
1389
1508
        request_timer          -> verify_timer(Val);
1390
1509
        long_request_timer     -> verify_timer(Val);
1391
1510
 
1392
 
        auto_ack               -> verify_bool(Val);
1393
 
 
1394
 
        trans_ack              -> verify_bool(Val);
1395
 
        trans_ack_maxcount     -> verify_uint(Val);
1396
 
 
1397
 
        trans_req              -> verify_bool(Val);
1398
 
        trans_req_maxcount     -> verify_uint(Val);
1399
 
        trans_req_maxsize      -> verify_uint(Val);
1400
 
 
1401
 
        trans_timer            -> verify_timer(Val) and (Val >= 0);
1402
 
        trans_sender when Val == undefined -> true;
 
1511
        auto_ack               -> 
 
1512
            megaco_config_misc:verify_bool(Val);
 
1513
 
 
1514
        trans_ack              -> 
 
1515
            megaco_config_misc:verify_bool(Val);
 
1516
        trans_ack_maxcount     -> 
 
1517
            megaco_config_misc:verify_uint(Val);
 
1518
 
 
1519
        trans_req              -> 
 
1520
            megaco_config_misc:verify_bool(Val);
 
1521
        trans_req_maxcount     -> 
 
1522
            megaco_config_misc:verify_uint(Val);
 
1523
        trans_req_maxsize      -> 
 
1524
            megaco_config_misc:verify_uint(Val);
 
1525
 
 
1526
        trans_timer            -> 
 
1527
            verify_timer(Val) and (Val >= 0);
 
1528
        trans_sender when Val =:= undefined -> true;
1403
1529
 
1404
1530
        pending_timer                      -> verify_timer(Val);
1405
 
        sent_pending_limit                 -> verify_uint(Val) andalso 
1406
 
                                                                 (Val > 0);
1407
 
        recv_pending_limit                 -> verify_uint(Val) andalso 
1408
 
                                                                 (Val > 0);
 
1531
        sent_pending_limit                 -> 
 
1532
            megaco_config_misc:verify_uint(Val) andalso (Val > 0);
 
1533
        recv_pending_limit                 -> 
 
1534
            megaco_config_misc:verify_uint(Val) andalso (Val > 0);
1409
1535
        reply_timer                        -> verify_timer(Val);
1410
1536
        control_pid      when is_pid(Val)  -> true;
1411
1537
        monitor_ref                        -> true; % Internal usage only
1413
1539
        send_handle                        -> true;
1414
1540
        encoding_mod     when is_atom(Val) -> true;
1415
1541
        encoding_config  when is_list(Val) -> true;
1416
 
        protocol_version                   -> verify_strict_uint(Val);
 
1542
        protocol_version                   -> 
 
1543
            megaco_config_misc:verify_strict_uint(Val);
1417
1544
        auth_data                          -> true;
1418
1545
        user_mod         when is_atom(Val) -> true;
1419
1546
        user_args        when is_list(Val) -> true;
1420
1547
        reply_data                         -> true;
1421
 
        threaded                           -> verify_bool(Val);
1422
 
        strict_version                     -> verify_bool(Val);
1423
 
        long_request_resend                -> verify_bool(Val);
1424
 
        call_proxy_gc_timeout              -> verify_strict_uint(Val);
1425
 
        cancel                             -> verify_bool(Val);
 
1548
        threaded                           -> 
 
1549
            megaco_config_misc:verify_bool(Val);
 
1550
        strict_version                     -> 
 
1551
            megaco_config_misc:verify_bool(Val);
 
1552
        long_request_resend                -> 
 
1553
            megaco_config_misc:verify_bool(Val);
 
1554
        call_proxy_gc_timeout              -> 
 
1555
            megaco_config_misc:verify_strict_uint(Val);
 
1556
        cancel                             -> 
 
1557
            megaco_config_misc:verify_bool(Val);
1426
1558
        resend_indication                  -> verify_resend_indication(Val);
1427
1559
 
1428
 
        segment_reply_ind               -> verify_bool(Val);
1429
 
        segment_recv_acc                -> verify_bool(Val);
 
1560
        segment_reply_ind               -> 
 
1561
            megaco_config_misc:verify_bool(Val);
 
1562
        segment_recv_acc                -> 
 
1563
            megaco_config_misc:verify_bool(Val);
1430
1564
        segment_recv_timer              -> verify_timer(Val);
1431
1565
        segment_send                    -> verify_segmentation_window(Val);
1432
1566
        segment_send_timer              -> verify_timer(Val);
1433
 
        max_pdu_size                    -> verify_int(Val) andalso (Val > 0);
 
1567
        max_pdu_size                    -> 
 
1568
            megaco_config_misc:verify_int(Val) andalso (Val > 0);
1434
1569
        request_keep_alive_timeout      -> 
1435
 
            (verify_int(Val) andalso (Val >= 0)) orelse (Val =:= plain);
 
1570
            (megaco_config_misc:verify_uint(Val) orelse (Val =:= plain));
1436
1571
 
1437
1572
        _                               -> false
1438
1573
    end.
1439
1574
 
1440
1575
 
1441
1576
 
1442
 
verify_bool(true)  -> true;
1443
 
verify_bool(false) -> true;
1444
 
verify_bool(_)     -> false.
1445
 
 
1446
1577
verify_resend_indication(flag) -> true;
1447
 
verify_resend_indication(Val)  -> verify_bool(Val).
1448
 
 
1449
 
-spec verify_strict_int(Int :: integer()) -> boolean().
1450
 
verify_strict_int(Int) when is_integer(Int) -> true;
1451
 
verify_strict_int(_)                        -> false.
1452
 
 
1453
 
-spec verify_strict_int(Int :: integer(), 
1454
 
                        Max :: integer() | 'infinity') -> boolean().
1455
 
verify_strict_int(Int, infinity) ->
1456
 
    verify_strict_int(Int);
1457
 
verify_strict_int(Int, Max) ->
1458
 
    verify_strict_int(Int) andalso verify_strict_int(Max) andalso (Int =< Max).
1459
 
 
1460
 
-spec verify_strict_uint(Int :: non_neg_integer()) -> boolean().
1461
 
verify_strict_uint(Int) when is_integer(Int) andalso (Int >= 0) -> true;
1462
 
verify_strict_uint(_)                                           -> false.
1463
 
 
1464
 
-spec verify_strict_uint(Int :: non_neg_integer(), 
1465
 
                         Max :: non_neg_integer() | 'infinity') -> boolean().
1466
 
verify_strict_uint(Int, infinity) ->
1467
 
    verify_strict_uint(Int);
1468
 
verify_strict_uint(Int, Max) ->
1469
 
    verify_strict_int(Int, 0, Max).
1470
 
 
1471
 
-spec verify_uint(Val :: non_neg_integer() | 'infinity') -> boolean().
1472
 
verify_uint(infinity) -> true;
1473
 
verify_uint(Val)      -> verify_strict_uint(Val).
1474
 
 
1475
 
-spec verify_int(Val :: integer() | 'infinity') -> boolean().
1476
 
verify_int(infinity) -> true;
1477
 
verify_int(Val)      -> verify_strict_int(Val).
1478
 
 
1479
 
-spec verify_int(Int :: integer() | 'infinity', 
1480
 
                 Max :: integer() | 'infinity') -> boolean().
1481
 
verify_int(Int, infinity) ->
1482
 
    verify_int(Int);
1483
 
verify_int(infinity, _Max) ->
1484
 
    true;
1485
 
verify_int(Int, Max) ->
1486
 
    verify_strict_int(Int) andalso verify_strict_int(Max) andalso (Int =< Max).
1487
 
 
1488
 
-spec verify_uint(Int :: non_neg_integer() | 'infinity', 
1489
 
                  Max :: non_neg_integer() | 'infinity') -> boolean().
1490
 
verify_uint(Int, infinity) ->
1491
 
    verify_uint(Int);
1492
 
verify_uint(infinity, _Max) ->
1493
 
    true;
1494
 
verify_uint(Int, Max) ->
1495
 
    verify_strict_int(Int, 0, Max).
1496
 
 
1497
 
-spec verify_strict_int(Int :: integer(), 
1498
 
                        Min :: integer(), 
1499
 
                        Max :: integer()) -> boolean().
1500
 
verify_strict_int(Val, Min, Max) 
1501
 
  when (is_integer(Val) andalso 
1502
 
        is_integer(Min) andalso 
1503
 
        is_integer(Max) andalso 
1504
 
        (Val >= Min)    andalso 
1505
 
        (Val =< Max)) ->
1506
 
    true;
1507
 
verify_strict_int(_Val, _Min, _Max) ->
1508
 
    false.
1509
 
    
1510
 
-spec verify_int(Val :: integer() | 'infinity', 
1511
 
                 Min :: integer(), 
1512
 
                 Max :: integer() | 'infinity') -> boolean(). 
1513
 
verify_int(infinity, Min, infinity) ->
1514
 
    verify_strict_int(Min);
1515
 
verify_int(Val, Min, infinity) ->
1516
 
    verify_strict_int(Val) andalso 
1517
 
        verify_strict_int(Min) andalso (Val >= Min);
1518
 
verify_int(Int, Min, Max) ->
1519
 
    verify_strict_int(Int, Min, Max).
 
1578
verify_resend_indication(Val)  -> megaco_config_misc:verify_bool(Val).
1520
1579
 
1521
1580
verify_timer(Timer) ->
1522
1581
    megaco_timer:verify(Timer).
1524
1583
verify_segmentation_window(none) ->
1525
1584
    true;
1526
1585
verify_segmentation_window(K) ->
1527
 
    verify_int(K, 1, infinity).
 
1586
    megaco_config_misc:verify_int(K, 1, infinity).
1528
1587
 
1529
1588
handle_stop_user(UserMid) ->
1530
1589
    case catch user_info(UserMid, mid) of