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

« back to all changes in this revision

Viewing changes to erts/emulator/sys/unix/sys_float.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:
21
21
#endif
22
22
 
23
23
#include "sys.h"
24
 
 
25
 
 
26
 
volatile int erl_fp_exception = 0;
 
24
#include "global.h"
 
25
#include "erl_process.h"
 
26
 
27
27
 
28
28
#ifdef NO_FPE_SIGNALS
29
29
 
35
35
# endif
36
36
}
37
37
 
 
38
static ERTS_INLINE void set_current_fp_exception(void)
 
39
{
 
40
    /* nothing to do */
 
41
}
 
42
 
38
43
#else  /* !NO_FPE_SIGNALS */
39
44
 
40
 
#if defined(__i386__) && defined(__GNUC__)
41
 
 
42
 
static void unmask_fpe(void)
 
45
#ifdef ERTS_SMP
 
46
static erts_tsd_key_t fpe_key;
 
47
 
 
48
/* once-only initialisation early in the main thread (via erts_sys_init_float()) */
 
49
static void erts_init_fp_exception(void)
 
50
{
 
51
    /* XXX: the wrappers prevent using a pthread destructor to
 
52
       deallocate the key's value; so when/where do we do that? */
 
53
    erts_tsd_key_create(&fpe_key);
 
54
}
 
55
 
 
56
void erts_thread_init_fp_exception(void)
 
57
{
 
58
    int *fpe = erts_alloc(ERTS_ALC_T_FP_EXCEPTION, sizeof(*fpe));
 
59
    erts_tsd_set(fpe_key, fpe);
 
60
}
 
61
 
 
62
static ERTS_INLINE volatile int *erts_thread_get_fp_exception(void)
 
63
{
 
64
    return (volatile int*)erts_tsd_get(fpe_key);
 
65
}
 
66
#else /* !SMP */
 
67
#define erts_init_fp_exception()        /*empty*/
 
68
static volatile int fp_exception;
 
69
#define erts_thread_get_fp_exception()  (&fp_exception)
 
70
#endif /* SMP */
 
71
 
 
72
volatile int *erts_get_current_fp_exception(void)
 
73
{
 
74
    Process *c_p;
 
75
 
 
76
    c_p = erts_get_current_process();
 
77
    if (c_p)
 
78
        return &c_p->fp_exception;
 
79
    return erts_thread_get_fp_exception();
 
80
}
 
81
 
 
82
static void set_current_fp_exception(void)
 
83
{
 
84
    volatile int *fpexnp = erts_get_current_fp_exception();
 
85
    ASSERT(fpexnp != NULL);
 
86
    *fpexnp = 1;
 
87
}
 
88
 
 
89
/* Is there no standard identifier for Darwin/MacOSX ? */
 
90
#if defined(__APPLE__) && defined(__MACH__) && !defined(__DARWIN__)
 
91
#define __DARWIN__ 1
 
92
#endif
 
93
 
 
94
#if (defined(__i386__) || defined(__x86_64__)) && defined(__GNUC__)
 
95
 
 
96
static void unmask_x87(void)
43
97
{
44
98
    unsigned short cw;
45
99
    __asm__ __volatile__("fstcw %0" : "=m"(cw));
47
101
    __asm__ __volatile__("fldcw %0" : : "m"(cw));
48
102
}
49
103
 
50
 
void erts_restore_x87(void)
 
104
static void unmask_sse2(void)
 
105
{
 
106
    unsigned int mxcsr;
 
107
    __asm__ __volatile__("stmxcsr %0" : "=m"(mxcsr));
 
108
    mxcsr &= ~(0x003F|0x0680); /* clear exn flags, unmask OM, ZM, IM (not PM, UM, DM) */
 
109
    __asm__ __volatile__("ldmxcsr %0" : : "m"(mxcsr));
 
110
}
 
111
 
 
112
#if defined(__x86_64__) || defined(__DARWIN__)
 
113
static inline int cpu_has_sse2(void) { return 1; }
 
114
#else /* !__x86_64__ */
 
