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

« back to all changes in this revision

Viewing changes to lib/orber/test/cdrcoding_10_SUITE.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
%%-----------------------------------------------------------------
 
21
%% 
 
22
%% Description:
 
23
%% Test suite for the CDR encode/decode functions
 
24
%%
 
25
%%-----------------------------------------------------------------
 
26
-module(cdrcoding_10_SUITE).
 
27
 
 
28
 
 
29
-include("idl_output/Module.hrl").
 
30
-include_lib("test_server/include/test_server.hrl").
 
31
-include_lib("orber/include/corba.hrl").
 
32
-include_lib("orber/src/orber_iiop.hrl").
 
33
 
 
34
-define(default_timeout, ?t:minutes(20)).
 
35
 
 
36
%%-----------------------------------------------------------------
 
37
%% External exports
 
38
%%-----------------------------------------------------------------
 
39
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2]).
 
40
 
 
41
%%-----------------------------------------------------------------
 
42
%% Internal exports
 
43
%%-----------------------------------------------------------------
 
44
-compile(export_all).
 
45
 
 
46
%%-----------------------------------------------------------------
 
47
%% Func: all/1
 
48
%% Args: 
 
49
%% Returns: 
 
50
%%-----------------------------------------------------------------
 
51
suite() -> [{ct_hooks,[ts_install_cth]}].
 
52
 
 
53
all() -> 
 
54
    cases().
 
55
 
 
56
groups() -> 
 
57
    [{types, [],
 
58
      [do_register, null_type, void_type, principal_type,
 
59
       objref_type, struct_type, union_type, string_type,
 
60
       array_type, any_type, typecode_type, alias_type,
 
61
       exception_type, do_unregister]}].
 
62
 
 
63
init_per_group(_GroupName, Config) ->
 
64
        Config.
 
65
 
 
66
end_per_group(_GroupName, Config) ->
 
67
        Config.
 
68
 
 
69
 
 
70
cases() -> 
 
71
    [{group, types}, reply, cancel_request,
 
72
     close_connection, message_error].
 
73
%% request, locate_request, locate_reply].
 
74
 
 
75
%%-----------------------------------------------------------------
 
76
%% Init and cleanup functions.
 
77
%%-----------------------------------------------------------------
 
78
 
 
79
init_per_testcase(_Case, Config) ->
 
80
    Path = code:which(?MODULE),
 
81
    code:add_pathz(filename:join(filename:dirname(Path), "idl_output")),
 
82
     ?line Dog=test_server:timetrap(?default_timeout),
 
83
    [{watchdog, Dog}|Config].
 
84
 
 
85
 
 
86
end_per_testcase(_Case, Config) ->
 
87
    Path = code:which(?MODULE),
 
88
    code:del_path(filename:join(filename:dirname(Path), "idl_output")),
 
89
    Dog = ?config(watchdog, Config),
 
90
    test_server:timetrap_cancel(Dog),
 
91
    ok.
 
92
 
 
93
init_per_suite(Config) when is_list(Config) ->
 
94
    orber:jump_start(0),
 
95
    if
 
96
        is_list(Config) ->
 
97
            Config;
 
98
        true ->
 
99
            exit("Config not a list")
 
100
    end.
 
101
 
 
102
end_per_suite(Config) when is_list(Config) ->
 
103
    orber:jump_stop(),
 
104
    Config.
 
105
 
 
106
%%-----------------------------------------------------------------
 
107
%% Test Case: type encoding tests
 
108
%% Description: Just testing the complex types, the others are 
 
109
%%              tested in the cdrlib SUITE.
 
110
%%-----------------------------------------------------------------
 
111
%types(Config) when list(Config) ->
 
112
%    'oe_orber_test':'oe_register'(),
 
113
%    null_type(), 
 
114
%    void_type(), 
 
115
%    principal_type(), 
 
116
%    objref_type(), 
 
117
%    struct_type(), 
 
118
%    union_type(), 
 
119
%    string_type(), 
 
120
%    array_type(), 
 
121
%    any_type(),
 
122
%    typecode_type(),
 
123
%    alias_type(), 
 
124
%    exception_type(), 
 
125
%    'oe_orber_test':'oe_unregister'(),
 
126
%    ok.
 
127
 
 
128
do_register(doc) -> [];
 
129
do_register(suite) -> [];
 
130
do_register(Config) when is_list(Config) ->
 
131
    io:format("Pwd: ~p, mod: ~p~n",[c:pwd(), c:m('oe_orber_test')]),
 
132
    'oe_orber_test':'oe_register'(),
 
133
    ok.
 
