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

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/all_SUITE_data/runner.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 1997-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
#include <stdio.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 "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
 * Returns: A pointer to a term (an ETERM structure) if there was
 
91
 * at term available, or a NULL pointer if there was an 'eot' (end-of-test)
 
92
 * packet.  Aborts if anything else received.
 
93
 */
 
94
 
 
95
ETERM*
 
96
get_term(void)
 
97
{
 
98
    char* encoded;
 
99
    ETERM* term;
 
100
    int n;
 
101
 
 
102
    encoded = read_packet(&n);
 
103
 
 
104
    switch (encoded[0]) {
 
105
    case 'e':
 
106
      free(encoded);
 
107
      return NULL;
 
108
    case 't':
 
109
        term = erl_decode(encoded+1);
 
110
        free(encoded);
 
111
        if (term == NULL) {
 
112
            fail("Failed to decode term");
 
113
            exit(0);
 
114
        }
 
115
        return term;
 
116
    default:
 
117
        fprintf(stderr, "Garbage received: ");
 
118
        dump(encoded, n, 16);
 
119
        putc('\n', stderr);
 
120
        fail("C program received garbage");
 
121
        free(encoded);
 
122
        exit(1);
 
123
    }
 
124
}
 
125
 
 
126
 
 
127
/*
 
128
 * Reads a packet from Erlang.  The packet must be a standard {packet, 2}
 
129
 * packet.  This function aborts if any error is detected (including EOF).
 
130
 *
 
131
 * Returns: The number of bytes in the packet.
 
132
 */
 
133
 
 
134
char *read_packet(int *len)
 
135
{
 
136
 
 
137
  unsigned char* io_buf = NULL; /* Buffer for file i/o. */
 
138
  int i;
 
139
  unsigned char header[HEADER_SIZE];
 
140
  unsigned packet_length;               /* Length of current packet. */
 
141
  int bytes_read;
 
142
    
 
143
  /*
 
144
   * Read the packet header.
 
145
   */
 
146
    
 
147
  bytes_read = readn(fd_from_erl, header, HEADER_SIZE);
 
148
 
 
149
  if (bytes_read == 0) {
 
150
    fprintf(stderr, "%s: Unexpected end of file\n", progname);
 
151
    exit(1);
 
152
  }
 
153
  if (bytes_read != HEADER_SIZE) {
 
154
    fprintf(stderr, "%s: Failed to read packet header\n", progname);
 
155
    exit(1);
 
156
  }
 
157
 
 
158
  /*
 
159
   * Get the length of this packet.
 
160
   */
 
161
        
 
162
  packet_length = 0;
 
163
 
 
164
  for (i = 0; i < HEADER_SIZE; i++)
 
165
    packet_length = (packet_length << 8) | header[i];
 
166
    
 
167
  if (len) *len=packet_length; /* report length only if caller requested it */
 
168
 
 
169
  if ((io_buf = (char *) malloc(packet_length)) == NULL) {
 
170
    fprintf(stderr, "%s: insufficient memory for i/o buffer of size %d\n",
 
171
            progname, packet_length);
 
172
    exit(1);
 
173
  }
 
174
 
 
175
  /*
 
176
   * Read the packet itself.
 
177
   */
 
178
    
 
179
  bytes_read = readn(fd_from_erl, io_buf, packet_length);
 
180
  if (bytes_read != packet_length) {
 
181
    fprintf(stderr, "%s: couldn't read packet of length %d\r\n",
 
182
            progname, packet_length);
 
183
    free(io_buf);
 
184
    exit(1);
 
185
  }
 
186
 
 
187
  return io_buf;
 
188
}
 
189
 
 
190
 
 
191
/***********************************************************************
 
192
 * S e n d i n g   r e p l i e s
 
193
 *
 
194
 * The functions below send various types of replies back to Erlang.
 
195
 * Each reply start with a letter indicating the type of reply.
 
196
 *
 
197
 * Reply                Translated to on Erlang side
 
198
 * -----                ----------------------------
 
199
 * [$b|Bytes]           {bytes, Bytes}
 
200
 * [$e]                 eot
 
201
 * [$f]                 test_server:fail()
 
202
 * [$f|Reason]          test_server:fail(Reason)
 
203
 * [$t|EncodedTerm]     {term, Term}
 
204
 * [$N]                 'NULL'
 
205
 * [$m|Message]         io:format("~s", [Message])   (otherwise ignored)
 
206
 *
 
207
 ***********************************************************************/
 