115
/*
 
116
 * Check if an x86-32 processor has SSE2.
 
117
 */
 
118
static unsigned int xor_eflags(unsigned int mask)
 
119
{
 
120
    unsigned int eax, edx;
 
121
 
 
122
    eax = mask;                 /* eax = mask */
 
123
    __asm__("pushfl\n\t"
 
124
            "popl %0\n\t"       /* edx = original EFLAGS */
 
125
            "xorl %0, %1\n\t"   /* eax = mask ^ EFLAGS */
 
126
            "pushl %1\n\t"
 
127
            "popfl\n\t"         /* new EFLAGS = mask ^ original EFLAGS */
 
128
            "pushfl\n\t"
 
129
            "popl %1\n\t"       /* eax = new EFLAGS */
 
130
            "xorl %0, %1\n\t"   /* eax = new EFLAGS ^ old EFLAGS */
 
131
            "pushl %0\n\t"
 
132
            "popfl"             /* restore original EFLAGS */
 
133
            : "=d"(edx), "=a"(eax)
 
134
            : "1"(eax));
 
135
    return eax;
 
136
}
 
137
 
 
138
static __inline__ unsigned int cpuid_eax(unsigned int op)
 
139
{
 
140
    unsigned int eax;
 
141
    __asm__("cpuid"
 
142
            : "=a"(eax)
 
143
            : "0"(op)
 
144
            : "bx", "cx", "dx");
 
145
    return eax;
 
146
}
 
147
 
 
148
static __inline__ unsigned int cpuid_edx(unsigned int op)
 
149
{
 
150
    unsigned int eax, edx;
 
151
    __asm__("cpuid"
 
152
            : "=a"(eax), "=d"(edx)
 
153
            : "0"(op)
 
154
            : "bx", "cx");
 
155
    return edx;
 
156
}
 
157
 
 
158
/* The AC bit, bit #18, is a new bit introduced in the EFLAGS
 
159
 * register on the Intel486 processor to generate alignment
 
160
 * faults. This bit cannot be set on the Intel386 processor.
 
161
 */
 
162
static __inline__ int is_386(void)
 
163
{
 
164
    return ((xor_eflags(1<<18) >> 18) & 1) == 0;
 
165
}
 
166
 
 
167
/* Newer x86 processors have a CPUID instruction, as indicated by
 
168
 * the ID bit (#21) in EFLAGS being modifiable.
 
169
 */
 
170
static __inline__ int has_CPUID(void)
 
171
{
 
172
    return (xor_eflags(1<<21) >> 21) & 1;
 
173
}
 
174
 
 
175
static int cpu_has_sse2(void)
 
176
{
 
177
    unsigned int maxlev, features;
 
178
    static int has_sse2 = -1;
 
179
 
 
180
    if (has_sse2 >= 0)
 
181
        return has_sse2;
 
182
    has_sse2 = 0;
 
183
 
 
184
    if (is_386())
 
185
        return 0;
 
186
    if (!has_CPUID())
 
187
        return 0;
 
188
    maxlev = cpuid_eax(0);
 
189
    /* Intel A-step Pentium had a preliminary version of CPUID.
 
190
       It also didn't have SSE2. */
 
191
    if ((maxlev & 0xFFFFFF00) == 0x0500)
 
192
        return 0;
 
193
    /* If max level is zero then CPUID cannot report any features. */
 
194
    if (maxlev == 0)
 
195
        return 0;
 
196
    features = cpuid_edx(1);
 
197
    has_sse2 = (features & (1 << 26)) != 0;
 
198
 
 
199
    return has_sse2;
 
200
}
 
201
#endif /* !__x86_64__ */
 
202
 
 
203
static void unmask_fpe(void)
 
204
{
 
205
    unmask_x87();
 
206
    if (cpu_has_sse2())
 
207
        unmask_sse2();
 
208
}
 
209
 
 
210
void erts_restore_fpu(void)
51
211
{
52
212
    __asm__ __volatile__("fninit");
53
 
    unmask_fpe();
54
 
}
55
 
 
56
 