134
do_unregister(doc) -> [];
 
135
do_unregister(suite) -> [];
 
136
do_unregister(Config) when is_list(Config) ->
 
137
    'oe_orber_test':'oe_unregister'(),
 
138
    ok.
 
139
%%-----------------------------------------------------------------
 
140
%% Encode/decode test of type: null 
 
141
%%-----------------------------------------------------------------
 
142
null_type(doc) -> [];
 
143
null_type(suite) -> [];
 
144
null_type(Config) when is_list(Config) ->
 
145
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, 'tk_null', 'null'),
 
146
    ?line {'null', <<>>, _} = cdr_decode:dec_type('tk_null', {1, 0}, B, 0, big),
 
147
    ok.
 
148
 
 
149
%%-----------------------------------------------------------------
 
150
%% Encode/decode test of type: void 
 
151
%%-----------------------------------------------------------------
 
152
void_type(doc) -> [];
 
153
void_type(suite) -> [];
 
154
void_type(Config) when is_list(Config) ->
 
155
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, 'tk_void', 'ok'),
 
156
    ?line {'ok', <<>>, _} = cdr_decode:dec_type('tk_void', {1, 0}, B, 0, big),
 
157
    ok.
 
158
 
 
159
%%-----------------------------------------------------------------
 
160
%% Encode/decode test of type: principal 
 
161
%%-----------------------------------------------------------------
 
162
principal_type(doc) -> [];
 
163
principal_type(suite) -> [];
 
164
principal_type(Config) when is_list(Config) ->
 
165
    ?line B0 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, 'tk_Principal', "principal"),
 
166
    ?line {"principal", <<>>, _} = cdr_decode:dec_type('tk_Principal', {1, 0}, B0, 0, big),
 
167
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, 'tk_Principal', ""),
 
168
    ?line {"", <<>>, _} = cdr_decode:dec_type('tk_Principal', {1, 0}, B1, 0, big),
 
169
    ?line B2 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, 'tk_Principal', "principal"),
 
170
    ?line {"principal", <<>>, _} =
 
171
        cdr_decode:dec_type('tk_Principal', {1, 0}, B2, 0, big),
 
172
    ok.
 
173
 
 
174
%%-----------------------------------------------------------------
 
175
%% Encode/decode test of type: object reference 
 
176
%%-----------------------------------------------------------------
 
177
version() -> #'IIOP_Version'{major=1,minor=0}.
 
178
 
 
179
objref(0) -> 
 
180
    PB = #'IIOP_ProfileBody_1_0'{iiop_version=version(),
 
181
                             host="my.hostname.org",
 
182
                             port=4040,
 
183
                             object_key="ExternalKey: which is an arbitary octet sequence"},
 
184
    TP = #'IOP_TaggedProfile'{tag=?TAG_INTERNET_IOP, profile_data=PB},
 
185
    #'IOP_IOR'{type_id="IDL:Module/Interface:1.0", profiles=[TP]};
 
186
objref(1) -> 
 
187
    K = corba_fake_mk_objkey("IDL:Module/Interface:1.0", key,
 
188
                             list_to_pid("<0.100.0>")),
 
189
    PB = #'IIOP_ProfileBody_1_0'{iiop_version=version(),
 
190
                             host="my.hostname.org",
 
191
                             port=4040,
 
192
                             object_key=K},
 
193
    TP = #'IOP_TaggedProfile'{tag=?TAG_INTERNET_IOP, profile_data=PB},
 
194
    #'IOP_IOR'{type_id="IDL:Module/Interface:1.0", profiles=[TP]};
 
195
objref(2) -> 
 
196
    K = corba_fake_mk_objkey("IDL:Module/Interface:1.0", registered,
 
197
                             list_to_atom("orber_nameservice")),
 
198
    PB = #'IIOP_ProfileBody_1_0'{iiop_version=version(),
 
199
                             host="my.hostname.org",
 
200
                             port=4040,
 
201
                             object_key=K},
 
202
    TP = #'IOP_TaggedProfile'{tag=?TAG_INTERNET_IOP, profile_data=PB},
 
203
    #'IOP_IOR'{type_id="IDL:Module/Interface:1.0", profiles=[TP]}.
 
204
 
 
205
objref_type(doc) -> [];
 
206
objref_type(suite) -> [];
 
207
objref_type(Config) when is_list(Config) ->
 
208
    T = {'tk_objref', "IDL:Module/Interface:1.0", "Interface"},
 
209
    Objref0 = objref(0),
 
210
    ?line B0 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T, Objref0),
 