208
 
 
209
/*
 
210
 * This function reports the outcome of a test fail.  It is useful if
 
211
 * you implement a test case entirely in C code.
 
212
 *
 
213
 * If the ok argument is zero, a [$f] reply will be sent to the
 
214
 * Erlang side (causing test_server:fail() to be called); otherwise,
 
215
 * the atom 'eot' will be sent to Erlang.
 
216
 *
 
217
 * If you need to provide more details on a failure, use the fail() function.
 
218
 */
 
219
 
 
220
void
 
221
do_report(file, line, ok)
 
222
    char* file;
 
223
    int line;
 
224
    int ok;                     /* Zero if failed; non-zero otherwise. */
 
225
{
 
226
    char reason;
 
227
    unsigned long ab;
 
228
    unsigned long fb;
 
229
 
 
230
    reason = ok ? 'e' : 'f';
 
231
 
 
232
    if (!ok) {
 
233
        do_fail(file, line, "Generic failure");
 
234
    } else {
 
235
      /* release all unallocated blocks */
 
236
      erl_eterm_release();
 
237
      /* check mem usage stats */
 
238
      erl_eterm_statistics(&ab, &fb);
 
239
      if ((ab == 0) && (fb == 0) ) {
 
240
        reply(&reason, 1);
 
241
      }
 
242
      else {
 
243
        char sbuf[128];
 
244
            
 
245
        sprintf(sbuf, "still %lu terms allocated,"
 
246
                " %lu on freelist at end of test", ab, fb);
 
247
        do_fail(file, line, sbuf);
 
248
      }
 
249
    }
 
250
}
 
251
 
 
252
 
 
253
/*
 
254
 * This function causes a call to test_server:fail(Reason) on the
 
255
 * Erlang side.
 
256
 */
 
257
 
 
258
void
 
259
do_fail(char* file, int line, char* reason)
 
260
{
 
261
    char sbuf[2048];
 
262
 
 
263
    sbuf[0] = 'f';
 
264
    sprintf(sbuf+1, "%s, line %d: %s", file, line, reason);
 
265
    reply(sbuf, 1+strlen(sbuf+1));
 
266
}
 
267
 
 
268
/*
 
269
 * This function sends a message to the Erlang side.
 
270
 * The message will be written to the test servers log file,
 
271
 * but will otherwise be completly ignored.
 
272
 */
 
273
 
 
274
void
 
275
message(char* format, ...)
 
276
{
 
277
    va_list ap;
 
278
    char sbuf[1024];
 
279
 
 
280
    sbuf[0] = 'm';
 
281
    va_start(ap, format);
 
282
    vsprintf(sbuf+1, format, ap);
 
283
    va_end(ap);
 
284
 
 
285
    reply(sbuf, 1+strlen(sbuf+1));
 
286
}
 
287
 
 
288
/*
 
289
 * This function sends the given term to the Erlang side,
 
290
 * where it will be received as {term, Term}.
 
291
 *
 
292
 * If the given pointer is NULL (indicating an invalid term),
 
293
 * the result on the Erlang side will be the atom 'NULL'.
 
294
 *
 
295
 * After sending the term, this function frees the term by
 
296
 * calling erl_free_term().
 
297
 */
 
298
 
 
299
void
 
300
send_term(term)
 
301
    ETERM* term;                /* Term to be sent to Erlang side. */
 
302
{
 
303
    char encoded[64*1024];
 
304
    int n;
 
305
 
 
306
    if (term == NULL) {
 
307
        encoded[0] = 'N';
 
308
        n = 1;
 
309
    } else {
 
310
        encoded[0] = 't';
 
311
        n = 1 + erl_encode(term, encoded+1);
 
312
        erl_free_term(term);
 
313
    }
 
314
    reply(encoded, n);
 
315
}
 
316
 
 
317
#if 0
 
318
 
 
319
/* Seriously broken!!! */
 
320
 
 
321
void
 
322
send_bin_term(x_ei_buff* x)
 
323
{
 
324
    x_ei_buff x2;
 
325
    x_ei_new(&x2);
 
326
    x2.buff[x2.index++] = 't';
 
327
    x_ei_append(&x2, x);
 
328
    reply(x2.buff, x2.index);
 
329
    free(x2.buff);
 
330
}
 
331
#endif
 
