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

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/erl_global_SUITE_data/erl_global_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 2000-2010. 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 erl_global.c.
 
22
 *
 
23
 * See the erl_global_SUITE.erl file for a "table of contents".
 
24
 */
 
25
 
 
26
#include <stdio.h>
 
27
#include <stdlib.h>
 
28
#include <string.h>
 
29
 
 
30
#include "runner.h"
 
31
 
 
32
static void cmd_erl_connect(ETERM* args);
 
33
static void cmd_erl_global_register(ETERM *args);
 
34
static void cmd_erl_global_whereis(ETERM *args);
 
35
static void cmd_erl_global_names(ETERM *args);
 
36
static void cmd_erl_global_unregister(ETERM *args);
 
37
static void cmd_erl_close_connection(ETERM *args);
 
38
 
 
39
static void send_errno_result(int value);
 
40
 
 
41
static struct {
 
42
    char* name;
 
43
    int num_args;               /* Number of arguments. */
 
44
    void (*func)(ETERM* args);
 
45
} commands[] = {
 
46
    "erl_connect",           4, cmd_erl_connect,
 
47
    "erl_close_connection",  1, cmd_erl_close_connection,
 
48
    "erl_global_register",   2, cmd_erl_global_register,
 
49
    "erl_global_whereis",    2, cmd_erl_global_whereis,
 
50
    "erl_global_names",      1, cmd_erl_global_names,
 
51
    "erl_global_unregister", 2, cmd_erl_global_unregister,
 
52
};
 
53
 
 
54
 
 
55
/*
 
56
 * Sends a list contaning all data types to the Erlang side.
 
57
 */
 
58
 
 
59
TESTCASE(interpret)
 
60
{
 
61
    ETERM* term;
 
62
 
 
63
    erl_init(NULL, 0);
 
64
 
 
65
    outer_loop:
 
66
 
 
67
    term = get_term();
 
68
 
 
69
    if (term == NULL) {
 
70
        report(1);
 
71
        return;
 
72
    } else {
 
73
        ETERM* Func;
 
74
        ETERM* Args;
 
75
        int i;
 
76
 
 
77
        if (!ERL_IS_TUPLE(term) || ERL_TUPLE_SIZE(term) != 2) {
 
78
            fail("term should be a tuple of size 2");
 
79
        }
 
80
 
 
81
        Func = erl_element(1, term);
 
82
        if (!ERL_IS_ATOM(Func)) {
 
83
            fail("function name should be an atom");
 
84
        }
 
85
        Args = erl_element(2, term);
 
86
        if (!ERL_IS_TUPLE(Args)) {
 
87
            fail("function arguments should be a tuple");
 
88
        }
 
89
        erl_free_term(term);
 
90
        for (i = 0; i < sizeof(commands)/sizeof(commands[0]); i++) {
 
91
            int n = strlen(commands[i].name);
 
92
            if (ERL_ATOM_SIZE(Func) != n) {
 
93
                continue;
 
94
            }
 
95
            if (memcmp(ERL_ATOM_PTR(Func), commands[i].name, n) == 0) {
 
96
                erl_free_term(Func);
 
97
                if (ERL_TUPLE_SIZE(Args) != commands[i].num_args) {
 
98
                    fail("wrong number of arguments");
 
99
                }
 
100
                commands[i].func(Args);
 
101
                erl_free_term(Args);
 
102
                goto outer_loop;
 
103
            }
 
104
        }
 
105
        fail("bad command");
 
106
    }
 
107
}
 
108
 
 
109
#define VERIFY_TYPE(Test, Term)                 \
 
