~ubuntu-branches/ubuntu/lucid/erlang/lucid-proposed

« back to all changes in this revision

Viewing changes to lib/orber/src/iop_ior.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
278
278
               #host_data{protocol = ssl, 
279
279
                          ssl_data = #'SSLIOP_SSL'{port = Port}, 
280
280
                          csiv2_mech = Mech}}},
281
 
             IOR, Acc, Indexes) when record(Mech, 'CSIIOP_CompoundSecMech') ->
 
281
             IOR, Acc, Indexes) when is_record(Mech, 'CSIIOP_CompoundSecMech') ->
282
282
    Alts = get_alt_addr(TaggedProfile),
283
283
    get_peerdata(get_key(IOR, [Index|Indexes]), IOR, [{Host, Port}|Alts] ++ Acc, 
284
284
                 [Index|Indexes]);
287
287
              {Host, Port, _InitObjkey, Index, TaggedProfile, 
288
288
               #host_data{protocol = normal, 
289
289
                          csiv2_mech = Mech}}},
290
 
             IOR, Acc, Indexes) when record(Mech, 'CSIIOP_CompoundSecMech') ->
 
290
             IOR, Acc, Indexes) when is_record(Mech, 'CSIIOP_CompoundSecMech') ->
291
291
    Alts = get_alt_addr(TaggedProfile),
292
292
    get_peerdata(get_key(IOR, [Index|Indexes]), IOR, [{Host, Port}|Alts] ++ Acc, 
293
293
                 [Index|Indexes]);
304
304
    get_key_1(P, false, 0, undefined, #host_data{});
305
305
get_key({Module, Type, Key, _UserDef, OrberDef, Flags}) ->
306
306
    if
307
 
        binary(Key) ->
 
307
        is_binary(Key) ->
308
308
            {'internal', Key, OrberDef, Flags, Module};
309
309
        Type == pseudo ->
310
310
            {'internal_registered', {pseudo, Key}, OrberDef, Flags, Module};
311
 
        atom(Key) ->
 
311
        is_atom(Key) ->
312
312
            {'internal_registered', Key, OrberDef, Flags, Module}
313
313
    end;
314
314
get_key(What) ->
338
338
            {object_key={Module, Type, Key, _UserDef, OrberDef, Flags}}}|_], 
339
339
          _Retry, _Counter, _Exclude, _HD) ->
340
340
    if
341
 
        binary(Key) ->
 
341
        is_binary(Key) ->
342
342
            {'internal', Key, OrberDef, Flags, Module};
343
343
        Type == pseudo ->
344
344
            {'internal_registered', {pseudo, Key}, OrberDef, Flags, Module};
345
 
        atom(Key) ->
 
345
        is_atom(Key) ->
346
346
            {'internal_registered', Key, OrberDef, Flags, Module}
347
347
    end;
348
348
%%--------- Local IIOP-1.1 & IIOP-1.2 Profiles ---------
352
352
            {object_key={Module, Type, Key, _UserDef, OrberDef, Flags}}}|_], 
353
353
          _Retry, _Counter, _Exclude, _HD) ->
354
354
    if
355
 
        binary(Key) ->
 
355
        is_binary(Key) ->
356
356
            {'internal', Key, OrberDef, Flags, Module};
357
357
        Type == pseudo ->
358
358
            {'internal_registered', {pseudo, Key}, OrberDef, Flags, Module};
363
363
            %% groupid in the component-section of IOR. ObjectKey will tell
364
364
            %% GroupID and database read transaction will tell primary member.
365
365
            {'internal_registered', {passive, Key}, OrberDef, Flags, Module};
366
 
        atom(Key) ->
 
366
        is_atom(Key) ->
367
367
            {'internal_registered', Key, OrberDef, Flags, Module}
368
368
    end;
369
369
%%--------- External IIOP-1.0 Profile ---------
442
442
    HostData;
443
443
check_components([#'IOP_TaggedComponent'{tag=?TAG_SSL_SEC_TRANS, 
444
444
                                         component_data=SSLStruct}|Rest], 
