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

« back to all changes in this revision

Viewing changes to erts/lib_src/common/erl_printf.c

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
/* ``The contents of this file are subject to the Erlang Public License,
 
2
 * Version 1.1, (the "License"); you may not use this file except in
 
3
 * compliance with the License. You should have received a copy of the
 
4
 * Erlang Public License along with this software. If not, it can be
 
5
 * retrieved via the world wide web at http://www.erlang.org/.
 
6
 * 
 
7
 * Software distributed under the License is distributed on an "AS IS"
 
8
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
 * the License for the specific language governing rights and limitations
 
10
 * under the License.
 
11
 * 
 
12
 * The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
 * Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
 * AB. All Rights Reserved.''
 
15
 * 
 
16
 *     $Id$
 
17
 */
 
18
 
 
19
/* Without this, variable argument lists break on VxWorks */
 
20
#ifdef VXWORKS
 
21
#include <vxWorks.h>
 
22
#endif
 
23
 
 
24
#ifdef HAVE_CONFIG_H
 
25
#include "config.h"
 
26
#endif
 
27
 
 
28
#include <string.h>
 
29
#include <errno.h>
 
30
#ifdef __WIN32__
 
31
#       include <io.h>
 
32
#else
 
33
#       include <unistd.h>
 
34
#endif
 
35
#include "erl_printf.h"
 
36
#include "erl_printf_format.h"
 
37
 
 
38
#ifdef DEBUG
 
39
#include <assert.h>
 
40
#define ASSERT(X) assert(X)
 
41
#else
 
42
#define ASSERT(X) 
 
43
#endif
 
44
 
 
45
#if defined(__WIN32__) && !defined(__GNUC__)
 
46
typedef int ssize_t;
 
47
#endif
 
48
 
 
49
int (*erts_printf_stdout_func)(char *, va_list) = NULL;
 
50
int (*erts_printf_stderr_func)(char *, va_list) = NULL;
 
51
 
 
52
int erts_printf_add_cr_to_stdout = 0;
 
53
int erts_printf_add_cr_to_stderr = 0;
 
54
 
 
55
#undef FLOCKFILE
 
56
#undef FUNLOCKFILE
 
57
#undef PUTC
 
58
#undef FWRITE
 
59
#undef PUTC_ON_SMALL_WRITES
 
60
 
 
61
#if defined(USE_THREADS) && defined(HAVE_FLOCKFILE)
 
62
#       define FLOCKFILE(FP)    flockfile(FP)
 
63
#       define FUNLOCKFILE(FP)  funlockfile(FP)
 
64
#       ifdef HAVE_PUTC_UNLOCKED
 
65
#               define PUTC     putc_unlocked
 
66
#               define PUTC_ON_SMALL_WRITES
 
67
#       endif
 
68
#       ifdef HAVE_FWRITE_UNLOCKED
 
69
#               define FWRITE   fwrite_unlocked
 
70
#       endif
 
71
#endif
 
72
#if !defined(USE_THREADS) && defined(putc) && !defined(fwrite)
 
73
#       define PUTC_ON_SMALL_WRITES
 
74
#endif
 
75
#if !defined(FLOCKFILE) || !defined(FUNLOCKFILE)
 
76
#       define FLOCKFILE(FP)
 
77
#       define FUNLOCKFILE(FP)
 
78
#endif
 
79
#ifndef PUTC
 
80
#       define PUTC putc
 
81
#endif
 
82
#ifndef FWRITE
 
83
#       define FWRITE fwrite
 
84
#endif
 
85
 
 
86
static int
 
87
get_error_result(void)
 
88
{
 
89
    int res = errno;
 
90
    if (res <= 0)
 
91
        res = EIO;
 
92
    return -res;
 
93
}
 
94
 
 
95
 
 
96
static int
 
97
write_f_add_cr(void *vfp, char* buf, size_t len)
 
98
{
 
99
    size_t i;
 
100
    ASSERT(vfp);
 
101
    for (i = 0; i < len; i++) {
 
102
        if (buf[i] == '\n' && PUTC('\r', (FILE *) vfp) == EOF)
 
103
            return get_error_result();
 
104
        if (PUTC(buf[i], (FILE *) vfp) == EOF)
 
105
            return get_error_result();
 
106
    }
 
107
    return 0;
 
108
}
 