332
 
 
333
/*
 
334
 * This function sends a raw buffer of data to the
 
335
 * Erlang side, where it will be received as {bytes, Bytes}.
 
336
 */
 
337
 
 
338
void
 
339
send_buffer(buf, size)
 
340
    char* buf;                  /* Buffer with bytes to send to Erlang. */
 
341
    int size;                   /* Size of data to send to Erlang. */
 
342
{
 
343
    char* send_buf;
 
344
 
 
345
    send_buf = (char *) malloc(size+1);
 
346
    send_buf[0] = 'b';
 
347
    memcpy(send_buf+1, buf, size);
 
348
    reply(send_buf, size+1);
 
349
    free(send_buf);
 
350
}
 
351
 
 
352
/***********************************************************************
 
353
 *
 
354
 * P r i v a t e   h e l p e r s
 
355
 *
 
356
 ***********************************************************************/
 
357
 
 
358
/*
 
359
 * Sends a packet back to Erlang.
 
360
 */
 
361
 
 
362
static void
 
363
reply(reply_buf, size)
 
364
     char* reply_buf;           /* Buffer with reply. */
 
365
     unsigned size;             /* Size of reply. */
 
366
{
 
367
    int n;                      /* Temporary to hold size. */
 
368
    int i;                      /* Loop counter. */
 
369
    char* buf;
 
370
 
 
371
 
 
372
    buf = (char *) malloc(size+HEADER_SIZE);
 
373
    memcpy(buf+HEADER_SIZE, reply_buf, size);
 
374
 
 
375
    /*
 
376
     * Fill the header starting with the least significant byte.
 
377
     */
 
378
 
 
379
    n = size;
 
380
    for (i = HEADER_SIZE-1; i >= 0; i--) {
 
381
        buf[i] = (char) n;      /* Store least significant byte. */
 
382
        n = n >> 8;
 
383
    }
 
384
 
 
385
    size += HEADER_SIZE;
 
386
/*
 
387
    fprintf(stderr, "\r\nReply size: %u\r\n",
 
388
            (unsigned)buf[0] << 8 + (unsigned)buf[1]);
 
389
 
 
390
    for (i = 0; i < size; i++) {
 
391
        fprintf(stderr,"%u %c\r\n",buf[i],buf[i]);
 
392
    }
 
393
 
 
394
    fprintf(stderr, "\r\n");
 
395
*/
 
396
    write(fd_to_erl, buf, size);
 
397
    free(buf);
 
398
}
 
399
 
 
400
 
 
401
/*
 
402
 * Reads len number of bytes.
 
403
 */
 
404
 
 
405
static int
 
406
readn(fd, buf, len)
 
407
     int fd;                    /* File descriptor to read from. */
 
408
     unsigned char *buf;        /* Store in this buffer. */
 
409
     int len;                   /* Number of bytes to read. */
 
410
{
 
411
    int n;                      /* Byte count in last read call. */
 
412
    int sofar = 0;              /* Bytes read so far. */
 
413
 
 
414
    do {
 
415
        if ((n = read(fd, buf+sofar, len-sofar)) <= 0)
 
416
            /* error or EOF in read */
 
417
            return(n);
 
418
        sofar += n;
 
419
    } while (sofar < len);
 
420
    return sofar;
 
421
}
 
422
 
 
423
void
 
424
dump(buf, sz, max)
 
425
     unsigned char* buf;
 
426
     int sz;
 
427
     int max;
 
428
{
 
429
    int i, imax;
 
430
    char comma[5] = ",";
 
431
    
 
432
    if (!sz)
 
433
        return;
 
434
    if (sz > max)
 
435
        imax = max;
 
436
    else
 
437
        imax = sz;
 
438
    
 
439
    for (i=0; i<imax; i++) {
 
440
        if (i == imax-1) {
 
441
            if (sz > max)
 
442
                strcpy(comma, ",...");
 
443
            else
 
444
                comma[0] = 0;
 
445
        }
 
446
        if (isdigit(buf[i]))
 
447
            fprintf(stderr, "%u%s", (int)(buf[i]), comma);
 
448
        else {
 
449
            if (isalpha(buf[i])) {
 
450
                fprintf(stderr, "%c%s", buf[i], comma);
 
451
            }
 
452
            else
 
453
                fprintf(stderr, "%u%s", (int)(buf[i]), comma);
 
454
        }
 
455
    }
 
456
}
 
457