445
 
                       Port, HostData) when record(SSLStruct, 'SSLIOP_SSL') ->
 
445
                       Port, HostData) when is_record(SSLStruct, 'SSLIOP_SSL') ->
446
446
    check_components(Rest, Port, HostData#host_data{protocol = ssl,
447
447
                                                    ssl_data = SSLStruct});
448
448
%% CSIv2 Components
449
449
check_components([#'IOP_TaggedComponent'{tag=?TAG_CSI_SEC_MECH_LIST, 
450
450
                                         component_data=Data}|Rest], 
451
 
                 Port, HostData) when record(Data, 'CSIIOP_CompoundSecMechList') ->
 
451
                 Port, HostData) when is_record(Data, 'CSIIOP_CompoundSecMechList') ->
452
452
    case check_sec_mech(Data#'CSIIOP_CompoundSecMechList'.mechanism_list, Port) of
453
453
        undefined ->
454
454
            check_components(Rest, Port, HostData);
585
585
%%-----------------------------------------------------------------
586
586
%% Func: add_component/2
587
587
%%-----------------------------------------------------------------
588
 
add_component(Objref, Component) when record(Objref, 'IOP_IOR') ->
 
588
add_component(Objref, Component) when is_record(Objref, 'IOP_IOR') ->
589
589
    add_component_ior(Objref, Component);
590
590
add_component(Objref, Component) ->
591
591
    add_component_local(Objref, Component, orber:giop_version()).
651
651
                           profile_data=#'IIOP_ProfileBody_1_1'
652
652
                           {object_key=Objkey,
653
653
                            components=Components} = PB} = H|T], 
654
 
                         Component, _Status, Acc) when tuple(Objkey) ->
 
654
                         Component, _Status, Acc) when is_tuple(Objkey) ->
655
655
    %% The objectkey must be a tuple if it's a local object. We cannot(!!) add components
656
656
    %% to an external IOR.
657
657
    add_component_ior_helper(T, Component, true, 
876
876
%%-----------------------------------------------------------------
877
877
check_nil(#'IOP_IOR'{type_id="", profiles=[]}) ->
878
878
    true;
879
 
check_nil({Id, _, _, _, _, _}) when atom(Id) ->
 
879
check_nil({Id, _, _, _, _, _}) when is_atom(Id) ->
880
880
    false;
881
881
check_nil({Id, _, _, _, _, _}) ->  
882
882
    case binary_to_list(Id) of
908
908
             "================== IOR ====================~n"
909
909
             "NIL Object Reference.~n"
910
910
             "================== END ====================~n");
911
 
print(IoDevice, IORStr) when list(IORStr) ->
 
911
print(IoDevice, IORStr) when is_list(IORStr) ->
912
912
    IOR = corba:string_to_object(IORStr),
913
913
    print_helper(IoDevice, IOR);
914
 
print(IoDevice, IOR) when record(IOR, 'IOP_IOR') ->
 
914
print(IoDevice, IOR) when is_record(IOR, 'IOP_IOR') ->
915
915
    print_helper(IoDevice, IOR);
916
916
print(IoDevice, {Mod, Type, Key, UserDef, OrberDef, Flags}) ->
917
917
    EnvFlags = orber:get_flags(),
1100
1100
    print_components(T, [lists:flatten([Unused | Octets])| Data]).
1101
1101
 
1102
1102
 
1103
 
print_objkey(Objkey) when tuple(Objkey) ->
 
1103
print_objkey(Objkey) when is_tuple(Objkey) ->
1104
1104
    io_lib:format("Local Object........:~n~p~n", [Objkey]);
1105
1105
print_objkey(Objkey) ->
1106
1106
    Hdr = io_lib:format("External Object.....: ~n", []),
1297
1297
          end,
1298
1298
    code(Env, IOR, Bytes, Len).
1299
1299
 
1300
 
check_port(Port, _Type) when integer(Port) ->
 
1300
check_port(Port, _Type) when is_integer(Port) ->
1301
1301
    Port;
1302
1302
check_port(_, normal) ->
1303
1303
    orber:iiop_port();