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

« back to all changes in this revision

Viewing changes to erts/lib_src/win/ethread.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 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
 * Description: Windows native threads implementation of the ethread library
 
22
 * Author: Rickard Green
 
23
 */
 
24
 
 
25
#ifdef HAVE_CONFIG_H
 
26
#include "config.h"
 
27
#endif
 
28
 
 
29
#define ETHR_CHILD_WAIT_SPIN_COUNT 4000
 
30
 
 
31
#undef WIN32_LEAN_AND_MEAN
 
32
#define WIN32_LEAN_AND_MEAN
 
33
#include <windows.h>
 
34
#include <process.h>
 
35
#include <winerror.h>
 
36
#include <stdio.h>
 
37
#include <limits.h>
 
38
 
 
39
#define ETHR_INLINE_FUNC_NAME_(X) X ## __
 
40
#define ETHREAD_IMPL__
 
41
 
 
42
#include "ethread.h"
 
43
#include "ethr_internal.h"
 
44
 
 
45
#ifndef ETHR_HAVE_ETHREAD_DEFINES
 
46
#error Missing configure defines
 
47
#endif
 
48
 
 
49
/* Argument passed to thr_wrapper() */
 
50
typedef struct {
 
51
    ethr_tid *tid;
 
52
    ethr_atomic32_t result;
 
53
    ethr_ts_event *tse;
 
54
    void *(*thr_func)(void *);
 
55
    void *arg;
 
56
    void *prep_func_res;
 
57
} ethr_thr_wrap_data__;
 
58
 
 
59
#define ETHR_INVALID_TID_ID -1
 
60
 
 
61
struct ethr_join_data_ {
 
62
    HANDLE handle;
 
63
    void *res;
 
64
};
 
65
 
 
66
static ethr_atomic_t thread_id_counter;
 
67
static DWORD own_tid_key;
 
68
static ethr_tid main_thr_tid;
 
69
static int child_wait_spin_count;
 
70
 
 
71
DWORD ethr_ts_event_key__;
 
72
 
 
73
#define ETHR_GET_OWN_TID__      ((ethr_tid *) TlsGetValue(own_tid_key))
 
74
 
 
75
/*
 
76
 * --------------------------------------------------------------------------
 
77
 * Static functions
 
78
 * --------------------------------------------------------------------------
 
79
 */
 
80
 
 
81
static void thr_exit_cleanup(ethr_tid *tid, void *res)
 
82
{
 
83
 
 
84
    ETHR_ASSERT(tid == ETHR_GET_OWN_TID__);
 
85
 
 
86
    if (tid->jdata)
 
87
        tid->jdata->res = res;
 
88
 
 
89
    ethr_run_exit_handlers__();
 
90
    ethr_ts_event_destructor__((void *) ethr_get_tse__());
 
91
}
 
92
 
 
93
static unsigned __stdcall thr_wrapper(LPVOID vtwd)
 
94
{
 
95
    ethr_tid my_tid;
 
96
    ethr_sint32_t result;
 
97
    void *res;
 
98
    ethr_thr_wrap_data__ *twd = (ethr_thr_wrap_data__ *) vtwd;
 
99
    void *(*thr_func)(void *) = twd->thr_func;
 
100
    void *arg = twd->arg;
 
101
    ethr_ts_event *tsep = NULL;
 
102
 
 
103
    result = (ethr_sint32_t) ethr_make_ts_event__(&tsep);
 
104
 
 
105
    if (result == 0) {
 
106
        tsep->iflgs |= ETHR_TS_EV_ETHREAD;
 
107
        my_tid = *twd->tid;
 
108
        if (!TlsSetValue(own_tid_key, (LPVOID) &my_tid)) {
 
109
            result = (ethr_sint32_t) ethr_win_get_errno__();
 
110
            ethr_free_ts_event__(tsep);
 
111
        }
 
112
        else {
 
113
            if (ethr_thr_child_func__)
 
114
                ethr_thr_child_func__(twd->prep_func_res);
 
115
        }
 
116
    }
 
117
 
 
118
    tsep = twd->tse; /* We aren't allowed to follow twd after
 
119
                        result has been set! */
 
120
 
 
121
    ethr_atomic32_set(&twd->result, result);
 
122
 
 
123
    ethr_event_set(&tsep->event);
 
124
 
 
125
    res = result == 0 ? (*thr_func)(arg) : NULL;
 
126
 
 
127
    thr_exit_cleanup(&my_tid, res);
 
128
    return 0;
 
129
}
 