#else  /* !(__i386__ && __GNUC__) */
 
213
    unmask_x87();
 
214
}
 
215
 
 
216
#elif defined(__sparc__) && defined(__linux__)
 
217
 
 
218
static void unmask_fpe(void)
 
219
{
 
220
    unsigned long fsr;
 
221
 
 
222
    __asm__("st %%fsr, %0" : "=m"(fsr));
 
223
    fsr &= ~(0x1FUL << 23);     /* clear FSR[TEM] field */
 
224
    fsr |= (0x1AUL << 23);      /* enable NV, OF, DZ exceptions */
 
225
    __asm__ __volatile__("ld %0, %%fsr" : : "m"(fsr));
 
226
}
 
227
 
 
228
#elif (defined(__powerpc__) && defined(__linux__)) || (defined(__ppc__) && defined(__DARWIN__))
 
229
 
 
230
#if defined(__linux__)
 
231
#include <sys/prctl.h>
 
232
 
 
233
static void set_fpexc_precise(void)
 
234
{
 
235
    if (prctl(PR_SET_FPEXC, PR_FP_EXC_PRECISE) < 0) {
 
236
        perror("PR_SET_FPEXC");
 
237
        exit(1);
 
238
    }
 
239
}
 
240
 
 
241
#elif defined(__DARWIN__)
 
242
 
 
243
#include <mach/mach.h>
 
244
#include <pthread.h>
 
245
 
 
246
/*
 
247
 * FE0 FE1      MSR bits
 
248
 *  0   0       floating-point exceptions disabled
 
249
 *  0   1       floating-point imprecise nonrecoverable
 
250
 *  1   0       floating-point imprecise recoverable
 
251
 *  1   1       floating-point precise mode
 
252
 *
 
253
 * Apparently:
 
254
 * - Darwin 5.5 (MacOS X <= 10.1) starts with FE0 == FE1 == 0,
 
255
 *   and resets FE0 and FE1 to 0 after each SIGFPE.
 
256
 * - Darwin 6.0 (MacOS X 10.2) starts with FE0 == FE1 == 1,
 
257
 *   and does not reset FE0 or FE1 after a SIGFPE.
 
258
 */
 
259
#define FE0_MASK        (1<<11)
 
260
#define FE1_MASK        (1<<8)
 
261
 
 
262
/* a thread cannot get or set its own MSR bits */
 
263
static void *fpu_fpe_enable(void *arg)
 
264
{
 
265
    thread_t t = *(thread_t*)arg;
 
266
    struct ppc_thread_state state;
 
267
    unsigned int state_size = PPC_THREAD_STATE_COUNT;
 
268
 
 
269
    if (thread_get_state(t, PPC_THREAD_STATE, (natural_t*)&state, &state_size) != KERN_SUCCESS) {
 
270
        perror("thread_get_state");
 
271
        exit(1);
 
272
    }
 
273
    if ((state.srr1 & (FE1_MASK|FE0_MASK)) != (FE1_MASK|FE0_MASK)) {
 
274
#if 0
 
275
        /* This would also have to be performed in the SIGFPE handler
 
276
           to work around the MSR reset older Darwin releases do. */
 
277
        state.srr1 |= (FE1_MASK|FE0_MASK);
 
278
        thread_set_state(t, PPC_THREAD_STATE, (natural_t*)&state, state_size);
 
279
#else
 
280
        fprintf(stderr, "srr1 == 0x%08x, your Darwin is too old\n", state.srr1);
 
281
        exit(1);
 
282
#endif
 
283
    }
 
284
    return NULL; /* Ok, we appear to be on Darwin 6.0 or later */
 
285
}
 
286
 
 
287
static void set_fpexc_precise(void)
 
288
{
 
289
    thread_t self = mach_thread_self();
 
290
    pthread_t enabler;
 
291
 
 
292
    if (pthread_create(&enabler, NULL, fpu_fpe_enable, &self)) {
 
293
        perror("pthread_create");
 
294
    } else if (pthread_join(enabler, NULL)) {
 
295
        perror("pthread_join");
 
296
    }
 
297
}
 