211
    ?line {Objref0, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B0, 0, big),
 
212
    Objref1 = objref(1),
 
213
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T, Objref1),
 
214
    ?line {Objref1, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B1, 0, big),
 
215
    Objref2 = objref(2),
 
216
    ?line B2 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T, Objref2),
 
217
    ?line {Objref2, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B2, 0, big),
 
218
    ok.
 
219
 
 
220
 
 
221
 
 
222
%%-----------------------------------------------------------------
 
223
%% Encode/decode test of type: struct 
 
224
%%-----------------------------------------------------------------
 
225
struct_type(doc) -> [];
 
226
struct_type(suite) -> [];
 
227
struct_type(Config) when is_list(Config) ->
 
228
    T0 = {'tk_struct',"IDL:Module/Struct0:1.0", "Module_Struct0",
 
229
          [{"long", 'tk_long'}, {"short", 'tk_short'}, {"character", 'tk_char'}]},
 
230
    S0 = #'Module_Struct0'{l=-4711, s=17, c=$a},
 
231
    ?line B0 = cdr_encode:enc_type({1, 0}, T0, S0),
 
232
    ?line {S0, <<>>, _} = cdr_decode:dec_type(T0, {1, 0}, B0, 0, big),
 
233
    
 
234
    T1 = {'tk_struct', "IDL:Module/Struct1:1.0", "Module_Struct1",
 
235
          [{"string", {'tk_string', 0}}, {"ushort", 'tk_ushort'}, {"ulong", 'tk_ulong'}]},
 
236
    S1 = #'Module_Struct1'{s="Hi !!!!", us=17, ul=4711},
 
237
    ?line B1 = cdr_encode:enc_type({1, 0}, T1, S1),
 
238
    ?line {S1, <<>>, _} = cdr_decode:dec_type(T1, {1, 0}, B1, 0, big),
 
