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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
228
228
get_prefixes([], Acc) ->
229
229
    Acc;
230
230
%% A list of ORBInitRef's
231
 
get_prefixes([H|T], Acc) when list(H) ->
 
231
get_prefixes([H|T], Acc) when is_list(H) ->
232
232
    [Key|_] = string:tokens(H, "="),
233
233
    get_prefixes(T, [Key|Acc]);
234
234
%% A single ORBInitRef
235
 
get_prefixes(InitRef, _Acc) when list(InitRef) ->
 
235
get_prefixes(InitRef, _Acc) when is_list(InitRef) ->
236
236
    [Key|_] = string:tokens(InitRef, "="),
237
237
    [Key];
238
238
get_prefixes(What, _) ->
268
268
check_prefixes([], _) ->
269
269
    false;
270
270
%% A list of ORBInitRef's
271
 
check_prefixes([H|T], ObjectId) when list(H) ->
 
271
check_prefixes([H|T], ObjectId) when is_list(H) ->
272
272
    case prefix(ObjectId, H) of
273
273
        false ->
274
274
            check_prefixes(T, ObjectId);
276
276
            UseRef
277
277
    end;
278
278
%% A single ORBInitRef
279
 
check_prefixes(InitRef, ObjectId) when list(InitRef) ->
 
279
check_prefixes(InitRef, ObjectId) when is_list(InitRef) ->
280
280
    case prefix(ObjectId, InitRef) of
281
281
        false ->
282
282
            false;