110
if (!Test(Term)) {                              \
 
111
    fail("wrong type for " #Term);              \
 
112
} else {                                        \
 
113
}
 
114
 
 
115
static void
 
116
cmd_erl_connect(ETERM* args)
 
117
{
 
118
    ETERM* number;
 
119
    ETERM* node;
 
120
    ETERM* cookie;
 
121
 
 
122
    int res;
 
123
    char buffer[256];
 
124
 
 
125
    number = ERL_TUPLE_ELEMENT(args, 0);
 
126
    VERIFY_TYPE(ERL_IS_INTEGER, number);
 
127
    node = ERL_TUPLE_ELEMENT(args, 1);
 
128
    VERIFY_TYPE(ERL_IS_ATOM, node);
 
129
    cookie = ERL_TUPLE_ELEMENT(args, 2);
 
130
    VERIFY_TYPE(ERL_IS_ATOM, cookie);
 
131
 
 
132
    if (ERL_ATOM_SIZE(cookie) == 0) {
 
133
        res = erl_connect_init(ERL_INT_VALUE(number), 0, 0);
 
134
    } else {
 
135
        memcpy(buffer, ERL_ATOM_PTR(cookie), ERL_ATOM_SIZE(cookie));
 
136
        buffer[ERL_ATOM_SIZE(cookie)] = '\0';
 
137
        res = erl_connect_init(ERL_INT_VALUE(number), buffer, 0);
 
138
    }
 
139
 
 
140
    if(!res) {
 
141
        send_errno_result(res);
 
142
        return;
 
143
    }
 
144
 
 
145
    memcpy(buffer, ERL_ATOM_PTR(node), ERL_ATOM_SIZE(node));
 
146
    buffer[ERL_ATOM_SIZE(node)] = '\0';
 
147
    send_errno_result(erl_connect(buffer));
 
148
}
 
149
 
 
150
static void
 
151
cmd_erl_close_connection(ETERM* args)
 
152
{
 
153
    ETERM* number;
 
154
    ETERM* res;
 
155
 
 
156
    number = ERL_TUPLE_ELEMENT(args, 0);
 
157
    VERIFY_TYPE(ERL_IS_INTEGER, number);
 
158
    res = erl_mk_int(erl_close_connection(ERL_INT_VALUE(number)));
 
159
    send_term(res);
 
160
    erl_free_term(res);
 
161
}
 
162
 
 
163
static void
 
164
cmd_erl_global_register(ETERM* args)
 
165
{
 
166
    ETERM* fd_term = ERL_TUPLE_ELEMENT(args, 0);
 
167
    ETERM* name = ERL_TUPLE_ELEMENT(args, 1);
 
168
    ETERM* pid = erl_mk_pid(erl_thisnodename(), 14, 0, 0);
 
169
 
 
170
    char buffer[256];
 
171
 
 
172
    VERIFY_TYPE(ERL_IS_INTEGER, fd_term);
 
173
    VERIFY_TYPE(ERL_IS_ATOM, name);
 
174
 
 
175
    memcpy(buffer, ERL_ATOM_PTR(name), ERL_ATOM_SIZE(name));
 
176
    buffer[ERL_ATOM_SIZE(name)] = '\0';
 
177
 
 
178
    send_errno_result(erl_global_register(ERL_INT_VALUE(fd_term), buffer, pid));
 
179
    erl_free_term(pid);
 
180
}
 
181
 
 
182
static void
 
183
cmd_erl_global_whereis(ETERM* args)
 
184
{
 
185
    ETERM* fd_term = ERL_TUPLE_ELEMENT(args, 0);
 
186
    ETERM* name = ERL_TUPLE_ELEMENT(args, 1);
 
187
    ETERM* pid = NULL;
 
188
 
 
189
    char buffer[256];
 
190
 
 
191
    VERIFY_TYPE(ERL_IS_INTEGER, fd_term);
 
192
    VERIFY_TYPE(ERL_IS_ATOM, name);
 
193
 
 
194
    memcpy(buffer, ERL_ATOM_PTR(name), ERL_ATOM_SIZE(name));
 
195
    buffer[ERL_ATOM_SIZE(name)] = '\0';
 
196
 
 
197
    pid = erl_global_whereis(ERL_INT_VALUE(fd_term), buffer, NULL);
 
198
    send_term(pid);
 
199
    erl_free_term(pid);
 
200
}
 
201
 
 
202
static void
 
203
cmd_erl_global_names(ETERM* args)
 
204
{
 
205
    ETERM* fd_term = ERL_TUPLE_ELEMENT(args, 0);
 
206
 
 
207
    ETERM* res_array[2], *res_tuple, *name;
 
208
    char** names = NULL;
 
209
    int count = 0, i;
 
210
 
 
211
    VERIFY_TYPE(ERL_IS_INTEGER, fd_term);
 
212
 
 
213
    names = erl_global_names(ERL_INT_VALUE(fd_term), &count);
 
214
 
 
215
    res_array[0] = erl_mk_empty_list();
 
216
    for(i=0; i<count; i++) {
 
217
        name = erl_mk_string(names[i]);
 
218
        res_array[0] = erl_cons(name, res_array[0]);
 
219
    }
 
220
 
 
221
    free(names);
 
222
 
 
223
    res_array[1] = erl_mk_int(count);
 
224
    res_tuple = erl_mk_tuple(res_array, 2);
 
225
 
 
226
    send_term(res_tuple);
 
227
 
 
228
    erl_free_compound(res_array[0]);
 
229
    erl_free_term(res_array[1]);
 
230
    erl_free_term(res_tuple);
 
231
}
 
232
 
 
233
static void
 
234
cmd_erl_global_unregister(ETERM* args)
 
235
{
 
236
    ETERM* fd_term = ERL_TUPLE_ELEMENT(args, 0);
 
237
    ETERM* name = ERL_TUPLE_ELEMENT(args, 1);
 
238
 
 
239
    char buffer[256];
 
240
 
 
241
    VERIFY_TYPE(ERL_IS_INTEGER, fd_term);
 
242
    VERIFY_TYPE(ERL_IS_ATOM, name);
 
243
 
 
244
    memcpy(buffer, ERL_ATOM_PTR(name), ERL_ATOM_SIZE(name));
 
245
    buffer[ERL_ATOM_SIZE(name)] = '\0';
 
246
 
 
247
    send_errno_result(erl_global_unregister(ERL_INT_VALUE(fd_term), buffer));
 
248
}
 
249
 
 
250
static void
 
251
send_errno_result(int value)
 
252
{
 
253
    ETERM* res_array[2];
 
254
    ETERM* res_tuple;
 
255
 
 
256
    res_array[0] = erl_mk_int(value);
 
257
    res_array[1] = erl_mk_int(erl_errno);
 
258
    res_tuple = erl_mk_tuple(res_array, 2);
 
259
    send_term(res_tuple);
 
260
    erl_free_term(res_array[0]);
 
261
    erl_free_term(res_array[1]);
 
262
    erl_free_term(res_tuple);
 
263
}