239
    
 
240
    T2 = {'tk_struct', "IDL:Module/Struct2:1.0", "Module_Struct2",
 
241
          [{"long_sequence", {'tk_sequence', 'tk_long', 0}},
 
242
           {"enum", {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum", ["horse", "pig", "cow"]}},
 
243
           {"octet", 'tk_octet'}]},
 
244
    S2 = #'Module_Struct2'{long_sequence=[4711, 350000, 0, -3030, -600000], e=cow, o=$X},
 
245
    ?line B2 = cdr_encode:enc_type({1, 0}, T2, S2),
 
246
    ?line {S2, <<>>, _} = cdr_decode:dec_type(T2, {1, 0}, B2, 0, big),
 
247
    ok.
 
248
 
 
249
%%-----------------------------------------------------------------
 
250
%% Encode/decode test of type: union 
 
251
%%-----------------------------------------------------------------
 
252
union_type(doc) -> [];
 
253
union_type(suite) -> [];
 
254
union_type(Config) when is_list(Config) ->
 
255
    T0 = {'tk_union', "IDL:Module/Union:1.0", "Union", 'tk_short', 2,
 
256
          [{0, "First", 'tk_short'},
 
257
           {1, "Second", {'tk_string', 0}},
 
258
           {2, "Third", 'tk_char'}]},
 
259
    S0 = #'Module_Union'{label=1, value="Foo Bar !"},
 
260
    ?line B0 = cdr_encode:enc_type({1, 0}, T0, S0),
 
261
    ?line {S0, <<>>, _} = cdr_decode:dec_type(T0, {1, 0}, B0, 0, big),
 
262
    S1 = #'Module_Union'{label=0, value=-17},
 
263
    ?line B1 = cdr_encode:enc_type({1, 0}, T0, S1),
 
264
    ?line {S1, <<>>, _} = cdr_decode:dec_type(T0, {1, 0}, B1, 0, big),
 
265
    S2 = #'Module_Union'{label=2, value=$X},
 
266
    ?line B2 = cdr_encode:enc_type({1, 0}, T0, S2),
 
267
    ?line {S2, <<>>, _} = cdr_decode:dec_type(T0, {1, 0}, B2, 0, big),
 
268
    T1 = {'tk_union', "IDL:Module/Union1:1.0", "Union1",
 
269
          {'tk_enum', "IDL:Module/Enum:1.0",
 
270
           "Module_Enum", ["horse", "pig", "cow"]}, "pig",
 
271
          [{"horse", "First", 'tk_ushort'},
 
272
           {"pig", "Second", {'tk_sequence', {'tk_string', 0}, 0}},
 
273
           {"cow", "Third", {'tk_enum', "IDL:Module/Enum1:1.0",
 
274
                             "Module_Enum1", ["orange", "banana", "apple"]}}]},
 
275
    S3 = #'Module_Union1'{label=pig, value=["Foo", "Bar", "!"]},
 
276
    ?line B3 = cdr_encode:enc_type({1, 0}, T1, S3),
 
277
    ?line {S3, <<>>, _} = cdr_decode:dec_type(T1, {1, 0}, B3, 0, big),
 
278
    S4 = #'Module_Union1'{label=cow, value=apple},
 
279
    ?line B4 = cdr_encode:enc_type({1, 0}, T1, S4),
 
280
    ?line {S4, <<>>, _} = cdr_decode:dec_type(T1, {1, 0}, B4, 0, big),
 
281
    S5 = #'Module_Union1'{label=horse, value=17},
 
282
    ?line B5 = cdr_encode:enc_type({1, 0}, T1, S5),
 
283
    ?line {S5, <<>>, _} = cdr_decode:dec_type(T1, {1, 0}, B5, 0, big),
 
284
    T2 = {'tk_union', "IDL:Module/Union2:1.0", "Union2",
 
285
          {'tk_enum', "IDL:Module/Enum:1.0",
 
286
           "Module_Enum", ["horse", "pig", "cow"]}, "pig",
 
287
          [{"horse", "First", {'tk_array', 'tk_long', 3}},
 
288
           {"pig", "Second",
 
289
            {'tk_union', "IDL:Module/Union:1.0", "Union", 'tk_short', 2,
 
290
             [{0, "First", 'tk_short'},
 
291
              {1, "Second", {'tk_string', 0}},
 
292
              {2, "Third", 'tk_char'}]}},
 
293
           {"cow", "Third", {'tk_union', "IDL:Module/Union1:1.0", "Union1",
 
294
                             {'tk_enum', "IDL:Module/Enum:1.0",
 
295
                              "Module_Enum", ["horse", "pig", "cow"]}, "pig",
 
296
                             [{"horse", "First", 'tk_ushort'},
 
297
                              {"pig", "Second", {'tk_sequence', 
 
298
                                                 {'tk_string', 0}, 0}},
 
299
                              {"cow", "Third", {'tk_enum', 
 
300
                                                "IDL:Module/Enum1:1.0",
 
301
                                                "Module_Enum1", 
 
302
                                                ["orange", "banana", 
 
303
                                                 "apple"]}}]}}]},
 
304
    S6 = #'Module_Union2'{label=pig, value=#'Module_Union'{label=0, value=-17}},
 
305
    ?line B6 = cdr_encode:enc_type({1, 0}, T2, S6),
 
306
    ?line {S6, <<>>, _} = cdr_decode:dec_type(T2, {1, 0}, B6, 0, big),
 
307
    S7 = #'Module_Union2'{label=cow, value=#'Module_Union1'{label=pig,
 
308
                                                      value=["Foo", "Bar", "!"]}},
 
309
    ?line B7 = cdr_encode:enc_type({1, 0}, T2, S7),
 
310
    ?line {S7, <<>>, _} = cdr_decode:dec_type(T2, {1, 0}, B7, 0, big),
 
311
    S8 = #'Module_Union2'{label=horse, value={-17, 1234567890, -987654321}},
 
312
    ?line B8 = cdr_encode:enc_type({1, 0}, T2, S8),
 
313
    ?line {S8, <<>>, _} = cdr_decode:dec_type(T2, {1, 0}, B8, 0, big),
 
314
    ok.
 
315
 
 
316
%%-----------------------------------------------------------------
 
317
%% Encode/decode test of type: string 
 
318
%%-----------------------------------------------------------------
 
319
string_type(doc) -> [];
 
320
string_type(suite) -> [];
 
321
string_type(Config) when is_list(Config) ->
 
322
    S0 = "Foo Bar ???",
 
323
    ?line B0 = cdr_encode:enc_type({1, 0}, {'tk_string', 0}, S0),
 
324
    ?line {S0, <<>>, _} = cdr_decode:dec_type({'tk_string', 0}, {1, 0}, B0, 0, big),
 
325
    S1 = "Yes, Foo Bar !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! more than 5000 characters",
 
326
    ?line B1 = cdr_encode:enc_type({1, 0}, {'tk_string', 0}, S1),
 
327
    ?line {S1, <<>>, _} = cdr_decode:dec_type({'tk_string', 0}, {1, 0}, B1, 0, big),
 
328
    S2 = "",
 
329
    ?line B2 = cdr_encode:enc_type({1, 0}, {'tk_string', 0}, S2),
 