130
 
 
131
/* internal exports */
 
132
 
 
133
int
 
134
ethr_win_get_errno__(void)
 
135
{
 
136
    return erts_get_last_win_errno();
 
137
}
 
138
 
 
139
int ethr_set_tse__(ethr_ts_event *tsep)
 
140
{
 
141
    return (TlsSetValue(ethr_ts_event_key__, (LPVOID) tsep)
 
142
            ? 0
 
143
            : ethr_win_get_errno__());
 
144
}
 
145
 
 
146
ethr_ts_event *ethr_get_tse__(void)
 
147
{
 
148
    return (ethr_ts_event *) TlsGetValue(ethr_ts_event_key__);
 
149
}
 
150
 
 
151
ETHR_IMPL_NORETURN__
 
152
ethr_abort__(void)
 
153
{
 
154
#if 1
 
155
    DebugBreak();
 
156
#else
 
157
    abort();
 
158
#endif
 
159
}
 
160
 
 
161
/*
 
162
 * ----------------------------------------------------------------------------
 
163
 * Exported functions
 
164
 * ----------------------------------------------------------------------------
 
165
 */
 
166
 
 
167
int
 
168
ethr_init(ethr_init_data *id)
 
169
{
 
170
#ifdef _WIN32_WINNT
 
171
    DWORD major = (_WIN32_WINNT >> 8) & 0xff;
 
172
    DWORD minor = _WIN32_WINNT & 0xff;
 
173
    OSVERSIONINFO os_version;
 
174
#endif
 
175
    int err = 0;
 
176
    unsigned long i;
 
177
 
 
178
    if (!ethr_not_inited__)
 
179
        return EINVAL;
 
180
 
 
181
#ifdef _WIN32_WINNT
 
182
    os_version.dwOSVersionInfoSize = sizeof(OSVERSIONINFO);
 
183
    GetVersionEx(&os_version);
 
184
    if (os_version.dwPlatformId != VER_PLATFORM_WIN32_NT
 
185
        || os_version.dwMajorVersion < major
 
186
        || (os_version.dwMajorVersion == major
 
187
            && os_version.dwMinorVersion < minor))
 
188
        return ENOTSUP;
 
189
#endif
 
190
    err = ethr_init_common__(id);
 
191
    if (err)
 
192
        goto error;
 
193
 
 
194
    own_tid_key = TlsAlloc();
 
195
    if (own_tid_key == TLS_OUT_OF_INDEXES)
 
196
        goto error;
 
197
 
 
198
    ethr_atomic_init(&thread_id_counter, 0);
 
199
 
 
200
    main_thr_tid.id = 0;
 
201
    main_thr_tid.jdata = NULL;
 
202
 
 
203
    if (!TlsSetValue(own_tid_key, (LPVOID) &main_thr_tid))
 
204
        goto error;
 
205
 
 
206
    ETHR_ASSERT(&main_thr_tid == ETHR_GET_OWN_TID__);
 
207
 
 
208
    ethr_ts_event_key__ = TlsAlloc();
 
209
    if (ethr_ts_event_key__ == TLS_OUT_OF_INDEXES)
 
210
        goto error;
 
211
 
 
212
    child_wait_spin_count = ETHR_CHILD_WAIT_SPIN_COUNT;
 
213
    if (erts_get_cpu_configured(ethr_cpu_info__) == 1)
 
214
        child_wait_spin_count = 0;
 
215
 
 
216
    ethr_not_inited__ = 0;
 
217
 
 
218
    return 0;
 
219
 
 
220
 error:
 
221
    ethr_not_inited__ = 1;
 
222
    if (err == 0)
 
223
        err = ethr_win_get_errno__();
 
224
    ETHR_ASSERT(err != 0);
 
225
    return err;
 
226
}
 
227
 
 
228
int
 
229
ethr_late_init(ethr_late_init_data *id)
 
230
{
 
231
    int res = ethr_late_init_common__(id);
 
232
    if (res != 0)
 
233
        return res;
 
234
    ethr_not_completely_inited__ = 0;
 
235
    return res;
 
236
}
 
237
 
 
238
 
 
239
/*
 
240
 * Thread functions.
 
241
 */
 