310
310
resolve_initial_references_remote(_ObjectId, [], _Ctx) ->
311
311
    raise(#'BAD_PARAM'{completion_status=?COMPLETED_NO});
312
312
resolve_initial_references_remote(ObjectId, [RemoteModifier| Rest], Ctx) 
313
 
  when list(RemoteModifier) ->
 
313
  when is_list(RemoteModifier) ->
314
314
    case lists:prefix("iiop://", RemoteModifier) of
315
315
       true ->
316
316
            [_, Host, Port] = string:tokens(RemoteModifier, ":/"),
331
331
 
332
332
list_initial_services_remote([], _Ctx) ->
333
333
    raise(#'BAD_PARAM'{completion_status=?COMPLETED_NO});
334
 
list_initial_services_remote([RemoteModifier| Rest], Ctx) when list(RemoteModifier) ->
 
334
list_initial_services_remote([RemoteModifier| Rest], Ctx) when is_list(RemoteModifier) ->
335
335
    case lists:prefix("iiop://", RemoteModifier) of
336
336
        true ->
337
337
            [_, Host, Port] = string:tokens(RemoteModifier, ":/"),
356
356
object_to_string(Object) ->
357
357
    iop_ior:string_code(Object).
358
358
 
359
 
object_to_string(Object, [H|_] = Hosts) when list(H) ->
 
359
object_to_string(Object, [H|_] = Hosts) when is_list(H) ->
360
360
    iop_ior:string_code(Object, Hosts);
361
361
object_to_string(_Object, _Hosts) ->
362
362
    raise(#'BAD_PARAM'{completion_status=?COMPLETED_NO}).
363
363
 
364
 
object_to_string(Object, [H|_] = Hosts, Port) when list(H), 
365
 
                                                   integer(Port) ->
 
364
object_to_string(Object, [H|_] = Hosts, Port) when is_list(H) andalso
 
365
                                                   is_integer(Port) ->
366
366
    iop_ior:string_code(Object, Hosts, Port);
367
367
object_to_string(_Object, _Hosts, _Port) ->
368
368
    raise(#'BAD_PARAM'{completion_status=?COMPLETED_NO}).
369
369
 
370
 
object_to_string(Object, [H|_] = Hosts, Port, SSLPort) when list(H), 
371
 
                                                            integer(Port),
372
 
                                                            integer(SSLPort)->
 
370
object_to_string(Object, [H|_] = Hosts, Port, SSLPort) when is_list(H) andalso 
 
371
                                                            is_integer(Port) andalso
 
372
                                                            is_integer(SSLPort)->
373
373
    iop_ior:string_code(Object, Hosts, Port, SSLPort);
374
374
object_to_string(_Object, _Hosts, _Port, _SSLPort) ->
375
375
    raise(#'BAD_PARAM'{completion_status=?COMPLETED_NO}).
378
378
string_to_object(IORString) ->
379
379
    string_to_object(IORString, []).
380
380
 
381
 
string_to_object(IORString, Ctx) when list(Ctx) ->
 
381
string_to_object(IORString, Ctx) when is_list(Ctx) ->
382
382
    case lists:prefix("IOR", IORString) of
383
383
        true ->
384
384
            {ObjRef, _, _} = iop_ior:string_decode(IORString),
392
392
                _ ->
393
393
                    Data = orber_cosnaming_utils:select_type(IORString),
394
394
                    case orber_cosnaming_utils:lookup(Data, Ctx) of
395
 
                        String when list(String) ->
 
395
                        String when is_list(String) ->
396
396
                            {Obj, _, _} = iop_ior:string_decode(String),
397
397
                            Obj;
398
398
                        ObjRef ->
473
473
node_check(Node) ->
474
474
    lists:member(Node,orber:orber_nodes()).
475
475
 
476
 
common_create(Module, _TypeID, Env, Options, StartMethod) when list(Options) ->
 
476
common_create(Module, _TypeID, Env, Options, StartMethod) when is_list(Options) ->
477
477
    Opt = evaluate_options(Options, #options{}),
478
478
    case Opt#options.regname of
479
479
        [] ->
480
480
            ok;
481
 
        {'local', Atom} when atom(Atom), Opt#options.persistent == false ->
 
481
        {'local', Atom} when is_atom(Atom) andalso Opt#options.persistent == false ->
482
482
            ok;
483
483
        {'global', _} ->
484
484
            ok;
574
574
%%              sub-object field changed to the given value.
575
575
%% Description: Initially, this field is set to 'undefined'
576
576
%%----------------------------------------------------------------------
577
 
create_subobject_key(Objkey, B) when binary(B) ->
 
577
create_subobject_key(Objkey, B) when is_binary(B) ->
578
578
    iop_ior:set_privfield(Objkey, B);
579
579
create_subobject_key(Objkey, T) ->
580
580
    create_subobject_key(Objkey, term_to_binary(T)).
600
600
    case iop_ior:get_key(Objkey) of
601
601
        {'internal', Key, _, _, _} ->
602
602
            orber_objectkeys:get_pid(Key);
603
 
        {'internal_registered', Key, _, _, _} when atom(Key) ->
 
603
        {'internal_registered', Key, _, _, _} when is_atom(Key) ->
604
604
            case whereis(Key) of
605
605
                undefined ->
606
606
                    raise(#'OBJECT_NOT_EXIST'{completion_status=?COMPLETED_NO});
667
667
%% Returns    : A local IOR with a TAG_ALTERNATE_IIOP_ADDRESS component.
668
668
%% Description: 
669
669
%%----------------------------------------------------------------------
670
 
add_alternate_iiop_address(Obj, Host, Port) when list(Host), integer(Port) ->
 
670
add_alternate_iiop_address(Obj, Host, Port) when is_list(Host) andalso is_integer(Port) ->
671
671
    TC = #'IOP_TaggedComponent'{tag = ?TAG_ALTERNATE_IIOP_ADDRESS, 
672
672
                                component_data = #'ALTERNATE_IIOP_ADDRESS'{
673
673
                                  'HostID' = Host, 
690
690
%% Description: 
691
691
%%----------------------------------------------------------------------
692
692
add_FTGroup_component(Obj, FTDomain, GroupID, GroupVer) 
693
 
  when list(FTDomain), integer(GroupID), integer(GroupVer),
694
 
       GroupID >= ?ULONGLONGMIN, GroupID =< ?ULONGLONGMAX,
695
 
       GroupVer >= ?ULONGMIN, GroupVer =< ?ULONGMAX ->
 
693
  when is_list(FTDomain) andalso is_integer(GroupID) andalso is_integer(GroupVer) andalso
 
694
       GroupID >= ?ULONGLONGMIN andalso GroupID =< ?ULONGLONGMAX andalso
 
695
       GroupVer >= ?ULONGMIN andalso GroupVer =< ?ULONGMAX ->
696
696
    TC = #'IOP_TaggedComponent'{tag = ?TAG_FT_GROUP,
697
697
                                component_data = #'FT_TagFTGroupTaggedComponent'{
698
698
                                  version = #'GIOP_Version'{major = 1, minor = 0},
962
962
            reply_after_exit(InternalState, State, Reason, OnewayOp,
963
963
                             #'OBJ_ADAPTER'{minor=(?ORBER_VMCID bor 2),
964
964
                                            completion_status=?COMPLETED_MAYBE});
965
 
        Exports when list(Exports) ->
 
965
        Exports when is_list(Exports) ->
966
966
            orber:dbg("~p:~p/~p doesn't exist.~n"
967
967
                      "~p:~p~s do exists.~nCheck export-attributes etc",
968
968
                      [M, F, length(A), M, F, Exports], ?DEBUG_LEVEL),
995
995
            reply_after_exit(InternalState, State, Reason, OnewayOp,
996
996
                             #'OBJ_ADAPTER'{minor=(?ORBER_VMCID bor 6),
997
997
                                            completion_status=?COMPLETED_MAYBE});
998
 
        Exports when list(Exports) ->
 
998
        Exports when is_list(Exports) ->
999
999
            orber:dbg("~p:~p/~p doesn't exist.~n"
1000
1000
                      "~p:~p~s do exist(s).~nCheck export-attributes etc~n"
1001
1001
                      "~p:~p/~p invoked the operation above~n",
1096
1096
    call_helper(Obj, Func, Args, TypesOrMod, infinity, Ctx);
1097
1097
call(Obj, Func, Args, TypesOrMod, [{timeout, Timeout}]) ->
1098
1098
    call_helper(Obj, Func, Args, TypesOrMod, Timeout, []);
1099
 
call(Obj, Func, Args, TypesOrMod, Extra) when list(Extra) ->
 
1099
call(Obj, Func, Args, TypesOrMod, Extra) when is_list(Extra) ->
1100
1100
    ExtraData = extract_extra_data(Extra, #extra{}),
1101
1101
    call_helper(Obj, Func, Args, TypesOrMod, ExtraData#extra.timeout, 
1102
1102
                ExtraData#extra.context);
1115
1115
            call_internal(Key, Obj, Func, Args, TypesOrMod,
1116
1116
                          ?ORB_FLAG_TEST(Flags, ?ORB_TYPECHECK), 
1117
1117
                          ?ORB_FLAG_TEST(Flags, ?ORB_USE_PI), Mod, Timeout, Ctx);
1118
 
        {'external', Key} when atom(TypesOrMod) ->                 
 
1118
        {'external', Key} when is_atom(TypesOrMod) ->              
1119
1119
            case catch TypesOrMod:oe_tc(Func) of
1120
1120
                {'EXIT', What} ->
1121
1121
                    orber:dbg("[~p] corba:call_helper(~p);~n"
1183
1183
    extract_extra_data(T, ED#extra{timeout = Timeout}).
1184
1184
 
1185
1185
call_internal(Pid, Obj, Func, Args, Types, Check, PI, Mod, Timeout, Ctx) 
1186
 
  when pid(Pid), node(Pid) == node() ->
 
1186
  when is_pid(Pid) andalso node(Pid) == node() ->
1187
1187
    invoke_pi_request(PI, Obj, Ctx, Func, Args),
1188
1188
    typecheck_request(Check, Args, Types, Func),
1189
1189
    case catch gen_server:call(Pid, {Obj, Ctx, Func, Args}, Timeout) of
1208
1208
            Res
1209
1209
    end;
1210
1210
call_internal(Pid, Obj, Func, Args, Types, Check, PI, 
1211
 
              _Mod, Timeout, Ctx) when pid(Pid) ->
 
1211
              _Mod, Timeout, Ctx) when is_pid(Pid) ->
1212
1212
    typecheck_request(Check, Args, Types, Func),
1213
1213
    case catch rpc:call(node(Pid), corba, call_relay, 
1214
1214
                        [Pid, {Obj, Ctx, Func, Args}, Timeout]) of
1371
1371
            raise(Exc)
1372
1372
    end;
1373
1373
call_internal(Registered, Obj, Func, Args, Types, Check, PI,
1374
 
              _Mod, Timeout, Ctx) when atom(Registered)->
 
1374
              _Mod, Timeout, Ctx) when is_atom(Registered)->
1375
1375
    invoke_pi_request(PI, Obj, Ctx, Func, Args),
1376
1376
    typecheck_request(Check, Args, Types, Func),
1377
1377
    case whereis(Registered) of
1426
1426
 
1427
1427
typecheck_request(false, _, _, _) ->
1428
1428
    ok;
1429
 
typecheck_request(true, Args, Mod, Func) when atom(Mod) ->
 
1429
typecheck_request(true, Args, Mod, Func) when is_atom(Mod) ->
1430
1430
    case catch Mod:oe_tc(Func) of
1431
1431
        undefined ->
1432
1432
            raise(#'BAD_OPERATION'{minor = (?ORBER_VMCID bor 4),
1476
1476
            ok
1477
1477
    end.
1478
1478
 
1479
 
typecheck_reply(true, Args, Mod, Func) when atom(Mod) ->
 
1479
typecheck_reply(true, Args, Mod, Func) when is_atom(Mod) ->
1480
1480
    case catch Mod:oe_tc(Func) of
1481
1481
        undefined ->
1482
1482
            raise(#'BAD_OPERATION'{minor = (?ORBER_VMCID bor 4),
1590
1590
            cast_internal(Key, Obj, Func, Args, TypesOrMod, 
1591
1591
                          ?ORB_FLAG_TEST(Flags, ?ORB_TYPECHECK), 
1592
1592
                          ?ORB_FLAG_TEST(Flags, ?ORB_USE_PI), Mod, Ctx);
1593
 
        {'external', Key} when atom(TypesOrMod) ->
 
1593
        {'external', Key} when is_atom(TypesOrMod) ->
1594
1594
            case catch TypesOrMod:oe_tc(Func) of
1595
1595
                {'EXIT', What} ->
1596
1596
                    orber:dbg("[~p] corba:cast_helper(~p);~n"
1612
1612
    end.
1613
1613
 
1614
1614
cast_internal(Pid, Obj, Func, Args, Types, Check, PI, _Mod, Ctx)
1615
 
  when pid(Pid), node(Pid) == node() ->
 
1615
  when is_pid(Pid) andalso node(Pid) == node() ->
1616
1616
    invoke_pi_request(PI, Obj, Ctx, Func, Args),
1617
1617
    typecheck_request(Check, Args, Types, Func),
1618
1618
    catch gen_server:cast(Pid, {Obj, Ctx, Func, Args}),
1619
1619
    ok;
1620
 
cast_internal(Pid, Obj, Func, Args, Types, Check, PI, Mod, Ctx) when pid(Pid) ->
 
1620
cast_internal(Pid, Obj, Func, Args, Types, Check, PI, Mod, Ctx) when is_pid(Pid) ->
1621
1621
    invoke_pi_request(PI, Obj, Ctx, Func, Args),
1622
1622
    typecheck_request(Check, Args, Types, Func),
1623
1623
    case catch rpc:call(node(Pid), corba, cast_relay, [Pid, {Obj, Ctx, Func, Args}]) of
1704
1704
 
1705
1705
%% "Ordinary" operations.
1706
1706
request_from_iiop({Mod, _, _, _, _, _}, oe_get_interface, 
1707
 
                  _, _, _, _ServiceCtx) when atom(Mod) ->
 
1707
                  _, _, _, _ServiceCtx) when is_atom(Mod) ->
1708
1708
    case catch Mod:oe_get_interface() of
1709
1709
        {'EXIT', What} ->
1710
1710
            orber:dbg("[~p] corba:request_from_iiop(~p);~n"
1846
1846
%% Internal stuff
1847
1847
%%------------------------------------------------------------
1848
1848
 
1849
 
convert_key_to_pid(Key) when binary(Key) ->
 
1849
convert_key_to_pid(Key) when is_binary(Key) ->
1850
1850
    orber_objectkeys:get_pid(Key);
1851
 
convert_key_to_pid(Name) when atom(Name) ->
 
1851
convert_key_to_pid(Name) when is_atom(Name) ->
1852
1852
    Name.
1853
1853
 
1854
1854
mk_objkey(Mod, Pid, RegName, Persistent) ->
1855
1855
    mk_objkey(Mod, Pid, RegName, Persistent, 0).
1856
1856
 
1857
 
mk_objkey(Mod, Pid, [], _, Flags) when pid(Pid) ->
 
1857
mk_objkey(Mod, Pid, [], _, Flags) when is_pid(Pid) ->
1858
1858
    Key = make_objkey(),
1859
1859
    case orber_objectkeys:register(Key, Pid, false) of
1860
1860
        ok ->
1864
1864
                      "unable to store key(~p).", [?LINE, Mod, R], ?DEBUG_LEVEL),
1865
1865
            raise(#'INTERNAL'{minor=(?ORBER_VMCID bor 2), completion_status=?COMPLETED_NO})
1866
1866
    end;
1867
 
mk_objkey(Mod, Pid, {'global', RegName}, Persitent, Flags) when pid(Pid) ->
 
1867
mk_objkey(Mod, Pid, {'global', RegName}, Persitent, Flags) when is_pid(Pid) ->
1868
1868
    Key = term_to_binary(RegName),
1869
1869
    case orber_objectkeys:register(Key, Pid, Persitent) of
1870
1870
        ok ->
1875
1875
                      [?LINE, Mod, RegName, R], ?DEBUG_LEVEL),
1876
1876
            raise(#'INTERNAL'{minor=(?ORBER_VMCID bor 2), completion_status=?COMPLETED_NO})
1877
1877
    end;
1878
 
mk_objkey(Mod, Pid, {'local', RegName}, Persistent, Flags) when pid(Pid), atom(RegName) ->
 
1878
mk_objkey(Mod, Pid, {'local', RegName}, Persistent, Flags) when is_pid(Pid) andalso is_atom(RegName) ->
1879
1879
    register(RegName, Pid),
1880
1880
    Key = make_objkey(),
1881
1881
    case orber_objectkeys:register(Key, Pid, Persistent) of
1958
1958
%% FT stuff
1959
1959
evaluate_options([{passive, true}|Rest], #options{pseudo = false} = Options) ->
1960
1960
    evaluate_options(Rest, Options#options{passive = true});
1961
 
evaluate_options([{group_id, ID}|Rest], Options) when integer(ID) ->
 
1961
evaluate_options([{group_id, ID}|Rest], Options) when is_integer(ID) ->
1962
1962
    evaluate_options(Rest, Options#options{group_id = ID});
1963
1963
%% Options accepted by gen_server (e.g. dbg).
1964
 
evaluate_options([{create_options, COpt}|Rest], Options) when list(COpt) ->
 
1964
evaluate_options([{create_options, COpt}|Rest], Options) when is_list(COpt) ->
1965
1965
    evaluate_options(Rest, Options#options{create_options = COpt});
1966
1966
%% When starting object as supervisor child.
1967
1967
evaluate_options([{sup_child, false}|Rest], Options) ->