298
 
 
299
#endif
 
300
 
 
301
static void set_fpscr(unsigned int fpscr)
 
302
{
 
303
    union {
 
304
        double d;
 
305
        unsigned int fpscr[2];
 
306
    } u;
 
307
    u.fpscr[0] = 0xFFF80000;
 
308
    u.fpscr[1] = fpscr;
 
309
    __asm__ __volatile__("mtfsf 255,%0" : : "f"(u.d));
 
310
}
 
311
 
 
312
static void unmask_fpe(void)
 
313
{
 
314
    set_fpexc_precise();
 
315
    set_fpscr(0x80|0x40|0x10);  /* VE, OE, ZE; not UE or XE */
 
316
}
 
317
 
 
318
#else
57
319
 
58
320
#define unmask_fpe()   fpsetmask(FP_X_INV | FP_X_OFL | FP_X_DZ)
59
321
 
60
 
#endif /* __i386__ && __GNUC__ */
 
322
#endif
 
323
 
 
324
#if (defined(__linux__) && (defined(__x86_64__) || defined(__i386__))) || (defined(__DARWIN__) && defined(__i386__)) || (defined(__FreeBSD__) && defined(__x86_64__)) || (defined(__sun__) && defined(__x86_64__))
 
325
#include <ucontext.h>
 
326
 
 
327
#if defined(__linux__) && defined(__x86_64__)
 
328
#define mc_pc(mc)       ((mc)->gregs[REG_RIP])
 
329
typedef mcontext_t *erts_mcontext_ptr_t;
 
330
#elif defined(__linux__) && defined(__i386__)
 
331
#define mc_pc(mc)       ((mc)->gregs[REG_EIP])
 
332
typedef mcontext_t *erts_mcontext_ptr_t;
 
333
#elif defined(__DARWIN__) && defined(__i386__)
 
334
#define mc_pc(mc)       ((mc)->ss.eip)
 
335
typedef mcontext_t erts_mcontext_ptr_t;
 
336
#elif defined(__FreeBSD__) && defined(__x86_64__)
 
337
#define mc_pc(mc)       ((mc)->mc_rip)
 
338
typedef mcontext_t *erts_mcontext_ptr_t;
 
339
#elif defined(__sun__) && defined(__x86_64__)
 
340
#define mc_pc(mc)       ((mc)->gregs[REG_RIP])
 
341
typedef mcontext_t *erts_mcontext_ptr_t;
 
342
#endif
 
343
 
 
344
static void skip_sse2_insn(erts_mcontext_ptr_t mc)
 