242
 
 
243
int
 
244
ethr_thr_create(ethr_tid *tid, void * (*func)(void *), void *arg,
 
245
                ethr_thr_opts *opts)
 
246
{
 
247
    HANDLE handle = INVALID_HANDLE_VALUE;
 
248
    int err = 0;
 
249
    ethr_thr_wrap_data__ twd;
 
250
    DWORD code;
 
251
    unsigned ID;
 
252
    unsigned stack_size = 0; /* 0 = system default */
 
253
    int use_stack_size = (opts && opts->suggested_stack_size >= 0
 
254
                          ? opts->suggested_stack_size
 
255
                          : -1 /* Use system default */);
 
256
 
 
257
#ifdef ETHR_MODIFIED_DEFAULT_STACK_SIZE
 
258
    if (use_stack_size < 0)
 
259
        use_stack_size = ETHR_MODIFIED_DEFAULT_STACK_SIZE;
 
260
#endif
 
261
 
 
262
#if ETHR_XCHK
 
263
    if (ethr_not_completely_inited__) {
 
264
        ETHR_ASSERT(0);
 
265
        return EACCES;
 
266
    }
 
267
    if (!tid || !func) {
 
268
        ETHR_ASSERT(0);
 
269
        return EINVAL;
 
270
    }
 
271
#endif
 
272
 
 
273
    do {
 
274
        tid->id = ethr_atomic_inc_read(&thread_id_counter);
 
275
    } while (tid->id == ETHR_INVALID_TID_ID);
 
276
 
 
277
    if (opts && opts->detached)
 
278
        tid->jdata = NULL;
 
279
    else {
 
280
        tid->jdata = ethr_mem__.std.alloc(sizeof(struct ethr_join_data_));
 
281
        if (!tid->jdata)
 
282
            return ENOMEM;
 
283
        tid->jdata->handle = INVALID_HANDLE_VALUE;
 
284
        tid->jdata->res = NULL;
 
285
    }
 
286
 
 
287
    if (use_stack_size >= 0) {
 
288
        size_t suggested_stack_size = (size_t) use_stack_size;
 
289
#ifdef ETHR_DEBUG
 
290
        suggested_stack_size /= 2; /* Make sure we got margin */
 
291
#endif
 
292
        if (suggested_stack_size < ethr_min_stack_size__)
 
293
            stack_size = (unsigned) ETHR_KW2B(ethr_min_stack_size__);
 
294
        else if (suggested_stack_size > ethr_max_stack_size__)
 
295
            stack_size = (unsigned) ETHR_KW2B(ethr_max_stack_size__);
 
296
        else
 
297
            stack_size = (unsigned)
 
298
              ETHR_PAGE_ALIGN(ETHR_KW2B(suggested_stack_size));
 
299
    }
 
300
 
 
301
    ethr_atomic32_init(&twd.result, -1);
 
302
 
 
303
    twd.tid = tid;
 
304
    twd.thr_func = func;
 
305
    twd.arg = arg;
 
306
    twd.tse = ethr_get_ts_event();
 
307
 
 
308
    /* Call prepare func if it exist */
 
309
    if (ethr_thr_prepare_func__)
 
310
        twd.prep_func_res = ethr_thr_prepare_func__();
 
311
    else
 
312
        twd.prep_func_res = NULL;
 
313
 
 
314
    /* spawn the thr_wrapper function */
 
315
    handle = (HANDLE) _beginthreadex(NULL, stack_size, thr_wrapper,
 
316
                                     (LPVOID) &twd, 0, &ID);
 
317
    if (handle == (HANDLE) 0) {
 
318
        handle = INVALID_HANDLE_VALUE;
 
319
        goto error;
 
320
    }
 
321
    else {
 
322
        int spin_count = child_wait_spin_count;
 
323
 
 
324
        ETHR_ASSERT(handle != INVALID_HANDLE_VALUE);
 
325
 
 
326
        if (!tid->jdata)
 
327
            CloseHandle(handle);
 
328
        else
 
329
            tid->jdata->handle = handle;
 
330
 
 
331
        /* Wait for child to initialize... */
 
332
        while (1) {
 
333
            ethr_sint32_t result;
 
334
            int err;
 
335
            ethr_event_reset(&twd.tse->event);
 
336
 
 
337
            result = ethr_atomic32_read(&twd.result);
 
338
            if (result == 0)
 
339
                break;
 
340
 
 
341
            if (result > 0) {
 
342
                err = (int) result;
 
343
                goto error;
 
344
            }
 
345
 
 
346
            err = ethr_event_swait(&twd.tse->event, spin_count);
 
347
            if (err && err != EINTR)
 
348
                goto error;
 
349
            spin_count = 0;
 
350
        }
 
351
    }
 
352
 
 
353
    if (ethr_thr_parent_func__)
 
354
        ethr_thr_parent_func__(twd.prep_func_res);
 
355
 
 
356
    if (twd.tse)
 
357
        ethr_leave_ts_event(twd.tse);
 
358
 
 
359
    return 0;
 
360
 
 
361
 error:
 
362
 
 
363
    if (err == 0)
 
364
        err = ethr_win_get_errno__();
 
365
    ETHR_ASSERT(err != 0);
 
366
 
 
367
    if (ethr_thr_parent_func__)
 
368
        ethr_thr_parent_func__(twd.prep_func_res);
 
369
 
 
370
    if (handle != INVALID_HANDLE_VALUE) {
 
371
        WaitForSingleObject(handle, INFINITE);
 
372
        CloseHandle(handle);
 
373
    }
 
374
 
 
375
    if (tid->jdata) {
 
376
        ethr_mem__.std.free(tid->jdata);
 
377
        tid->jdata = NULL;
 
378
    }
 
379
 
 
380
    tid->id = ETHR_INVALID_TID_ID;
 
381
 
 
382
    if (twd.tse)
 
383
        ethr_leave_ts_event(twd.tse);
 
384
 
 
385
    return err;
 
386
}
 
