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

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/all_SUITE_data/ei_runner.c

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

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
#include <stdio.h>
 
20
#include <stdlib.h>
 
21
#include <errno.h>
 
22
#include <sys/types.h>
 
23
#include <sys/stat.h>
 
24
#include <fcntl.h>
 
25
#ifndef __WIN32__
 
26
#include <unistd.h>
 
27
#endif
 
28
#include <stdarg.h>
 
29
 
 
30
#include "ei_runner.h"
 
31
 
 
32
#ifndef __WIN32__
 
33
#define _O_BINARY 0
 
34
#define _setmode(fd, mode)
 
35
#endif
 
36
 
 
37
#define HEADER_SIZE 4
 
38
 
 
39
static char* progname;          /* Name of this program (from argv[0]). */
 
40
static int fd_from_erl;         /* File descriptor from Erlang. */
 
41
static int fd_to_erl;           /* File descriptor to Erlang. */
 
42
 
 
43
static int packet_loop();
 
44
static void ensure_buf_big_enough();
 
45
static int readn();
 
46
static void reply(char* buf, unsigned size);
 
47
static void dump();
 
48
 
 
49
void
 
50
run_tests(char* argv0, TestCase test_cases[], unsigned number)
 
51
{
 
52
    int i;
 
53
    int n;
 
54
    char* packet;
 
55
 
 
56
    progname = argv0;
 
57
    _setmode(0, _O_BINARY);
 
58
    _setmode(1, _O_BINARY);
 
59
    fd_from_erl = 0;
 
60
    fd_to_erl = 1;
 
61
 
 
62
    packet = read_packet(&n);
 
63
 
 
64
    /*
 
65
     * Dispatch to the appropriate test function.
 
66
     */
 
67
 
 
68
    i = packet[0] * 256 + packet[1];
 
69
    if (i >= number) {
 
70
        fprintf(stderr, "%s: bad test case number %d",
 
71
                progname, i);
 
72
        free(packet);
 
73
        exit(1);
 
74
    } else {
 
75
        (*test_cases[i])();
 
76
        free(packet);
 
77
    }
 
78
}
 
79
 
 
80
 
 
81
/***********************************************************************
 
82
 *
 
83
 * R e a d i n g   p a c k e t s
 
84
 *
 
85
 ************************************************************************/
 
86
 
 
87
/*
 
88
 * Reads an Erlang term.
 
89
 *
 
90
 * Only accepts 't' (term) or 'e' (end of test),
 
91
 * exits program on error
 
92
 * returns 1 on 'e', 0 on 't'
 
93
 */
 
94
int get_bin_term(ei_x_buff* x, ei_term* term)
 
95
{
 
96
    int len, version;
 
97
 
 
98
    ei_x_free(x);
 
99
    x->buff = read_packet(&len);
 
100
    x->buffsz = len;
 
101
    x->index = 0;
 
102
    switch (x->buff[x->index++]) {
 
103
    case 'e':
 
104
        return 1;
 
105
    case 't':
 
106
        if (ei_decode_version(x->buff, &x->index, &version) < 0
 
107
            || ei_decode_ei_term(x->buff, &x->index, term) < 0) {
 
108
            fail("Failed to decode term");
 
109
            exit(0);
 
110
        }
 
111
        return 0;
 
112
    default:
 
113
        fprintf(stderr, "Garbage received: ");
 
114
        dump(x->buff, len, 16);
 
115
        putc('\n', stderr);
 
116
        fail("C program received garbage");
 
117
        exit(1);
 
118
    }
 
119
}
 
120
 
 
121
 
 
122
/*
 
123
 * Reads a packet from Erlang.  The packet must be a standard {packet, 2}
 
124
 * packet.  This function aborts if any error is detected (including EOF).
 
125
 *
 
126
 * Returns: The number of bytes in the packet.
 
127
 */
 
128
 
 
129
char *read_packet(int *len)
 