345
{
 
346
    unsigned char *pc0 = (unsigned char*)mc_pc(mc);
 
347
    unsigned char *pc = pc0;
 
348
    unsigned int opcode;
 
349
    unsigned int nr_skip_bytes;
 
350
 
 
351
    opcode = *pc++;
 
352
    switch (opcode) {
 
353
    case 0x66: case 0xF2: case 0xF3:
 
354
        opcode = *pc++;
 
355
    }
 
356
#if defined(__x86_64__)
 
357
    if ((opcode & 0xF0) == 0x40)
 
358
        opcode = *pc++;
 
359
#endif
 
360
    do {
 
361
        switch (opcode) {
 
362
        case 0x0F:
 
363
            opcode = *pc++;
 
364
            switch (opcode) {
 
365
            case 0x2A: /* cvtpi2ps,cvtsi2sd,cvtsi2ss /r */
 
366
            case 0x2C: /* cvttpd2pi,cvttps2pi,cvttsd2si,cvtss2si /r */
 
367
            case 0x2D: /* cvtpd2pi,cvtps2pi,cvtsd2si,cvtss2si /r */
 
368
            case 0x2E: /* ucomisd,ucomiss /r */
 
369
            case 0x2F: /* comisd,comiss /r */
 
370
            case 0x51: /* sqrtpd,sqrtps,sqrtsd,sqrtss /r */
 
371
            case 0x58: /* addpd,addps,addsd,addss /r */
 
372
            case 0x59: /* mulpd,mulps,mulsd,mulss /r */
 
373
            case 0x5A: /* cvtpd2ps,cvtps2pd,cvtsd2ss,cvtss2sd /r */
 
374
            case 0x5B: /* cvtdq2ps,cvtps2dq,cvttps2dq /r */
 
375
            case 0x5C: /* subpd,subps,subsd,subss /r */
 
376
            case 0x5D: /* minpd,minps,minsd,minss /r */
 
377
            case 0x5E: /* divpd,divps,divsd,divss /r */
 
378
            case 0x5F: /* maxpd,maxps,maxsd,maxss /r */
 
379
            case 0xE6: /* cvtpd2dq,cvttpd2dq /r */
 
380
                nr_skip_bytes = 0;
 
381
                continue;
 
382
            case 0xC2: /* cmppd,cmpps,cmpsd,cmpss /r /ib */
 
383
                nr_skip_bytes = 1;
 
384
                continue;
 
385
            }
 
386
        }
 
387
        fprintf(stderr, "%s: unexpected code at %p:", __FUNCTION__, pc0);
 
388
        do {
 
389
            fprintf(stderr, " %02X", *pc0++);
 
390
        } while (pc0 < pc);
 
391
        fprintf(stderr, "\r\n");
 
392
        abort();
 
393
    } while (0);
 
394
 
 
395
    /* Past the opcode. Parse and skip the mod/rm and sib bytes. */
 
396
    opcode = *pc++;
 
397
    switch ((opcode >> 6) & 3) {        /* inspect mod */
 
398
    case 0:
 
399
        switch (opcode & 7) {           /* inspect r/m */
 
400
        case 4:
 
401
            opcode = *pc++;             /* sib */
 
402
            switch (opcode & 7) {       /* inspect base */
 
403
            case 5:
 
404
                nr_skip_bytes += 4;     /* disp32 */
 
405
                break;
 
406
            }
 
407
            break;
 
408
        case 5:
 
409
            nr_skip_bytes += 4;         /* disp32 */
 
410
            break;
 
411
        }
 
412
        break;
 
413
    case 1:
 
414
        nr_skip_bytes += 1;             /* disp8 */
 
415
        switch (opcode & 7) {           /* inspect r/m */
 
416
        case 4:
 
417
            pc += 1;                    /* sib */
 
418
            break;
 
419
        }
 
420
        break;
 
421
    case 2:
 
422
        nr_skip_bytes += 4;             /* disp32 */
 
423
        switch (opcode & 7) {           /* inspect r/m */
 
424
        case 4:
 
425
            pc += 1;                    /* sib */
 
426
            break;
 
427
        }
 
428
        break;
 
429
    case 3:
 
430
        break;
 
431
    }
 
432
 
 
433
    /* Past mod/rm and sib. Skip any disp, and /ib for cmp{pd,ps,sd,ss}. */
 
434
    pc += nr_skip_bytes;
 
435
 
 
436
    /* The longest instruction handled above is 11 bytes. So there is
 
437
       no need to check the 15-byte instruction length limit here. */
 
438
 
 
439
    /* Done. */
 
440
    mc_pc(mc) = (long)pc;
 
441
}
 
442
#endif /* (__linux__ && (__x86_64__ || __i386__)) || (__DARWIN__ && __i386__) || (__FreeBSD__ && __x86_64__) || (__sun__ && __x86_64__) */
 
443
 
 
444
#if (defined(__linux__) && (defined(__i386__) || defined(__x86_64__) || defined(__sparc__) || defined(__powerpc__))) || (defined(__DARWIN__) && (defined(__i386__) || defined(__ppc__))) || (defined(__FreeBSD__) && defined(__x86_64__)) || (defined(__sun__) && defined(__x86_64__))
61
445
 
62
446
#if defined(__linux__) && defined(__i386__)
63
 
 
 
447
#include <asm/sigcontext.h>
 
448
#elif defined(__FreeBSD__) && defined(__x86_64__)
 
449
#include <sys/types.h>
 
450
#include <machine/fpu.h>
 