387
 
 
388
int ethr_thr_join(ethr_tid tid, void **res)
 
389
{
 
390
    DWORD code;
 
391
 
 
392
#if ETHR_XCHK 
 
393
    if (ethr_not_inited__) {
 
394
        ETHR_ASSERT(0);
 
395
        return EACCES;
 
396
    }
 
397
#endif
 
398
 
 
399
    if (tid.id == ETHR_INVALID_TID_ID || !tid.jdata)
 
400
        return EINVAL;
 
401
 
 
402
    /* Wait for thread to terminate */
 
403
    code = WaitForSingleObject(tid.jdata->handle, INFINITE);
 
404
    if (code != WAIT_OBJECT_0)
 
405
        return ethr_win_get_errno__();
 
406
 
 
407
    CloseHandle(tid.jdata->handle);
 
408
    tid.jdata->handle = INVALID_HANDLE_VALUE;
 
409
 
 
410
    if (res)
 
411
        *res = tid.jdata->res;
 
412
 
 
413
    /*
 
414
     * User better not try to join or detach again; or
 
415
     * bad things will happen... (users responsibility)
 
416
     */
 
417
 
 
418
    ethr_mem__.std.free(tid.jdata);
 
419
 
 
420
    return 0;
 
421
}
 
422
 
 
423
 
 
424
int
 
425
ethr_thr_detach(ethr_tid tid)
 
426
{
 
427
#if ETHR_XCHK 
 
428
    if (ethr_not_inited__) {
 
429
        ETHR_ASSERT(0);
 
430
        return EACCES;
 
431
    }
 
432
#endif
 
433
 
 
434
    if (tid.id == ETHR_INVALID_TID_ID || !tid.jdata)
 
435
        return EINVAL;
 
436
 
 
437
    CloseHandle(tid.jdata->handle);
 
438
    tid.jdata->handle = INVALID_HANDLE_VALUE;
 
439
 
 
440
    /*
 
441
     * User better not try to join or detach again; or
 
442
     * bad things will happen... (users responsibility)
 
443
     */
 
444
 
 
445
    ethr_mem__.std.free(tid.jdata);
 
446
 
 
447
    return 0;
 
448
}
 
449
 
 
450
 
 
451
void
 
452
ethr_thr_exit(void *res)
 
453
{
 
454
    ethr_tid *tid;
 
455
#if ETHR_XCHK
 
456
    if (ethr_not_inited__) {
 
457
        ETHR_ASSERT(0);
 
458
        return;
 
459
    }
 
460
#endif
 
461
    tid = ETHR_GET_OWN_TID__;
 
462
    if (!tid) {
 
463
        ETHR_ASSERT(0);
 
464
        _endthreadex((unsigned) 0);
 
465
    }
 
466
    thr_exit_cleanup(tid, res);
 
467
    _endthreadex((unsigned) 0);
 
468
}
 