130
{
 
131
 
 
132
    unsigned char* io_buf = NULL; /* Buffer for file i/o. */
 
133
    int i;
 
134
    unsigned char header[HEADER_SIZE];
 
135
    unsigned packet_length;     /* Length of current packet. */
 
136
    int bytes_read;
 
137
    
 
138
    /*
 
139
     * Read the packet header.
 
140
     */
 
141
    
 
142
    bytes_read = readn(fd_from_erl, header, HEADER_SIZE);
 
143
 
 
144
    if (bytes_read == 0) {
 
145
        fprintf(stderr, "%s: Unexpected end of file\n", progname);
 
146
        exit(1);
 
147
    }
 
148
    if (bytes_read != HEADER_SIZE) {
 
149
        fprintf(stderr, "%s: Failed to read packet header\n", progname);
 
150
        exit(1);
 
151
    }
 
152
 
 
153
    /*
 
154
     * Get the length of this packet.
 
155
     */
 
156
        
 
157
    packet_length = 0;
 
158
 
 
159
    for (i = 0; i < HEADER_SIZE; i++)
 
160
        packet_length = (packet_length << 8) | header[i];
 
161
 
 
162
    if (len) *len=packet_length; /* report length only if caller requested it */
 
163
    
 
164
    if ((io_buf = (char *) malloc(packet_length)) == NULL) {
 
165
        fprintf(stderr, "%s: insufficient memory for i/o buffer of size %d\n",
 
166
                progname, packet_length);
 
167
        exit(1);
 
168
    }
 
169
 
 
170
    /*
 
171
     * Read the packet itself.
 
172
     */
 
173
    
 
174
    bytes_read = readn(fd_from_erl, io_buf, packet_length);
 
175
    if (bytes_read != packet_length) {
 
176
        fprintf(stderr, "%s: couldn't read packet of length %d\r\n",
 
177
                progname, packet_length);
 
178
        free(io_buf);
 
179
        exit(1);
 
180
    }
 
181
 
 
182
    return io_buf;
 
183
}
 
184
 
 
185
 
 
186
/***********************************************************************
 
187
 * S e n d i n g   r e p l i e s
 
188
 *
 
189
 * The functions below send various types of replies back to Erlang.
 
190
 * Each reply start with a letter indicating the type of reply.
 
191
 *
 
192
 * Reply                Translated to on Erlang side
 
193
 * -----                ----------------------------
 
194
 * [$b|Bytes]           {bytes, Bytes}
 
195
 * [$e]                 eot
 
196
 * [$f]                 test_server:fail()
 
197
 * [$f|Reason]          test_server:fail(Reason)
 
198
 * [$t|EncodedTerm]     {term, Term}
 
199
 * [$N]                 'NULL'
 
200
 * [$m|Message]         io:format("~s", [Message])   (otherwise ignored)
 
201
 *
 
202
 ***********************************************************************/
 
203
 
 
204
/*
 
205
 * This function reports the outcome of a test fail.  It is useful if
 
206
 * you implement a test case entirely in C code.
 
207
 *
 
208
 * If the ok argument is zero, a [$f] reply will be sent to the
 
209
 * Erlang side (causing test_server:fail() to be called); otherwise,
 
210
 * the atom 'eot' will be sent to Erlang.
 
211
 *
 
212
 * If you need to provide more details on a failure, use the fail() function.
 
213
 */
 
214
 
 
215
void
 
216
do_report(file, line, ok)
 
217
    char* file;
 
218
    int line;
 
219
    int ok;                     /* Zero if failed; non-zero otherwise. */
 
220
{
 
221
    char reason;
 
222
    /*unsigned long ab;
 
223
    unsigned long fb;*/
 
224
 
 
225
    reason = ok ? 'e' : 'f';
 
226
 
 
227
    if (!ok) {
 
228
        do_fail(file, line, "Generic failure");
 
229
    } else {
 
230
        /* release all unallocated blocks */
 
231
        /*erl_eterm_release();*/
 
232
        /* check mem usage stats */
 
233
        /*erl_eterm_statistics(&ab, &fb);*/
 
234
        /*if ((ab == 0) && (fb == 0) ) {*/
 
235
            reply(&reason, 1);
 
236
        /*}
 
237
        else {
 
238
            char sbuf[128];
 
239
            
 
240
            sprintf(sbuf, "still %lu terms allocated,"
 
241
                    " %lu on freelist at end of test", ab, fb);
 
242
            do_fail(file, line, sbuf);
 
243
        }*/
 
244
    }
 
245
}
 
246
 
 
247
 
 
248
/*
 
249
 * This function causes a call to test_server:fail(Reason) on the
 
250
 * Erlang side.
 
251
 */
 
252
 
 
253
void do_fail(char* file, int line, char* reason)
 
254
{
 
255
    char sbuf[2048];
 
256
 
 
257
    sbuf[0] = 'f';
 
258
    sprintf(sbuf+1, "%s, line %d: %s", file, line, reason);
 
259
    reply(sbuf, 1+strlen(sbuf+1));
 
260
}
 
261
 
 
262
/*
 
263
 * This function sends a message to the Erlang side.
 
264
 * The message will be written to the test servers log file,
 
265
 * but will otherwise be completly ignored.
 
266
 */
 
267
 
 
268
void message(char* format, ...)
 
