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

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/ei_accept_SUITE_data/ei_accept_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-2009. 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 accept function in ei_connect.c.
 
22
 * Author: Jakob Cederlund (taken from erl_connect by Bj�rn Gustavsson)
 
23
 *
 
24
 * See the ei_accept_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
#ifdef __WIN32__
 
34
#include <winsock2.h>
 
35
#include <windows.h>
 
36
#else
 
37
#include <sys/types.h>
 
38
#include <sys/socket.h>
 
39
#include <netinet/in.h>
 
40
#endif
 
41
 
 
42
#include "ei_runner.h"
 
43
 
 
44
static void cmd_ei_connect_init(char* buf, int len);
 
45
static void cmd_ei_accept(char* buf, int len);
 
46
static void cmd_ei_receive(char* buf, int len);
 
47
static void cmd_ei_unpublish(char* buf, int len);
 
48
 
 
49
static void send_errno_result(int value);
 
50
 
 
51
ei_cnode ec;
 
52
 
 
53
 
 
54
static struct {
 
55
    char* name;
 
56
    int num_args;               /* Number of arguments. */
 
57
    void (*func)(char* buf, int len);
 
58
} commands[] = {
 
59
    "ei_connect_init",  3, cmd_ei_connect_init,
 
60
    "ei_accept",        1, cmd_ei_accept,
 
61
    "ei_receive",       1, cmd_ei_receive,
 
62
    "ei_unpublish",     0, cmd_ei_unpublish
 
63
};
 
64
 
 
65
/*
 
66
 * Sends a list contaning all data types to the Erlang side.
 
67
 */
 
68
TESTCASE(interpret)
 
69
{
 
70
    ei_x_buff x;
 
71
    int i;
 
72
    ei_term term;
 
73
 
 
74
    ei_x_new(&x);
 
75
    for (;;) {
 
76
        if (get_bin_term(&x, &term)) {
 
77
            report(1);
 
78
            return;
 
79
        } else {
 
80
            char* buf = x.buff, func[MAXATOMLEN];
 
81
            int index = x.index, arity;
 
82
            if (term.ei_type != ERL_SMALL_TUPLE_EXT || term.arity != 2)
 
83
                fail("term should be a tuple of size 2");
 
84
            if (ei_decode_atom(buf, &index, func) < 0)
 
85
                fail("function name should be an atom");
 
86
            if (ei_decode_tuple_header(buf, &index, &arity) != 0)
 
87
                fail("function arguments should be a tuple");
 
88
            for (i = 0; i < sizeof(commands)/sizeof(commands[0]); i++) {
 
89
                if (strcmp(func, commands[i].name) == 0) {
 
90
                    if (arity != commands[i].num_args)
 
91
                        fail("wrong number of arguments");
 
92
                    commands[i].func(buf + index, x.buffsz - index);
 
93
                    break;
 
94
                }
 
95
            }
 
96
            if (i >= sizeof(commands)/sizeof(commands[0])) {
 
97
                message("\"%d\" \n", func);
 
98
                fail("bad command");
 
99
            }
 
100
        }
 
101
    }   
 
102
}
 
103
 
 
104
static void cmd_ei_connect_init(char* buf, int len)
 
105
{
 
106
    int index = 0, r = 0;
 
107
    int type, size;
 
108
    long l;
 
109
    char b[100];
 
110
    char cookie[MAXATOMLEN], * cp = cookie;
 
111
    ei_x_buff res;
 
112
    if (ei_decode_long(buf, &index, &l) < 0)
 
113
        fail("expected int");
 
114
    sprintf(b, "c%d", l);
 
115
    /* FIXME don't use internal and maybe use skip?! */
 
116
    ei_get_type_internal(buf, &index, &type, &size);
 
117
    if (ei_decode_atom(buf, &index, cookie) < 0)
 
118
        fail("expected atom (cookie)");
 
119
    if (cookie[0] == '\0')
 
120
        cp = NULL;
 
121
    r = ei_connect_init(&ec, b, cp, 0);
 
122
    ei_x_new_with_version(&res);
 
123
    ei_x_encode_long(&res, r);
 
124
    send_bin_term(&res);
 
125
    ei_x_free(&res);
 
126
}
 