469
 
 
470
ethr_tid
 
471
ethr_self(void)
 
472
{
 
473
    ethr_tid *tid;
 
474
#if ETHR_XCHK
 
475
    if (ethr_not_inited__) {
 
476
        ethr_tid dummy_tid = {ETHR_INVALID_TID_ID, NULL};
 
477
        ETHR_ASSERT(0);
 
478
        return dummy_tid;
 
479
    }
 
480
#endif
 
481
    /* It is okay for non-ethreads (i.e. native win32 threads) to call
 
482
       ethr_self(). They will however be returned an invalid tid. */
 
483
    tid = ETHR_GET_OWN_TID__;
 
484
    if (!tid) {
 
485
        ethr_tid dummy_tid = {ETHR_INVALID_TID_ID, NULL};
 
486
        return dummy_tid;
 
487
    }
 
488
    return *tid;
 
489
}
 
490
 
 
491
int
 
492
ethr_equal_tids(ethr_tid tid1, ethr_tid tid2)
 
493
{
 
494
    /* An invalid tid does not equal any tid, not even an invalid tid */
 
495
    return tid1.id == tid2.id && tid1.id != ETHR_INVALID_TID_ID;
 
496
}
 
497
 
 
498
/*
 
499
 * Thread specific data
 
500
 */
 
501
 
 
502
int
 
503
ethr_tsd_key_create(ethr_tsd_key *keyp)
 
504
{
 
505
    DWORD key;
 
506
#if ETHR_XCHK
 
507
    if (ethr_not_inited__) {
 
508
        ETHR_ASSERT(0);
 
509
        return EACCES;
 
510
    }
 
511
    if (!keyp) {
 
512
        ETHR_ASSERT(0);
 
513
        return EINVAL;
 
514
    }
 
515
#endif
 
516
    key = TlsAlloc();
 
517
    if (key == TLS_OUT_OF_INDEXES)
 
518
        return ethr_win_get_errno__();
 
519
    *keyp = (ethr_tsd_key) key;
 
520
    return 0;
 
521
}
 
522
 
 
523
int
 
524
ethr_tsd_key_delete(ethr_tsd_key key)
 
525
{
 
526
#if ETHR_XCHK
 
527
    if (ethr_not_inited__) {
 
528
        ETHR_ASSERT(0);
 
529
        return EACCES;
 
530
    }
 
531
#endif
 
532
    if (!TlsFree((DWORD) key))
 
533
        return ethr_win_get_errno__();
 
534
    return 0;
 
535
}
 
536
 
 
537
int
 
538
ethr_tsd_set(ethr_tsd_key key, void *value)
 
539
{
 
540
#if ETHR_XCHK
 
541
    if (ethr_not_inited__) {
 
542
        ETHR_ASSERT(0);
 
543
        return EACCES;
 
544
    }
 
545
#endif
 
546
    if (!TlsSetValue((DWORD) key, (LPVOID) value))
 
547
        return ethr_win_get_errno__();
 
548
    return 0;
 
549
}
 
550
 
 
551
void *
 
552
ethr_tsd_get(ethr_tsd_key key)
 
553
{
 
554
#if ETHR_XCHK
 
555
    if (ethr_not_inited__) {
 
556
        ETHR_ASSERT(0);
 
557
        return NULL;
 
558
    }
 
559
#endif
 
560
    return (void *) TlsGetValue((DWORD) key);
 
561
}
 
562
 
 
563
 
 
564
/*
 
565
 * Thread specific events
 
566
 */
 
567
 
 
568
ethr_ts_event *
 
569
ethr_get_ts_event(void)
 
570
{
 
571
    return ethr_get_ts_event__();
 
572
}
 
573
 
 
574
void
 
575
ethr_leave_ts_event(ethr_ts_event *tsep)
 
576
{
 
577
    ethr_leave_ts_event__(tsep);
 
578
}
 
579
 
 
580
ethr_ts_event *
 
581
ethr_create_ts_event__(void)
 
582
{
 
583
    ethr_ts_event *tsep;
 
584
    ethr_make_ts_event__(&tsep);
 
585
    return tsep;
 
586
}