451
#endif
64
452
#include <ucontext.h>
 
453
#include <string.h>
65
454
 
66
455
static void fpe_sig_action(int sig, siginfo_t *si, void *puc)
67
456
{
68
457
    ucontext_t *uc = puc;
69
 
    mcontext_t *mc = &uc->uc_mcontext;
70
 
    fpregset_t fpstate = mc->fpregs;
71
 
    fpstate->sw &= ~0xFF;
72
 
    erl_fp_exception = 1;
 
458
#if defined(__linux__)
 
459
#if defined(__x86_64__)
 
460
    mcontext_t *mc = &uc->uc_mcontext;
 
461
    fpregset_t fpstate = mc->fpregs;
 
462
    /* A failed SSE2 instruction will restart. To avoid
 
463
       looping, we must update RIP to skip the instruction
 
464
       (leaving garbage in the destination).
 
465
       The alternative is to mask SSE2 exceptions now and
 
466
       unmask them again later in erts_check_fpe(), but that
 
467
       relies too much on other code being cooperative. */
 
468
    if (fpstate->mxcsr & 0x000D) { /* OE|ZE|IE; see unmask_sse2() */
 
469
        fpstate->mxcsr &= ~(0x003F|0x0680);
 
470
        skip_sse2_insn(mc);
 
471
    }
 
472
    fpstate->swd &= ~0xFF;
 
473
#elif defined(__i386__)
 
474
    mcontext_t *mc = &uc->uc_mcontext;
 
475
    fpregset_t fpstate = mc->fpregs;
 
476
    if ((fpstate->status >> 16) == X86_FXSR_MAGIC &&
 
477
        ((struct _fpstate*)fpstate)->mxcsr & 0x000D) {
 
478
        ((struct _fpstate*)fpstate)->mxcsr &= ~(0x003F|0x0680);
 
479
        skip_sse2_insn(mc);
 
480
    }
 
481
    fpstate->sw &= ~0xFF;
 
482
#elif defined(__sparc__)
 
483
    /* on SPARC the 3rd parameter points to a sigcontext not a ucontext */
 
484
    struct sigcontext *sc = (struct sigcontext*)puc;
 
485
    sc->si_regs.pc = sc->si_regs.npc;
 
486
    sc->si_regs.npc = (unsigned long)sc->si_regs.npc + 4;
 
487
#elif defined(__powerpc__)
 
488
#if defined(__powerpc64__)
 
489
    mcontext_t *mc = &uc->uc_mcontext;
 
490
    unsigned long *regs = &mc->gp_regs[0];
 
491
#else
 
492
    mcontext_t *mc = uc->uc_mcontext.uc_regs;
 
493
    unsigned long *regs = &mc->gregs[0];
 
494
#endif
 
495
    regs[PT_NIP] += 4;
 
496
    regs[PT_FPSCR] = 0x80|0x40|0x10;    /* VE, OE, ZE; not UE or XE */
 
497
#endif
 
498
#elif defined(__DARWIN__) && defined(__i386__)
 
499
    mcontext_t mc = uc->uc_mcontext;
 
500
    if (mc->fs.fpu_mxcsr & 0x000D) {
 
501
        mc->fs.fpu_mxcsr &= ~(0x003F|0x0680);
 
502
        skip_sse2_insn(mc);
 
503
    }
 
504
    *(unsigned short *)&mc->fs.fpu_fsw &= ~0xFF;
 
505
#elif defined(__DARWIN__) && defined(__ppc__)
 
506
    mcontext_t mc = uc->uc_mcontext;
 
507
    mc->ss.srr0 += 4;
 
508
    mc->fs.fpscr = 0x80|0x40|0x10;
 
509
#elif defined(__FreeBSD__) && defined(__x86_64__)
 
510
    mcontext_t *mc = &uc->uc_mcontext;
 
511
    struct savefpu *savefpu = (struct savefpu*)&mc->mc_fpstate;
 
512
    struct envxmm *envxmm = &savefpu->sv_env;
 
513
    if (envxmm->en_mxcsr & 0x000D) {
 
514
        envxmm->en_mxcsr &= ~(0x003F|0x0680);
 
515
        skip_sse2_insn(mc);
 
516
    }
 
517
    envxmm->en_sw &= ~0xFF;
 
518
#elif defined(__sun__) && defined(__x86_64__)
 
519
    mcontext_t *mc = &uc->uc_mcontext;
 
520
    struct fpchip_state *fpstate = &mc->fpregs.fp_reg_set.fpchip_state;
 
521
    if (fpstate->mxcsr & 0x000D) {
 
522
        fpstate->mxcsr &= ~(0x003F|0x0680);
 
523
        skip_sse2_insn(mc);
 
524
    }
 
525
    fpstate->sw &= ~0xFF;
 
526
#endif
 
527
    set_current_fp_exception();
73
528
}
74
529
 