109
 
 
110
static int
 
111
write_f(void *vfp, char* buf, size_t len)
 
112
{
 
113
    ASSERT(vfp);
 
114
#ifdef PUTC_ON_SMALL_WRITES
 
115
    if (len <= 64) { /* Try to optimize writes of small bufs. */
 
116
        int i;
 
117
        for (i = 0; i < len; i++)
 
118
            if (PUTC(buf[i], (FILE *) vfp) == EOF)
 
119
                return get_error_result();
 
120
    }
 
121
    else
 
122
#endif
 
123
    if (FWRITE((void *) buf, sizeof(char), len, (FILE *) vfp) != len)
 
124
        return get_error_result();
 
125
    return 0;
 
126
}
 
127
 
 
128
static int
 
129
write_fd(void *vfdp, char* buf, size_t len)
 
130
{
 
131
    ssize_t size;
 
132
    ASSERT(vfdp);
 
133
 
 
134
    while (len) {
 
135
        size = write(*((int *) vfdp), (void *) buf, len);
 
136
        if (size < 0) {
 
137
#ifdef EINTR
 
138
            if (errno == EINTR)
 
139
                continue;
 
140
#endif
 
141
            return get_error_result();
 
142
        }
 
143
        if (size > len)
 
144
            return -EIO;
 
145
        len -= size;
 
146
    }
 
147
 
 
148
    return 0;
 
149
}
 
150
 
 
151
static int
 
152
write_s(void *vwbufpp, char* bufp, size_t len)
 
153
{
 
154
    char **wbufpp = (char **) vwbufpp;
 
155
    ASSERT(wbufpp && *wbufpp);
 
156
    ASSERT(len > 0);
 
157
    memcpy((void *) *wbufpp, (void *) bufp, len);
 
158
    *wbufpp += len;
 
159
    return 0;
 
160
}
 
161
 
 
162
 
 
163
typedef struct {
 
164
    char *buf;
 
165
    size_t len;
 
166
} write_sn_arg_t;
 
167
 
 
168
static int
 
169
write_sn(void *vwsnap, char* buf, size_t len)
 
170
{
 
171
    write_sn_arg_t *wsnap = (write_sn_arg_t *) vwsnap;
 
172
    ASSERT(wsnap);
 
173
    ASSERT(len > 0);
 
174
    if (wsnap->len > 0) {
 
175
        size_t sz = len;
 
176
        if (sz >= wsnap->len)
 
177
            sz = wsnap->len;
 
178
        memcpy((void *) wsnap->buf, (void *) buf, sz);
 
179
        wsnap->buf += sz;
 
180
        wsnap->len -= sz;
 
181
    }
 
182
    return 0;
 
183
}
 
184
 
 
185
static int
 
186
write_ds(void *vdsbufp, char* buf, size_t len)
 
187
{
 
188
    erts_dsprintf_buf_t *dsbufp = (erts_dsprintf_buf_t *) vdsbufp;
 
189
    size_t need_len = len + 1; /* Also trailing '\0' */
 
190
    ASSERT(dsbufp);
 
191
    ASSERT(len > 0);
 
192
    ASSERT(dsbufp->str_len <= dsbufp->size);
 
193
    if (need_len > dsbufp->size - dsbufp->str_len) {
 
194
        dsbufp = (*dsbufp->grow)(dsbufp, need_len);
 
195
        if (!dsbufp)
 
196
            return -ENOMEM;
 
197
    }
 
198
    memcpy((void *) (dsbufp->str + dsbufp->str_len), (void *) buf, len);
 
199
    dsbufp->str_len += len;
 
200
    return 0;
 
201
}
 
202
 
 
203
int
 
204
erts_printf(const char *format, ...)
 