330
    ?line {S2, <<>>, _} = cdr_decode:dec_type({'tk_string', 0}, {1, 0}, B2, 0, big),
 
331
    S3 = "\0",
 
332
    ?line B3 = cdr_encode:enc_type({1, 0}, {'tk_string', 0}, S3),
 
333
    ?line {S3, <<>>, _} = cdr_decode:dec_type({'tk_string', 0}, {1, 0}, B3, 0, big),
 
334
    S4 = "~n",
 
335
    ?line B4 = cdr_encode:enc_type({1, 0}, {'tk_string', 0}, S4),
 
336
    ?line {S4, <<>>, _} = cdr_decode:dec_type({'tk_string', 0}, {1, 0}, B4, 0, big),
 
337
    ok.
 
338
 
 
339
%%-----------------------------------------------------------------
 
340
%% Encode/decode test of type: array 
 
341
%%-----------------------------------------------------------------
 
342
array_type(doc) -> [];
 
343
array_type(suite) -> [];
 
344
array_type(Config) when is_list(Config) ->
 
345
    T0 = {'tk_array', 'tk_long', 5},
 
346
    S0 = {-100, 0, 30000, -900100900, 123456789},
 
347
    ?line B0 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T0, S0),
 
348
    ?line {S0, <<>>, _} = cdr_decode:dec_type(T0, {1, 0}, B0, 0, big),
 
349
    T1 = {'tk_array', {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum", ["horse", "pig", "cow"]}, 2},
 
350
    S1 = {pig, cow},
 
351
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T1, S1),
 
352
    ?line {S1, <<>>, _} = cdr_decode:dec_type(T1, {1, 0}, B1, 0, big),
 
353
    T2 = {'tk_array', {'tk_union', "IDL:Module/Union:1.0", "Union",
 
354
                       {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum", ["horse", "pig", "cow"]}, "pig",
 
355
                       [{"horse", "First", 'tk_ushort'},
 
356
                        {"pig", "Second", {'tk_sequence', {'tk_string', 0}, 0}},
 
357
                        {"cow", "Third", {'tk_enum', "IDL:Module/Enum1:1.0",
 
358
                                        "Module_Enum1", ["orange", "banana", "apple"]}}]}, 2},
 
359
    S2 = {#'Module_Union'{label=cow, value=banana}, #'Module_Union'{label=pig, value=["This", "is", "a", "test", ""]}},
 
360
    ?line B2 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T2, S2),
 
361
    ?line {S2, <<>>, _} = cdr_decode:dec_type(T2, {1, 0}, B2, 0, big),
 
362
    T3 = {'tk_array', {'tk_objref', "IDL:Module/Interface:1.0", "Interface"}, 3},
 
363
    S3 = {objref(0), objref(1), objref(2)},
 
364
    ?line B3 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T3, S3),
 
365
    ?line {S3, <<>>, _} = cdr_decode:dec_type(T3, {1, 0}, B3, 0, big),    
 
366
    ok.
 
367
%%-----------------------------------------------------------------
 
368
%% Encode/decode test of type: TypeCode 
 
369
%%-----------------------------------------------------------------
 
370
any_type(doc) -> [];
 
371
any_type(suite) -> [];
 
372
any_type(Config) when is_list(Config) ->
 
373
    T = 'tk_any',
 
374
    TC = {'tk_struct', "IDL:Module/Struct2:1.0", "Module_Struct2",
 
375
          [{"long_sequence", {'tk_sequence', 'tk_long', 0}},
 
376
           {"enum", {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum",
 
377
                     ["horse", "pig", "cow"]}},
 
378
           {"octet", 'tk_octet'}]},
 
379
    S = #'Module_Struct2'{long_sequence=[4711, 350000, 0, -3030, -600000], 
 
380
                          e=cow, o=$X},
 
381
    Any = #any{typecode=TC,value=S},
 
382
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T,Any),
 
383
    ?line {Any, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B, 0, big),
 
384
    TC1 = {'tk_array', {'tk_union', "IDL:Module/Union:1.0", "Union",
 
385
                      {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum",
 
386
                       ["horse", "pig", "cow"]}, 1,
 
387
                      [{"horse", "First", 'tk_ushort'},
 
388
                       {"pig", "Second", {'tk_sequence', {'tk_string', 0}, 0}},
 
389
                       {"cow", "Third", {'tk_enum', "IDL:Module/Enum1:1.0",
 
390
                                         "Module_Enum1", ["orange", "banana",
 
391
                                                          "apple"]}}]},2},
 