75
 
void erts_sys_init_float(void)
 
530
static void erts_thread_catch_fp_exceptions(void)
76
531
{
77
532
    struct sigaction act;
78
533
    memset(&act, 0, sizeof act);
82
537
    unmask_fpe();
83
538
}
84
539
 
85
 
#else  /* !(__linux__ && __i386__) */
 
540
#else  /* !((__linux__ && (__i386__ || __x86_64__ || __powerpc__)) || (__DARWIN__ && (__i386__ || __ppc__))) */
86
541
 
87
542
static void fpe_sig_handler(int sig)
88
543
{
89
 
    erl_fp_exception = 1;
 
544
    set_current_fp_exception();
90
545
}
91
546
 
92
 
void
93
 
erts_sys_init_float(void)
 
547
static void erts_thread_catch_fp_exceptions(void)
94
548
{
95
549
    sys_sigset(SIGFPE, fpe_sig_handler);
96
550
    unmask_fpe();
97
551
}
98
552
 
99
 
#endif /* __linux__ && __i386__ */
 
553
#endif /* (__linux__ && (__i386__ || __x86_64__ || __powerpc__)) || (__DARWIN__ && (__i386__ || __ppc__))) */
 
554
 
 
555
/* once-only initialisation early in the main thread */
 
556
void erts_sys_init_float(void)
 
557
{
 
558
    erts_init_fp_exception();
 
559
    erts_thread_catch_fp_exceptions();
 
560
}
100
561
 
101
562
#endif /* NO_FPE_SIGNALS */
102
563
 
 
564
void erts_thread_init_float(void)
 
565
{
 
566
#ifdef ERTS_SMP
 
567
    /* This allows Erlang schedulers to leave Erlang-process context
 
568
       and still have working FP exceptions. XXX: is this needed? */
 
569
    erts_thread_init_fp_exception();
 
570
#endif
 
571
 
 
572
#if !defined(NO_FPE_SIGNALS) && (defined(__DARWIN__) || defined(__FreeBSD__))
 
573
    /* Darwin (7.9.0) does not appear to propagate FP exception settings
 
574
       to a new thread from its parent. So if we want FP exceptions, we
 
575
       must manually re-enable them in each new thread.
 
576
       FreeBSD 6.1 appears to suffer from a similar issue. */
 
577
    erts_thread_catch_fp_exceptions();
 
578
#endif
 
579
}
 
580
 
 
581
/* The following check is incorporated from the Vee machine */
 
582
    
 
583
#define ISDIGIT(d) ((d) >= '0' && (d) <= '9')
 
584
 
103
585
/* 
104
586
 ** Convert a double to ascii format 0.dddde[+|-]ddd
105
587
 ** return number of characters converted
 
588
 **
 
589
 ** These two functions should maybe use localeconv() to pick up
 
590
 ** the current radix character, but since it is uncertain how
 
591
 ** expensive such a system call is, and since no-one has heard
 
592
 ** of other radix characters than '.' and ',' an ad-hoc 
 
593
 ** low execution time solution is used instead.
106
594
 */
107
595
 
108
596
int
109
 
sys_double_to_chars(double fp, char* buf)
 