205
{
 
206
    int res;
 
207
    va_list arglist;
 
208
    va_start(arglist, format);
 
209
    errno = 0;
 
210
    if (erts_printf_stdout_func)
 
211
        res = (*erts_printf_stdout_func)((char *) format, arglist);
 
212
    else {
 
213
        FLOCKFILE(stdout);
 
214
        res = erts_printf_format(erts_printf_add_cr_to_stdout
 
215
                                 ? write_f_add_cr
 
216
                                 : write_f,
 
217
                                 (void *) stdout,
 
218
                                 (char *) format,
 
219
                                 arglist);
 
220
        FUNLOCKFILE(stdout);
 
221
    }
 
222
    va_end(arglist);
 
223
    return res;
 
224
}
 
225
 
 
226
int
 
227
erts_fprintf(FILE *filep, const char *format, ...)
 
228
{
 
229
    int res;
 
230
    va_list arglist;
 
231
    va_start(arglist, format);
 
232
    errno = 0;
 
233
    if (erts_printf_stdout_func && filep == stdout)
 
234
        res = (*erts_printf_stdout_func)((char *) format, arglist);
 
235
    else if (erts_printf_stderr_func && filep == stderr)
 
236
        res = (*erts_printf_stderr_func)((char *) format, arglist);
 
237
    else {
 
238
        int (*fmt_f)(void*, char*, size_t);
 
239
        if (erts_printf_add_cr_to_stdout && filep == stdout)
 
240
            fmt_f = write_f_add_cr;
 
241
        else if (erts_printf_add_cr_to_stderr && filep == stderr)
 
242
            fmt_f = write_f_add_cr;
 
243
        else
 
244
            fmt_f = write_f;
 
245
        FLOCKFILE(filep);
 
246
        res = erts_printf_format(fmt_f,(void *)filep,(char *)format,arglist);
 
247
        FUNLOCKFILE(filep);
 
248
    }
 
249
    va_end(arglist);
 
250
    return res;
 
251
}
 
252
 
 
253
int
 
254
erts_fdprintf(int fd, const char *format, ...)
 
255
{
 
256
    int res;
 
257
    va_list arglist;
 
258
    va_start(arglist, format);
 
259
    errno = 0;
 
260
    res = erts_printf_format(write_fd,(void *)&fd,(char *)format,arglist);
 
261
    va_end(arglist);
 
262
    return res;
 
263
}
 
264
 
 
265
int
 
266
erts_sprintf(char *buf, const char *format, ...)
 
267
{
 
268
    int res;
 
269
    char *p = buf;
 
270
    va_list arglist;
 
271
    va_start(arglist, format);
 
272
    errno = 0;
 
273
    res = erts_printf_format(write_s, (void *) &p, (char *) format, arglist);
 
274
    if (res < 0)
 
275
        buf[0] = '\0';
 
276
    else
 
277
        buf[res] = '\0';
 
278
    va_end(arglist);
 
279
    return res;
 
280
}
 
281
 
 
282
int
 
283
erts_snprintf(char *buf, size_t size, const char *format, ...)
 
284
{
 
285
    write_sn_arg_t wsnap;
 
286
    int res;
 
287
    va_list arglist;
 
288
    if (size < 1)
 
289
        return -EINVAL;
 
290
    wsnap.buf = buf;
 
291
    wsnap.len = size-1; /* Always need room for trailing '\0' */
 
292
    va_start(arglist, format);
 
293
    errno = 0;
 
294
    res = erts_printf_format(write_sn, (void *)&wsnap, (char *)format, arglist);
 
295
    if (res < 0)
 
296
        buf[0] = '\0';
 
297
    else if (res < size)
 
298
        buf[res] = '\0';
 
299
    else
 
300
        buf[size-1] = '\0';
 
301
    va_end(arglist);
 
302
    return res;
 
303
}
 
304
 
 
305
int
 
306
erts_dsprintf(erts_dsprintf_buf_t *dsbufp, const char *format, ...)
 
307
{
 
308
    int res;
 
309
    va_list arglist;
 
310
    if (!dsbufp)
 
311
        return -EINVAL;
 
312
    va_start(arglist, format);
 
313
    errno = 0;
 
314
    res = erts_printf_format(write_ds, (void *)dsbufp, (char *)format, arglist);
 
315
    if (dsbufp->str) {
 
316
        if (res < 0)
 
317
            dsbufp->str[0] = '\0';
 
318
        else
 
319
            dsbufp->str[dsbufp->str_len] = '\0';
 
320
    }
 
321
    va_end(arglist);
 
322
    return res;
 
323
}
 