269
{
 
270
    va_list ap;
 
271
    char sbuf[1024];
 
272
 
 
273
    sbuf[0] = 'm';
 
274
    va_start(ap, format);
 
275
    vsprintf(sbuf+1, format, ap);
 
276
    va_end(ap);
 
277
 
 
278
    reply(sbuf, 1+strlen(sbuf+1));
 
279
}
 
280
 
 
281
/*
 
282
 * This function sends the given binary term to the Erlang side,
 
283
 * where it will be received as {term, Term} (prefix 't').
 
284
 */
 
285
void send_bin_term(ei_x_buff* x)
 
286
{
 
287
    ei_x_buff x2;
 
288
    ei_x_new(&x2);
 
289
    x2.buff[x2.index++] = 't';
 
290
    ei_x_append(&x2, x);
 
291
    reply(x2.buff, x2.index);
 
292
    ei_x_free(&x2);
 
293
}
 
294
 
 
295
/*
 
296
 * This function sends a raw buffer of data to the
 
297
 * Erlang side, where it will be received as {bytes, Bytes} (prefix 'b').
 
298
 */
 
299
void send_buffer(char* buf, int size)
 
300
{
 
301
    char* send_buf;
 
302
 
 
303
    send_buf = (char *) malloc(size+1);
 
304
    send_buf[0] = 'b';
 
305
    memcpy(send_buf+1, buf, size);
 
306
    reply(send_buf, size+1);
 
307
    free(send_buf);
 
308
}
 
309
 
 
310
/***********************************************************************
 
311
 *
 
312
 * P r i v a t e   h e l p e r s
 
313
 *
 
314
 ***********************************************************************/
 
315
 
 
316
/*
 
317
 * Sends a packet back to Erlang.
 
318
 */
 
319
static void reply(char* reply_buf, unsigned size)
 
320
{
 
321
    int n;                      /* Temporary to hold size. */
 
322
    int i;                      /* Loop counter. */
 
323
    char* buf;
 
324
 
 
325
 
 
326
    buf = (char *) malloc(size+HEADER_SIZE);
 
327
    memcpy(buf+HEADER_SIZE, reply_buf, size);
 
328
 
 
329
    /*
 
330
     * Fill the header starting with the least significant byte.
 
331
     */
 
332
    n = size;
 
333
    for (i = HEADER_SIZE-1; i >= 0; i--) {
 
334
        buf[i] = (char) n;      /* Store least significant byte. */
 
335
        n = n >> 8;
 
336
    }
 
337
 
 
338
    size += HEADER_SIZE;
 
339
    write(fd_to_erl, buf, size);
 
340
    free(buf);
 
341
}
 
342
 
 
343
 
 
344
/*
 
345
 * Reads len number of bytes.
 
346
 */
 
347
 
 
348
static int
 
349
readn(fd, buf, len)
 
350
    int fd;                     /* File descriptor to read from. */
 
351
    unsigned char *buf; /* Store in this buffer. */
 
352
    int len;                    /* Number of bytes to read. */
 
353
{
 
354
    int n;                      /* Byte count in last read call. */
 
355
    int sofar = 0;              /* Bytes read so far. */
 
356
 
 
357
    do {
 
358
        if ((n = read(fd, buf+sofar, len-sofar)) <= 0)
 
359
            /* error or EOF in read */
 
360
            return(n);
 
361
        sofar += n;
 
362
    } while (sofar < len);
 
363
    return sofar;
 
364
}
 
365
 
 
366
void
 
367
dump(buf, sz, max)
 
368
    unsigned char* buf;
 
369
    int sz;
 
370
    int max;
 
371
{
 
372
    int i, imax;
 
373
    char comma[5] = ",";
 
374
    
 
375
    if (!sz)
 
376
        return;
 
377
    if (sz > max)
 
378
        imax = max;
 
379
    else
 
380
        imax = sz;
 
381
    
 
382
    for (i=0; i<imax; i++) {
 
383
        if (i == imax-1) {
 
384
            if (sz > max)
 
385
                strcpy(comma, ",...");
 
386
            else
 
387
                comma[0] = 0;
 
388
        }
 
389
        if (isdigit(buf[i]))
 
390
            fprintf(stderr, "%u%s", (int)(buf[i]), comma);
 
391
        else {
 
392
            if (isalpha(buf[i])) {
 
393
                fprintf(stderr, "%c%s", buf[i], comma);
 
394
            }
 
395
            else
 
396
                fprintf(stderr, "%u%s", (int)(buf[i]), comma);
 
397
        }
 
398
    }
 
399
}
 
400