392
    S1 = {#'Module_Union'{label=cow, value=banana}, #'Module_Union'{label=pig, value=["This", "is", "a", "test", ""]}},
 
393
    Any1 = #any{typecode=TC1,value=S1}, 
 
394
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T,Any1),
 
395
    ?line {Any1, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B1, 0, big),
 
396
    ok.
 
397
 
 
398
 
 
399
%%-----------------------------------------------------------------
 
400
%% Encode/decode test of type: TypeCode 
 
401
%%-----------------------------------------------------------------
 
402
typecode_type(doc) -> [];
 
403
typecode_type(suite) -> [];
 
404
typecode_type(Config) when is_list(Config) ->
 
405
    T = 'tk_TypeCode',
 
406
    TC = {'tk_array', {'tk_union', "IDL:Module/Union:1.0", "Union",
 
407
                      {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum",
 
408
                       ["horse", "pig", "cow"]}, 1,
 
409
                      [{"horse", "First", 'tk_ushort'},
 
410
                       {"pig", "Second", {'tk_sequence', {'tk_string', 0}, 0}},
 
411
               {"cow", "Third", {'tk_enum', "IDL:Module/Enum1:1.0",
 
412
                                         "Module_Enum1", ["orange", "banana",
 
413
                                                          "apple"]}}]}, 10},
 
414
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T,TC),
 
415
    ?line {TC, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B, 0, big),
 
416
    TC1 = {'tk_union', "IDL:Module/Union2:1.0", "Union2",
 
417
          {'tk_enum', "IDL:Module/Enum:1.0",
 
418
           "Module_Enum", ["horse", "pig", "cow"]}, 2,
 
419
          [{"horse", "First", 'tk_long'},
 
420
           {"pig", "Second",
 
421
            {'tk_union', "IDL:Module/Union:1.0", "Union", 'tk_short', 2,
 
422
             [{0, "First", 'tk_short'},
 
423
              {1, "Second", {'tk_string', 0}},
 
424
              {2, "Third", 'tk_char'}]}},
 
425
           {"cow", "Third", {'tk_union', "IDL:Module/Union1:1.0", "Union1",
 
426
                             {'tk_enum', "IDL:Module/Enum:1.0",
 
427
                              "Module_Enum", ["horse", "pig", "cow"]}, 2,
 
428
                             [{"horse", "First", 'tk_ushort'},
 
429
                              {"pig", "Second", {'tk_sequence', 
 
430
                                                 {'tk_string', 0}, 0}},
 
431
                              {"cow", "Third", {'tk_enum', 
 
432
                                                "IDL:Module/Enum1:1.0",
 
433
                                                "Module_Enum1", 
 
434
                                                ["orange", "banana", 
 
435
                                                 "apple"]}}]}}]},
 
436
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T, TC1),
 
437
    ?line {TC1, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B1, 0, big),
 
438
    ok.
 
439
 
 
440
%%-----------------------------------------------------------------
 
441
%% Encode/decode test of type: TypeCode 
 
442
%%-----------------------------------------------------------------
 
443
alias_type(doc) -> [];
 
444
alias_type(suite) -> [];
 
445
alias_type(Config) when is_list(Config) ->
 
446
    T = {'tk_alias', "IDL:Module/Alias:1.0", "Alias",
 
447
         {'tk_struct', "IDL:Module/Struct2:1.0", "Module_Struct2",
 
448
          [{"long_sequence", {'tk_sequence', 'tk_long', 0}},
 
449
           {"enum", {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum",
 
450
                     ["horse", "pig", "cow"]}},
 
451
           {"octet", 'tk_octet'}]}},
 
452
    S = #'Module_Struct2'{long_sequence=[4711, 350000, 0, -3030, -600000], 
 
453
                          e=cow, o=$X},
 
454
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T,S),
 
455
    ?line {S, <<>>, _} = cdr_decode:dec_type(T, {1, 0}, B, 0, big),
 
456
    T1 = {'tk_alias', "IDL:Module/Alias1:1.0", "Alias1",
 
457
         {'tk_sequence', {'tk_union', "IDL:Module/Union:1.0", "Union",
 
458
                      {'tk_enum', "IDL:Module/Enum:1.0", "Module_Enum",
 
459
                       ["horse", "pig", "cow"]}, 2,
 
460
                      [{"horse", "First", 'tk_ushort'},
 
461
                       {"pig", "Second", {'tk_sequence', {'tk_string', 0}, 0}},
 
462
                       {"cow", "Third", {'tk_enum', "IDL:Module/Enum1:1.0",
 
463
                                         "Module_Enum1", ["orange", "banana",
 
464
                                                          "apple"]}}]},0}},
 