324
 
 
325
int
 
326
erts_vprintf(const char *format, va_list arglist)
 
327
{       
 
328
    int res;
 
329
    if (erts_printf_stdout_func)
 
330
        res = (*erts_printf_stdout_func)((char *) format, arglist);
 
331
    else {
 
332
        errno = 0;
 
333
        res = erts_printf_format(erts_printf_add_cr_to_stdout
 
334
                                 ? write_f_add_cr
 
335
                                 : write_f,
 
336
                                 (void *) stdout,
 
337
                                 (char *) format,
 
338
                                 arglist);
 
339
    }
 
340
    return res;
 
341
}
 
342
 
 
343
int
 
344
erts_vfprintf(FILE *filep, const char *format, va_list arglist)
 
345
{
 
346
    int res;
 
347
    if (erts_printf_stdout_func && filep == stdout)
 
348
        res = (*erts_printf_stdout_func)((char *) format, arglist);
 
349
    else if (erts_printf_stderr_func && filep == stderr)
 
350
        res = (*erts_printf_stderr_func)((char *) format, arglist);
 
351
    else {
 
352
        int (*fmt_f)(void*, char*, size_t);
 
353
        errno = 0;
 
354
        if (erts_printf_add_cr_to_stdout && filep == stdout)
 
355
            fmt_f = write_f_add_cr;
 
356
        else if (erts_printf_add_cr_to_stderr && filep == stderr)
 
357
            fmt_f = write_f_add_cr;
 
358
        else
 
359
            fmt_f = write_f;
 
360
        res = erts_printf_format(fmt_f,(void *)filep,(char *)format,arglist);
 
361
    }
 
362
    return res;
 
363
}
 
364
 
 
365
int
 
366
erts_vfdprintf(int fd, const char *format, va_list arglist)
 
367
{
 
368
    int res;
 
369
    errno = 0;
 
370
    res = erts_printf_format(write_fd,(void *)&fd,(char *)format,arglist);
 
371
    return res;
 
372
}
 
373
 
 
374
int
 
375
erts_vsprintf(char *buf, const char *format, va_list arglist)
 
376
{
 
377
    int res;
 
378
    char *p = buf;
 
379
    errno = 0;
 
380
    res = erts_printf_format(write_s, (void *) &p, (char *) format, arglist);
 
381
    if (res < 0)
 
382
        buf[0] = '\0';
 
383
    else
 
384
        buf[res] = '\0';
 
385
    return res;
 
386
}
 
387
 
 
388
int
 
389
erts_vsnprintf(char *buf, size_t size, const char *format,  va_list arglist)
 
390
{
 
391
    write_sn_arg_t wsnap;
 
392
    int res;
 
393
    if (size < 1)
 
394
        return -EINVAL;
 
395
    wsnap.buf = buf;
 
396
    wsnap.len = size-1; /* Always need room for trailing '\0' */
 
397
    errno = 0;
 
398
    res = erts_printf_format(write_sn, (void *)&wsnap, (char *)format, arglist);
 
399
    if (res < 0)
 
400
        buf[0] = '\0';
 
401
    else if (res < size)
 
402
        buf[res] = '\0';
 
403
    else
 
404
        buf[size-1] = '\0';
 
405
    return res;
 
406
}
 
407
 
 
408
int
 
409
erts_vdsprintf(erts_dsprintf_buf_t *dsbufp, const char *format, va_list arglist)
 
410
{
 
411
    int res;
 
412
    if (!dsbufp)
 
413
        return -EINVAL;
 
414
    errno = 0;
 
415
    res = erts_printf_format(write_ds, (void *)dsbufp, (char *)format, arglist);
 
416
    if (dsbufp->str) {
 
417
        if (res < 0)
 
418
            dsbufp->str[0] = '\0';
 
419
        else
 
420
            dsbufp->str[dsbufp->str_len] = '\0';
 
421
    }
 
422
    return res;
 
423
}