~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/ei_connect_SUITE_data/ei_connect_test.c

  • 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 2001-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
 * Purpose: Tests the functions in ei_connect.c.
 
22
 * Author: Bjorn Gustavsson (rewritten somewhat by Jakob Cederlund)
 
23
 *
 
24
 * See the ei_connect_SUITE.erl file for a "table of contents".
 
25
 */
 
26
 
 
27
#include <stdio.h>
 
28
#include <string.h>
 
29
#ifdef VXWORKS
 
30
#include "reclaim.h"
 
31
#endif
 
32
 
 
33
#include "ei_runner.h"
 
34
 
 
35
static void cmd_ei_connect_init(char* buf, int len);
 
36
static void cmd_ei_connect(char* buf, int len);
 
37
static void cmd_ei_send(char* buf, int len);
 
38
static void cmd_ei_format_pid(char* buf, int len);
 
39
static void cmd_ei_send_funs(char* buf, int len);
 
40
static void cmd_ei_reg_send(char* buf, int len);
 
41
static void cmd_ei_rpc(char* buf, int len);
 
42
static void cmd_ei_set_get_tracelevel(char* buf, int len);
 
43
 
 
44
static void send_errno_result(int value);
 
45
 
 
46
ei_cnode ec;
 
47
 
 
48
 
 
49
static struct {
 
50
    char* name;
 
51
    int num_args;               /* Number of arguments. */
 
52
    void (*func)(char* buf, int len);
 
53
} commands[] = {
 
54
    "ei_connect_init",       3, cmd_ei_connect_init,
 
55
    "ei_connect",            1, cmd_ei_connect,
 
56
    "ei_send",               3, cmd_ei_send,
 
57
    "ei_send_funs",          3, cmd_ei_send_funs,
 
58
    "ei_reg_send",           3, cmd_ei_reg_send,
 
59
    "ei_rpc",                4, cmd_ei_rpc,
 
60
    "ei_set_get_tracelevel", 1, cmd_ei_set_get_tracelevel,
 
61
    "ei_format_pid",         2, cmd_ei_format_pid,
 
62
};
 
63
 
 
64
 
 
65
/*
 
66
 * Sends a list contaning all data types to the Erlang side.
 
67
 */
 
68
 
 
69
TESTCASE(interpret)
 
70
{
 
71
    ei_x_buff x;
 
72
    int i;
 
73
    ei_term term;
 
74
 
 
75
    ei_x_new(&x);
 
76
    for (;;) {
 
77
        if (get_bin_term(&x, &term)) {
 
78
            report(1);
 
79
            return;
 
80
        } else {
 
81
            char* buf = x.buff, func[MAXATOMLEN];
 
82
            int index = x.index, arity;
 
83
            if (term.ei_type != ERL_SMALL_TUPLE_EXT || term.arity != 2)
 
84
                fail("term should be a tuple of size 2");
 
85
            if (ei_decode_atom(buf, &index, func) < 0)
 
86
                fail("function name should be an atom");
 
87
            if (ei_decode_tuple_header(buf, &index, &arity) != 0)
 
88
                fail("function arguments should be a tuple");
 
89
            for (i = 0; i < sizeof(commands)/sizeof(commands[0]); i++) {
 
90
                if (strcmp(func, commands[i].name) == 0) {
 
91
                    if (arity != commands[i].num_args)
 
92
                        fail("wrong number of arguments");
 
93
                    commands[i].func(buf + index, x.buffsz - index);
 
94
                    break;
 
95
                }
 
96
            }
 
97
            if (i >= sizeof(commands)/sizeof(commands[0])) {
 
98
                message("\"%d\" \n", func);
 
99
                fail("bad command");
 
100
            }
 
101
        }
 
102
    }   
 
103
}
 
104
 
 
105
 
 
106
static void cmd_ei_connect_init(char* buf, int len)
 