465
    S1 = [#'Module_Union'{label=cow, value=banana}, #'Module_Union'{label=pig, value=["This", "is", "a", "test", ""]}],
 
466
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T1, S1),
 
467
    ?line {S1, <<>>, _} = cdr_decode:dec_type(T1, {1, 0}, B1, 0, big),
 
468
    ok.
 
469
 
 
470
%%-----------------------------------------------------------------
 
471
%% Encode/decode test of type: exception 
 
472
%%-----------------------------------------------------------------
 
473
exception_type(doc) -> [];
 
474
exception_type(suite) -> [];
 
475
exception_type(Config) when is_list(Config) ->
 
476
    system_exceptions(),
 
477
    user_exceptions(),
 
478
    ok.
 
479
 
 
480
system_exceptions() ->
 
481
    E = #'UNKNOWN'{completion_status=?COMPLETED_YES},
 
482
    {system_exception, T, E} = orber_exceptions:get_def(E),
 
483
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T,E),
 
484
    ?line {E, _} = cdr_decode:dec_system_exception({1, 0}, B, 0, big),
 
485
    E1 = #'INV_OBJREF'{completion_status=?COMPLETED_NO},
 
486
    {system_exception, T1, E1} = orber_exceptions:get_def(E1),
 
487
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T1,E1),
 
488
    ?line {E1, _} = cdr_decode:dec_system_exception({1, 0}, B1, 0, big),
 
489
    E2 = #'BAD_OPERATION'{completion_status=?COMPLETED_NO},
 
490
    {system_exception, T2, E2} = orber_exceptions:get_def(E2),
 
491
    ?line B2 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T2,E2),
 
492
    ?line {E2, _} = cdr_decode:dec_system_exception({1, 0}, B2, 0, big),
 
493
    E3 = #'INTF_REPOS'{completion_status=?COMPLETED_MAYBE},
 
494
    {system_exception, T3, E3} = orber_exceptions:get_def(E3),
 
495
    ?line B3 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T3,E3),
 
496
    ?line {E3, _} = cdr_decode:dec_system_exception({1, 0}, B3, 0, big),
 
497
    ok.
 
498
 
 
499
user_exceptions() ->
 
500
    E = #'Module_Except1'{rest_of_name=["I","am","testing","exceptions"], why="Error"},
 
501
    {user_exception, T, E} = orber_exceptions:get_def(E),
 
502
    ?line B = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T, E),
 
503
    ?line {E, _} = cdr_decode:dec_user_exception({1, 0}, B, 0, big),
 
504
    E1 = #'Module_Except2'{e=banana,
 
505
                           s=#'Module_Struct2'{long_sequence=[12,-4040,
 
506
                                                        1234567898],
 
507
                                         e=horse,
 
508
                                         o=$a}},
 
509
    {user_exception, T1, E1} = orber_exceptions:get_def(E1),
 
510
    ?line B1 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T1, E1),
 
511
    ?line {E1, _} = cdr_decode:dec_user_exception({1, 0}, B1, 0, big),
 
512
    E2 = #'Module_Except3'{u=#'Module_Union1'{label=pig,value=["high","and","low"]},s=1313, o=objref(0)},
 
513
    {user_exception, T2, E2} = orber_exceptions:get_def(E2),
 
514
    ?line B2 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T2, E2),
 
515
    ?line {E2, _} = cdr_decode:dec_user_exception({1, 0}, B2, 0, big),
 
516
    E3 = #'Module_Except4'{},
 
517
    {user_exception, T3, E3} = orber_exceptions:get_def(E3),
 
518
    ?line B3 = cdr_encode:enc_type(#giop_env{version = {1, 0}}, T3, E3),
 
519
    ?line {E3, _} = cdr_decode:dec_user_exception({1, 0}, B3, 0, big),
 
520
    ok.
 
521
 
 
522
%%-----------------------------------------------------------------
 
523
%% Test Case: request encoding test
 
524
%% Description: Precondition the stack must be started so the
 
525
%%              objectkey is valid.
 
526
%%-----------------------------------------------------------------
 
527
%request(suite) -> [];
 
528
%request(_) ->
 
529
%    exit(not_implemented).
 
530
 
 
531
%%-----------------------------------------------------------------
 
532
%% Test Case: reply encoding test
 
533
%% Description: 
 
534
%%-----------------------------------------------------------------
 
535
reply(doc) -> ["Description", "more description"];
 
536
reply(suite) -> [];
 
537
reply(Config) when is_list(Config) ->
 
538
    R = #reply_header{service_context=[], request_id=1,
 
539
                      reply_status='no_exception'},
 