597
sys_double_to_chars(double fp, char *buf)
110
598
{
 
599
    char *s = buf;
 
600
    
111
601
    (void) sprintf(buf, "%.20e", fp);
112
 
    return strlen(buf);
 
602
    /* Search upto decimal point */
 
603
    if (*s == '+' || *s == '-') s++;
 
604
    while (ISDIGIT(*s)) s++;
 
605
    if (*s == ',') *s++ = '.'; /* Replace ',' with '.' */
 
606
    /* Scan to end of string */
 
607
    while (*s) s++;
 
608
    return s-buf; /* i.e strlen(buf) */
113
609
}
114
610
 
115
611
/* Float conversion */
117
613
int
118
614
sys_chars_to_double(char* buf, double* fp)
119
615
{
120
 
    char *s = buf;
121
 
 
122
 
    /* The following check is incorporated from the Vee machine */
123
 
    
124
 
#define ISDIGIT(d) ((d) >= '0' && (d) <= '9')
 
616
    volatile int *fpexnp = erts_get_current_fp_exception();
 
617
    char *s = buf, *t, *dp;
125
618
 
126
619
    /* Robert says that something like this is what he really wanted:
 
620
     * (The [.,] radix test is NOT what Robert wanted - it was added later)
127
621
     *
128
 
     * 7 == sscanf(Tbuf, "%[+-]%[0-9].%[0-9]%[eE]%[+-]%[0-9]%s", ....);
 
622
     * 7 == sscanf(Tbuf, "%[+-]%[0-9][.,]%[0-9]%[eE]%[+-]%[0-9]%s", ....);
129
623
     * if (*s2 == 0 || *s3 == 0 || *s4 == 0 || *s6 == 0 || *s7)
130
624
     *   break;
131
625
     */
132
626
 
133
627
    /* Scan string to check syntax. */
134
 
    if (*s == '+' || *s == '-')
135
 
      s++;
136
 
            
 
628
    if (*s == '+' || *s == '-') s++;
137
629
    if (!ISDIGIT(*s))           /* Leading digits. */
138
630
      return -1;
139
631
    while (ISDIGIT(*s)) s++;
140
 
    if (*s++ != '.')            /* Decimal part. */
 
632
    if (*s != '.' && *s != ',') /* Decimal part. */
141
633
      return -1;
 
634
    dp = s++;                   /* Remember decimal point pos just in case */
142
635
    if (!ISDIGIT(*s))
143
636
      return -1;
144
637
    while (ISDIGIT(*s)) s++;
145
638
    if (*s == 'e' || *s == 'E') {
146
639
        /* There is an exponent. */
147
640
        s++;
148
 
        if (*s == '+' || *s == '-')
149
 
          s++;
 
641
        if (*s == '+' || *s == '-') s++;
150
642
        if (!ISDIGIT(*s))
151
643
          return -1;
152
644
        while (ISDIGIT(*s)) s++;
157
649
#ifdef NO_FPE_SIGNALS
158
650
    errno = 0;
159
651
#endif
160
 
 
161
 
    ERTS_FP_CHECK_INIT();
162
 
    *fp = strtod(buf, NULL);
163
 
    ERTS_FP_ERROR(*fp, return -1);
 
652
    __ERTS_FP_CHECK_INIT(fpexnp);
 
653
    *fp = strtod(buf, &t);
 
654
    __ERTS_FP_ERROR(fpexnp, *fp, return -1);
 
655
    if (t != s) {               /* Whole string not scanned */
 
656
        /* Try again with other radix char */
 
657
        *dp = (*dp == '.') ? ',' : '.';
 
658
        errno = 0;
 
659
        __ERTS_FP_CHECK_INIT(fpexnp);
 
660
        *fp = strtod(buf, &t);
 
661
        __ERTS_FP_ERROR(fpexnp, *fp, return -1);
 
662
    }
164
663
 
165
664
#ifdef DEBUG
166
665
    if (errno == ERANGE)
184
683
int
185
684
matherr(struct exception *exc)
186
685
{
187
 
    erl_fp_exception = 1;
 
686
    set_current_fp_exception();
188
687
    return 1;
189
688
}