107
{
 
108
    int index = 0, r = 0;
 
109
    int type, size;
 
110
    long l;
 
111
    char b[100];
 
112
    char cookie[MAXATOMLEN], * cp = cookie;
 
113
    ei_x_buff res;
 
114
    if (ei_decode_long(buf, &index, &l) < 0)
 
115
        fail("expected int");
 
116
    sprintf(b, "c%ld", l);
 
117
    /* FIXME don't use internal and maybe use skip?! */
 
118
    ei_get_type_internal(buf, &index, &type, &size);
 
119
    if (ei_decode_atom(buf, &index, cookie) < 0)
 
120
        fail("expected atom (cookie)");
 
121
    if (cookie[0] == '\0')
 
122
        cp = NULL;
 
123
    r = ei_connect_init(&ec, b, cp, 0);
 
124
    ei_x_new_with_version(&res);
 
125
    ei_x_encode_long(&res, r);
 
126
    send_bin_term(&res);
 
127
    ei_x_free(&res);
 
128
}
 
129
 
 
130
static void cmd_ei_connect(char* buf, int len)
 
131
{
 
132
    int index = 0;
 
133
    char node[256];
 
134
    int i;
 
135
    if (ei_decode_atom(buf, &index, node) < 0)
 
136
        fail("expected atom");
 
137
    i=ei_connect(&ec, node);
 
138
#ifdef VXWORKS
 
139
    if(i >= 0) {
 
140
        save_fd(i);
 
141
    }
 
142
#endif
 
143
    send_errno_result(i);
 
144
}
 
145
 
 
146
static void cmd_ei_set_get_tracelevel(char* buf, int len)
 
147
{
 
148
    int  index = 0;
 
149
    long level = 0;
 
150
    long ret   = 0;
 
151
    ei_x_buff x;
 
152
 
 
153
    if (ei_decode_long(buf, &index, &level) < 0) {
 
154
        fail("expected long");
 
155
    }
 
156
    
 
157
    ei_set_tracelevel((int)level);
 
158
 
 
159
    ret = (long) ei_get_tracelevel();
 
160
 
 
161
    ei_x_new_with_version(&x);
 
162
    ei_x_encode_tuple_header(&x, 2);
 
163
    ei_x_encode_atom(&x, "tracelevel");
 
164
    ei_x_encode_long(&x, ret);
 
165
    send_bin_term(&x);
 
166
    ei_x_free(&x);
 
167
}
 
168
 
 
169
static void cmd_ei_send(char* buf, int len)
 
170
{
 
171
    int index = 0;
 
172
    long fd;
 
173
    erlang_pid pid;
 
174
    ei_x_buff x;
 
175
 
 
176
    if (ei_decode_long(buf, &index, &fd) < 0)
 
177
        fail("expected long");
 
178
    if (ei_decode_pid(buf, &index, &pid) < 0)
 
179
        fail("expected pid (node)");
 
180
    if (ei_x_new_with_version(&x) < 0)
 
181
        fail("ei_x_new_with_version");
 
182
    if (ei_x_append_buf(&x, &buf[index], len - index) < 0)
 
183
        fail("append");
 
184
    send_errno_result(ei_send(fd, &pid, x.buff, x.index));
 
185
    ei_x_free(&x);
 
186
}
 
187
 
 
188
static void cmd_ei_format_pid(char* buf, int len)
 
189
{
 
190
    int index = 0;
 
191
    long fd;
 
192
    erlang_pid pid;
 
193
    ei_x_buff x;
 
194
 
 
195
    if (ei_decode_long(buf, &index, &fd) < 0)
 
196
        fail("expected long");
 
197
    if (ei_decode_pid(buf, &index, &pid) < 0)
 
198
        fail("expected pid (node)");
 
199
    if (ei_x_new_with_version(&x) < 0)
 
200
        fail("ei_x_new_with_version");
 
201
    if (ei_x_format_wo_ver(&x, "~p", &pid) < 0)
 
202
        fail("ei_x_format_wo_ver");
 
203
    send_errno_result(ei_send(fd, &pid, x.buff, x.index));
 
204
    ei_x_free(&x);
 
205
}
 
206
 
 
207
static void cmd_ei_send_funs(char* buf, int len)
 