127
 
 
128
static int my_listen(int port)
 
129
{
 
130
    int listen_fd;
 
131
    struct sockaddr_in addr;
 
132
    const char *on = "1";
 
133
    
 
134
    if ((listen_fd = socket(AF_INET, SOCK_STREAM, 0)) < 0)
 
135
        return -1;
 
136
    
 
137
    setsockopt(listen_fd, SOL_SOCKET, SO_REUSEADDR, on, sizeof(on));
 
138
    
 
139
    memset((void*) &addr, 0, (size_t) sizeof(addr));
 
140
    addr.sin_family = AF_INET;
 
141
    addr.sin_port = htons(port);
 
142
    addr.sin_addr.s_addr = htonl(INADDR_ANY);
 
143
    
 
144
    if (bind(listen_fd, (struct sockaddr*) &addr, sizeof(addr)) < 0)
 
145
        return -1;
 
146
 
 
147
    listen(listen_fd, 5);
 
148
    return listen_fd;
 
149
}
 
150
 
 
151
static void cmd_ei_accept(char* buf, int len)
 
152
{
 
153
    int index = 0;
 
154
    int listen, r;
 
155
    ErlConnect conn;
 
156
    long port;
 
157
    ei_x_buff x;
 
158
    int i;
 
159
 
 
160
    /* get port */
 
161
    if (ei_decode_long(buf, &index, &port) < 0)
 
162
        fail("expected int (port)");
 
163
    /* Make a listen socket */
 
164
    if ((listen = my_listen(port)) <= 0)
 
165
        fail("listen");
 
166
    
 
167
    if ((i = ei_publish(&ec, port)) == -1)
 
168
        fail("ei_publish");
 
169
#ifdef VXWORKS
 
170
    save_fd(i);
 
171
#endif
 
172
    r = ei_accept(&ec, listen, &conn);
 
173
#ifdef VXWORKS
 
174
    save_fd(r);
 
175
#endif
 
176
    /* send result, errno and nodename */
 
177
    ei_x_new_with_version(&x);
 
178
    ei_x_encode_tuple_header(&x, 3);
 
179
    ei_x_encode_long(&x, r);
 
180
    ei_x_encode_long(&x, erl_errno);
 
181
    ei_x_encode_atom(&x, conn.nodename); /* or rather string? */
 
182
    send_bin_term(&x);
 
183
    ei_x_free(&x);
 
184
}
 
185
 
 
186
static void cmd_ei_receive(char* buf, int len)
 
187
{
 
188
    ei_x_buff x;
 
189
    erlang_msg msg;
 
190
    long l;
 
191
    int fd, index = 0;
 
192
    
 
193
    if (ei_decode_long(buf, &index, &l) < 0)
 
194
        fail("expected int (fd)");
 
195
    fd = l;
 
196
    ei_x_new(&x);
 
197
    for (;;) {
 
198
        int got = ei_xreceive_msg(fd, &msg, &x);
 
199
        if (got == ERL_TICK)
 
200
            continue;
 
201
        if (got == ERL_ERROR)
 
202
            fail("ei_xreceive_msg");
 
203
        break;
 
204
    }
 
205
    index = 1;
 
206
    send_bin_term(&x);
 
207
    ei_x_free(&x);
 
208
}
 
209
 
 
210
static void cmd_ei_unpublish(char* buf, int len)
 
211
{
 
212
    send_errno_result(ei_unpublish(&ec));
 
213
}
 
214
 
 
215
static void send_errno_result(int value)
 
216
{
 
217
    ei_x_buff x;
 
218
    ei_x_new_with_version(&x);
 
219
    ei_x_encode_tuple_header(&x, 2);
 
220
    ei_x_encode_long(&x, value);
 
221
    ei_x_encode_long(&x, erl_errno);
 
222
    send_bin_term(&x);
 
223
    ei_x_free(&x);
 
224
}