540
    ?line B = cdr_encode:enc_reply(
 
541
                #giop_env{version = {1, 0}, request_id = 1, 
 
542
                          reply_status = 'no_exception',
 
543
                          tc = {'tk_long', [], [{'tk_sequence',
 
544
                                                 {'tk_string', 0}, 0}]},
 
545
                          result = 1200, parameters = [["foo","Bar"]], 
 
546
                          ctx = []}),
 
547
    ?line {R, 1200, [["foo","Bar"]]}  =
 
548
        cdr_decode:dec_message({'tk_long', [], [{'tk_sequence', {'tk_string', 0},0}]},
 
549
                               B),
 
550
    ok.
 
551
 
 
552
%%-----------------------------------------------------------------
 
553
%% Test Case: cancel_request encoding test
 
554
%% Description: 
 
555
%%-----------------------------------------------------------------
 
556
cancel_request(doc) -> ["Description", "more description"];
 
557
cancel_request(suite) -> [];
 
558
cancel_request(Config) when is_list(Config) ->
 
559
    R = #cancel_request_header{request_id=1},
 
560
    ?line B = cdr_encode:enc_cancel_request(#giop_env{version = {1, 0}, 
 
561
                                                      request_id = 1}),
 
562
    ?line R = cdr_decode:dec_message([], B),
 
563
    ok.
 
564
 
 
565
%%-----------------------------------------------------------------
 
566
%% Test Case: locate_request encoding test
 
567
%% Description: 
 
568
%%-----------------------------------------------------------------
 
569
locate_request(doc) -> ["Description", "more description"];
 
570
locate_request(suite) -> [];
 
571
locate_request(Config) when is_list(Config) ->
 
572
    io:format("Function not imlpemented yet"),
 
573
    exit(not_implemented).
 
574
 
 
575
%%-----------------------------------------------------------------
 
576
%% Test Case: locate_reply encoding test
 
577
%% Description: 
 
578
%%-----------------------------------------------------------------
 
579
locate_reply(doc) -> ["Description", "more description"];
 
580
locate_reply(suite) -> [];
 
581
locate_reply(Config) when is_list(Config) ->
 
582
    io:format("Function not imlpemented yet"),
 
583
    exit(not_implemented).
 
584
 
 
585
%%-----------------------------------------------------------------
 
586
%% Test Case: close_connection encoding test
 
587
%% Description: 
 
588
%%-----------------------------------------------------------------
 
589
close_connection(doc) -> ["Description", "more description"];
 
590
close_connection(suite) -> [];
 
591
close_connection(Config) when is_list(Config) ->
 
592
    ?line B = cdr_encode:enc_close_connection(#giop_env{version = {1, 0}}),
 
593
    ?line 'close_connection' = cdr_decode:dec_message([], B),
 
594
    ok.
 
595
 
 
596
%%-----------------------------------------------------------------
 
597
%% Test Case: message_error encoding test
 
598
%% Description: 
 
599
%%-----------------------------------------------------------------
 
600
message_error(doc) -> ["Description", "more description"];
 
601
message_error(suite) -> [];
 
602
message_error(Config) when is_list(Config) ->
 
603
    ?line B = cdr_encode:enc_message_error(#giop_env{version = {1, 0}}),
 
604
    ?line 'message_error' = cdr_decode:dec_message([], B),
 
605
    ok.
 
606
 
 
607
 
 
608
 
 
609
%%-----------------------------------------------------------------
 
610
%% Internal functions
 
611
%%-----------------------------------------------------------------
 
612
corba_fake_mk_objkey(Id, 'key', Pid) when is_pid(Pid) ->
 
613
    Key = make_objkey(),
 
614
    {list_to_binary(Id), 'key', Key, term_to_binary(undefined),
 
615
     term_to_binary(undefined), term_to_binary(undefined)};
 
616
corba_fake_mk_objkey(Id, 'key', RegName) when is_atom(RegName) ->
 
617
    Key = term_to_binary(RegName),
 
618
    {list_to_binary(Id), 'key', Key, term_to_binary(undefined),
 
619
     term_to_binary(undefined), term_to_binary(undefined)};
 
620
corba_fake_mk_objkey(Id, 'registered', RegName) when is_atom(RegName) ->
 
621
    {list_to_binary(Id), 'registered', RegName, term_to_binary(undefined),
 
622
     term_to_binary(undefined), term_to_binary(undefined)}.
 
623
 
 
624
make_objkey() ->
 
625
    term_to_binary({now(), node()}).