208
{
 
209
    int index = 0, n;
 
210
    long fd;
 
211
    erlang_pid pid;
 
212
    ei_x_buff x;
 
213
    erlang_fun fun1, fun2;
 
214
 
 
215
    if (ei_decode_long(buf, &index, &fd) < 0)
 
216
        fail("expected long");
 
217
    if (ei_decode_pid(buf, &index, &pid) < 0)
 
218
        fail("expected pid (node)");
 
219
    if (ei_decode_tuple_header(buf, &index, &n) < 0)
 
220
        fail("expected tuple");
 
221
    if (n != 2)
 
222
        fail("expected tuple");
 
223
    if (ei_decode_fun(buf, &index, &fun1) < 0)
 
224
        fail("expected Fun1");
 
225
    if (ei_decode_fun(buf, &index, &fun2) < 0)
 
226
        fail("expected Fun2");
 
227
    if (ei_x_new_with_version(&x) < 0)
 
228
        fail("ei_x_new_with_version");
 
229
    if (ei_x_encode_tuple_header(&x, 2) < 0)
 
230
        fail("encode tuple header");
 
231
    if (ei_x_encode_fun(&x, &fun1) < 0)
 
232
        fail("encode fun1");
 
233
    if (ei_x_encode_fun(&x, &fun2) < 0)
 
234
        fail("encode fun2");
 
235
    free_fun(&fun1);
 
236
    free_fun(&fun2);
 
237
    send_errno_result(ei_send(fd, &pid, x.buff, x.index));
 
238
    ei_x_free(&x);
 
239
}
 
240
 
 
241
static void cmd_ei_reg_send(char* buf, int len)
 
242
{
 
243
    int index = 0;
 
244
    long fd;
 
245
    char reg_name[MAXATOMLEN];
 
246
    erlang_pid pid;
 
247
    ei_x_buff x;
 
248
    
 
249
    if (ei_decode_long(buf, &index, &fd) < 0)
 
250
        fail("expected long (fd)");
 
251
    if (ei_decode_atom(buf, &index, reg_name) < 0)
 
252
        fail("expected atom (reg name)");
 
253
    if (ei_x_new_with_version(&x) < 0)
 
254
        fail("ei_x_new_with_version");
 
255
    if (ei_x_append_buf(&x, &buf[index], len - index) < 0)
 
256
        fail("append");
 
257
    send_errno_result(ei_reg_send(&ec, fd,
 
258
                                  reg_name, x.buff, x.index));
 
259
    ei_x_free(&x);
 
260
}
 
261
 
 
262
static void cmd_ei_rpc(char* buf, int len)
 
263
{
 
264
    int index = 0, n;
 
265
    long fd;
 
266
    erlang_pid pid;
 
267
    ei_x_buff x, rpc_x;
 
268
    int r;
 
269
    char mod[MAXATOMLEN], func[MAXATOMLEN];
 
270
 
 
271
#if 0 && defined(__WIN32__) 
 
272
    DebugBreak();
 
273
#endif
 
274
 
 
275
    if (ei_decode_long(buf, &index, &fd) < 0)
 
276
        fail("expected long");
 
277
    if (ei_decode_pid(buf, &index, &pid) < 0)
 
278
        fail("expected pid (node)");
 
279
    if (ei_decode_tuple_header(buf, &index, &n) < 0 && n < 2)
 
280
        fail("expected tuple {module, function}");
 
281
    if (ei_decode_atom(buf, &index, mod) < 0)
 
282
        fail("expected atom (module)");
 
283
    if (ei_decode_atom(buf, &index, func) < 0)
 
284
        fail("expected atom (function)");
 
285
    message("pid %s %d %d %d\n", pid.node, pid.num, pid.serial, pid.creation);
 
286
    message("{%s, %s}\n", mod, func);
 
287
    if (ei_x_new(&rpc_x) < 0)
 
288
        fail("ei_x_new");
 
289
    if (ei_rpc(&ec, fd, mod, func, &buf[index], len - index, &rpc_x) < 0)
 
290
        fail("ei_rpc");
 
291
    if (ei_x_new_with_version(&x) < 0)
 
292
        fail("ei_x_new_with_version");
 
293
    if (ei_x_append(&x, &rpc_x) < 0)
 
294
        fail("append");
 
295
    send_bin_term(&x);
 
296
    /*send_errno_result(ei_send(&ec, fd, &pid, x.buff, x.index));*/
 
297
    ei_x_free(&x);
 
298
    ei_x_free(&rpc_x);
 
299
}
 
300
 
 
301
static void send_errno_result(int value)
 
302
{
 
303
    ei_x_buff x;
 
304
    ei_x_new_with_version(&x);
 
305
    ei_x_encode_tuple_header(&x, 2);
 
306
    ei_x_encode_long(&x, value);
 
307
    ei_x_encode_long(&x, erl_errno);
 
308
    send_bin_term(&x);
 
309
    ei_x_free(&x);
 
310
}