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

« back to all changes in this revision

Viewing changes to erts/lib_src/common/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 2004-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
 
/*
21
 
 * Description: A Thread library for use in the ERTS and other OTP
22
 
 *              applications.
23
 
 * Author: Rickard Green
24
 
 */
25
 
 
26
 
#ifdef HAVE_CONFIG_H
27
 
#include "config.h"
28
 
#endif
29
 
 
30
 
#undef ETHR_STACK_GUARD_SIZE 
31
 
 
32
 
#if defined(ETHR_PTHREADS)
33
 
 
34
 
#ifdef ETHR_TIME_WITH_SYS_TIME
35
 
#  include <time.h>
36
 
#  include <sys/time.h>
37
 
#else
38
 
#  ifdef ETHR_HAVE_SYS_TIME_H
39
 
#    include <sys/time.h>
40
 
#  else
41
 
#    include <time.h>
42
 
#  endif
43
 
#endif
44
 
#include <sys/types.h>
45
 
#include <unistd.h>
46
 
#include <signal.h>
47
 
 
48
 
#ifdef ETHR_HAVE_PTHREAD_ATTR_SETGUARDSIZE
49
 
#  define ETHR_STACK_GUARD_SIZE (pagesize)
50
 
#endif
51
 
 
52
 
#elif defined(ETHR_WIN32_THREADS)
53
 
 
54
 
#undef WIN32_LEAN_AND_MEAN
55
 
#define WIN32_LEAN_AND_MEAN
56
 
#include <windows.h>
57
 
#include <process.h>
58
 
#include <winerror.h>
59
 
 
60
 
#else
61
 
#error "Missing thread implementation"
62
 
#endif
63
 
 
64
 
#include <limits.h>
65
 
 
66
 
#define ETHR_FORCE_INLINE_FUNCS
67
 
#define ETHR_INLINE_FUNC_NAME_(X) X ## __
68
 
#include "ethread.h"
69
 
 
70
 
#ifndef ETHR_HAVE_ETHREAD_DEFINES
71
 
#error Missing configure defines
72
 
#endif
73
 
 
74
 
/*
75
 
 * ----------------------------------------------------------------------------
76
 
 * Common stuff
77
 
 * ----------------------------------------------------------------------------
78
 
 */
79
 
 
80
 
#define ETHR_MAX_THREADS 2048 /* Has to be an even power of 2 */
81
 
 
82
 
static int ethr_not_inited = 1;
83
 
 
84
 
#define ASSERT(A) ETHR_ASSERT((A))
85
 
 
86
 
static void *(*allocp)(size_t) = malloc;
87
 
static void *(*reallocp)(void *, size_t) = realloc;
88
 
static void (*freep)(void *) = free;
89
 
 
90
 
#ifndef ETHR_HAVE_OPTIMIZED_ATOMIC_OPS
91
 
ethr_atomic_protection_t ethr_atomic_protection__[1 << ETHR_ATOMIC_ADDR_BITS];
92
 
#endif
93
 
 
94
 
void *(*thread_create_prepare_func)(void) = NULL;
95
 
void (*thread_create_parent_func)(void *) = NULL;
96
 
void (*thread_create_child_func)(void *) = NULL;
97
 
 
98
 
typedef struct ethr_xhndl_list_ ethr_xhndl_list;
99
 
struct ethr_xhndl_list_ {
100
 
    ethr_xhndl_list *next;
101
 
    void (*funcp)(void);
102
 
};
103
 
 
104
 
static size_t pagesize;
105
 
#define ETHR_PAGE_ALIGN(SZ) (((((size_t) (SZ)) - 1)/pagesize + 1)*pagesize)
106
 
static size_t min_stack_size; /* kilo words */
107
 
static size_t max_stack_size; /* kilo words */
108
 
#define ETHR_B2KW(B) ((((size_t) (B)) - 1)/(sizeof(void *)*1024) + 1)
109
 
#define ETHR_KW2B(KW) (((size_t) (KW))*sizeof(void *)*1024)
110
 
 
111
 
ethr_mutex xhndl_mtx;
112
 
ethr_xhndl_list *xhndl_list;
113
 
 
114
 
static int
115
 
init_common(ethr_init_data *id)
116
 
{
117
 
    int res;
118
 
    if (id) {
119
 
        allocp                          = id->alloc;
120
 
        reallocp                        = id->realloc;
121
 
        freep                           = id->free;
122
 
        thread_create_prepare_func      = id->thread_create_prepare_func;
123
 
        thread_create_parent_func       = id->thread_create_parent_func;
124
 
        thread_create_child_func        = id->thread_create_child_func;
125
 
    }
126
 
    if (!allocp || !reallocp || !freep)
127
 
        return EINVAL;
128
 
 
129
 
#ifdef _SC_PAGESIZE
130
 
    pagesize = (size_t) sysconf(_SC_PAGESIZE);
131
 
#elif defined(HAVE_GETPAGESIZE)
132
 
    pagesize = (size_t) getpagesize();
133
 
#else
134
 
    pagesize = (size_t) 4*1024; /* Guess 4 KB */
135
 
#endif
136
 
 
137
 
    /* User needs at least 4 KB */
138
 
    min_stack_size = 4*1024;
139
 
#if SIZEOF_VOID_P == 8
140
 
    /* Double that on 64-bit archs */
141
 
    min_stack_size *= 2;
142
 
#endif
143
 
    /* On some systems as much as about 4 KB is used by the system */
144
 
    min_stack_size += 4*1024;
145
 
    /* There should be room for signal handlers */
146
 
#ifdef SIGSTKSZ
147
 
    min_stack_size += SIGSTKSZ;
148
 
#else
149
 
    min_stack_size += pagesize;
150
 
#endif
151
 
    /* The system may think that we need more stack */
152
 
#if defined(PTHREAD_STACK_MIN)
153
 
    if (min_stack_size < PTHREAD_STACK_MIN)
154
 
        min_stack_size = PTHREAD_STACK_MIN;
155
 
#elif defined(_SC_THREAD_STACK_MIN)
156
 
    {
157
 
        size_t thr_min_stk_sz = (size_t) sysconf(_SC_THREAD_STACK_MIN);
158
 
        if (min_stack_size < thr_min_stk_sz)
159
 
            min_stack_size = thr_min_stk_sz;
160
 
    }
161
 
#endif
162
 
    /* The guard is at least on some platforms included in the stack size
163
 
       passed when creating threads */
164
 
#ifdef ETHR_STACK_GUARD_SIZE
165
 
    min_stack_size += ETHR_STACK_GUARD_SIZE;
166
 
#endif
167
 
    min_stack_size = ETHR_PAGE_ALIGN(min_stack_size);
168
 
 
169
 
    min_stack_size = ETHR_B2KW(min_stack_size);
170
 
 
171
 
    max_stack_size = 32*1024*1024;
172
 
#if SIZEOF_VOID_P == 8
173
 
    max_stack_size *= 2;
174
 
#endif
175
 
    max_stack_size = ETHR_B2KW(max_stack_size);
176
 
 
177
 
    xhndl_list = NULL;
178
 
 
179
 
    res = ethr_mutex_init(&xhndl_mtx);
180
 
    if (res != 0)
181
 
        return res;
182
 
 
183
 
    res = ethr_mutex_set_forksafe(&xhndl_mtx);
184
 
    if (res != 0 && res != ENOTSUP)
185
 
        return res;
186
 
 
187
 
    return 0;
188
 
}
189
 
 
190
 
int
191
 
ethr_install_exit_handler(void (*funcp)(void))
192
 
{
193
 
    ethr_xhndl_list *xhp;
194
 
    int res;
195
 
 
196
 
#if ETHR_XCHK
197
 
    if (ethr_not_inited) {
198
 
        ASSERT(0);
199
 
        return EACCES;
200
 
    }
201
 
#endif
202
 
 
203
 
    if (!funcp)
204
 
        return EINVAL;
205
 
 
206
 
    xhp = (ethr_xhndl_list *) (*allocp)(sizeof(ethr_xhndl_list));
207
 
    if (!xhp)
208
 
        return ENOMEM;
209
 
 
210
 
    res = ethr_mutex_lock__(&xhndl_mtx);
211
 
    if (res != 0) {
212
 
        (*freep)((void *) xhp);
213
 
        return res;
214
 
    }
215
 
 
216
 
    xhp->funcp = funcp;
217
 
    xhp->next = xhndl_list;
218
 
    xhndl_list = xhp;
219
 
 
220
 
    res = ethr_mutex_unlock__(&xhndl_mtx);
221
 
    if (res != 0)
222
 
        abort();
223
 
 
224
 
    return res;
225
 
}
226
 
 
227
 
static void
228
 
run_exit_handlers(void)
229
 
{
230
 
    int res;
231
 
    ethr_xhndl_list *xhp;
232
 
 
233
 
    res = ethr_mutex_lock__(&xhndl_mtx);
234
 
    if (res != 0)
235
 
        abort();
236
 
 
237
 
    xhp = xhndl_list;
238
 
 
239
 
    res = ethr_mutex_unlock__(&xhndl_mtx);
240
 
    if (res != 0)
241
 
        abort();
242
 
 
243
 
    for (; xhp; xhp = xhp->next)
244
 
        (*xhp->funcp)();
245
 
}
246
 
 
247
 
#if defined(ETHR_PTHREADS)
248
 
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
249
 
 * pthread implementation                                                    *
250
 
\*                                                                           */
251
 
 
252
 
typedef struct {
253
 
    pthread_mutex_t mtx;
254
 
    pthread_cond_t cnd;
255
 
    int initialized;
256
 
    void *(*thr_func)(void *);
257
 
    void *arg;
258
 
    void *prep_func_res;
259
 
} thr_wrap_data_;
260
 
 
261
 
static int no_ethreads;
262
 
static ethr_mutex no_ethrs_mtx;
263
 
 
264
 
#ifndef ETHR_HAVE_PTHREAD_ATFORK
265
 
#define ETHR_HAVE_PTHREAD_ATFORK 0
266
 
#endif
267
 
 
268
 
#if !ETHR_HAVE_PTHREAD_ATFORK
269
 
#warning "Cannot enforce fork-safety"
270
 
#endif
271
 
 
272
 
/*
273
 
 * ----------------------------------------------------------------------------
274
 
 * Static functions
275
 
 * ----------------------------------------------------------------------------
276
 
 */
277
 
 
278
 
/*
279
 
 * Functions with safe_ prefix aborts on failure. To be used when
280
 
 * we cannot recover after failure.
281
 
 */
282
 
 
283
 
static ETHR_INLINE void
284
 
safe_mutex_lock(pthread_mutex_t *mtxp)
285
 
{
286
 
    int res = pthread_mutex_lock(mtxp);
287
 
    if (res != 0)
288
 
        abort();
289
 
}
290
 
 
291
 
static ETHR_INLINE void
292
 
safe_mutex_unlock(pthread_mutex_t *mtxp)
293
 
{
294
 
    int res = pthread_mutex_unlock(mtxp);
295
 
    if (res != 0)
296
 
        abort();
297
 
}
298
 
 
299
 
static ETHR_INLINE void
300
 
safe_cond_signal(pthread_cond_t *cndp)
301
 
{
302
 
    int res = pthread_cond_signal(cndp);
303
 
    if (res != 0)
304
 
        abort();
305
 
}
306
 
 
307
 
#ifdef ETHR_HAVE_ETHR_REC_MUTEX_INIT
308
 
 
309
 
static volatile int rec_mtx_attr_need_init = 1;
310
 
static pthread_mutexattr_t rec_mtx_attr;
311
 
 
312
 
static int init_rec_mtx_attr(void);
313
 
 
314
 
#endif
315
 
 
316
 
#if ETHR_HAVE_PTHREAD_ATFORK
317
 
 
318
 
static ethr_mutex forksafe_mtx = ETHR_MUTEX_INITER;
319
 
 
320
 
static void lock_mutexes(void)
321
 
{
322
 
    ethr_mutex *m = &forksafe_mtx;
323
 
    do {
324
 
 
325
 
        safe_mutex_lock(&m->pt_mtx);
326
 
 
327
 
        m = m->next;
328
 
 
329
 
    } while (m != &forksafe_mtx);
330
 
}
331
 
 
332
 
static void unlock_mutexes(void)
333
 
{
334
 
    ethr_mutex *m = forksafe_mtx.prev;
335
 
    do {
336
 
 
337
 
        safe_mutex_unlock(&m->pt_mtx);
338
 
 
339
 
        m = m->prev;
340
 
 
341
 
    } while (m->next != &forksafe_mtx);
342
 
}
343
 
 
344
 
#if ETHR_INIT_MUTEX_IN_CHILD_AT_FORK
345
 
 
346
 
static void reinit_mutexes(void)
347
 
{
348
 
    ethr_mutex *m = forksafe_mtx.prev;
349
 
    do {
350
 
        pthread_mutexattr_t *attrp = NULL;
351
 
 
352
 
#ifdef ETHR_HAVE_ETHR_REC_MUTEX_INIT
353
 
        if (m->is_rec_mtx) {
354
 
            if (rec_mtx_attr_need_init) {
355
 
                int res = init_rec_mtx_attr();
356
 
                if (res != 0)
357
 
                    abort();
358
 
            }
359
 
            attrp = &rec_mtx_attr;
360
 
        }
361
 
#endif
362
 
        if (pthread_mutex_init(&m->pt_mtx, attrp) != 0)
363
 
            abort();
364
 
 
365
 
        m = m->prev;
366
 
 
367
 
    } while (m->next != &forksafe_mtx);
368
 
}
369
 
 
370
 
#endif
371
 
 
372
 
static int
373
 
init_forksafe(void)
374
 
{
375
 
    static int init_done = 0;
376
 
    int res = 0;
377
 
 
378
 
    if (init_done)
379
 
        return res;
380
 
 
381
 
    forksafe_mtx.prev = &forksafe_mtx;
382
 
    forksafe_mtx.next = &forksafe_mtx;
383
 
 
384
 
    res = pthread_atfork(lock_mutexes,
385
 
                         unlock_mutexes,
386
 
#if ETHR_INIT_MUTEX_IN_CHILD_AT_FORK
387
 
                         reinit_mutexes
388
 
#else
389
 
                         unlock_mutexes
390
 
#endif
391
 
        );
392
 
 
393
 
    init_done = 1;
394
 
    return res;
395
 
}
396
 
 
397
 
#endif
398
 
 
399
 
 
400
 
#ifdef ETHR_HAVE_ETHR_REC_MUTEX_INIT
401
 
 
402
 
#if defined(ETHR_HAVE_PTHREAD_MUTEXATTR_SETTYPE)
403
 
 
404
 
#define SET_REC_MUTEX_ATTR(AP) \
405
 
  pthread_mutexattr_settype((AP), PTHREAD_MUTEX_RECURSIVE);
406
 
 
407
 
#elif defined(ETHR_HAVE_PTHREAD_MUTEXATTR_SETKIND_NP)
408
 
 
409
 
#define SET_REC_MUTEX_ATTR(AP) \
410
 
  pthread_mutexattr_setkind_np((AP), PTHREAD_MUTEX_RECURSIVE_NP);
411
 
 
412
 
#else
413
 
 
414
 
#error "Don't know how to set recursive mutex attributes"
415
 
 
416
 
#endif
417
 
 
418
 
static int
419
 
init_rec_mtx_attr(void)
420
 
{
421
 
    int res, mres;
422
 
    static pthread_mutex_t attrinit_mtx = PTHREAD_MUTEX_INITIALIZER;
423
 
 
424
 
    mres = pthread_mutex_lock(&attrinit_mtx);
425
 
    if (mres != 0)
426
 
        return mres;
427
 
    /* Got here under race conditions; check again ... */
428
 
    if (!rec_mtx_attr_need_init)
429
 
        res = 0;
430
 
    else {
431
 
        res = pthread_mutexattr_init(&rec_mtx_attr);
432
 
        if (res == 0) {
433
 
            res = SET_REC_MUTEX_ATTR(&rec_mtx_attr);
434
 
            if (res == 0)
435
 
                rec_mtx_attr_need_init = 0;
436
 
            else
437
 
                (void) pthread_mutexattr_destroy(&rec_mtx_attr);
438
 
        }
439
 
    }
440
 
 
441
 
    mres = pthread_mutex_unlock(&attrinit_mtx);
442
 
    if (mres != 0)
443
 
        return mres;
444
 
    return res;
445
 
}
446
 
 
447
 
#endif /* #if ETHR_HAVE_ETHR_REC_MUTEX_INIT */
448
 
 
449
 
static ETHR_INLINE void thr_exit_cleanup(void)
450
 
{
451
 
    run_exit_handlers();
452
 
    safe_mutex_lock(&no_ethrs_mtx.pt_mtx);
453
 
    ASSERT(no_ethreads > 0);
454
 
    no_ethreads--;
455
 
    safe_mutex_unlock(&no_ethrs_mtx.pt_mtx);
456
 
}
457
 
 
458
 
static void *thr_wrapper(void *vtwd)
459
 
{
460
 
    void *res;
461
 
    thr_wrap_data_ *twd = (thr_wrap_data_ *) vtwd;
462
 
    void *(*thr_func)(void *) = twd->thr_func;
463
 
    void *arg = twd->arg;
464
 
 
465
 
    safe_mutex_lock(&twd->mtx);
466
 
 
467
 
    if (thread_create_child_func)
468
 
        (*thread_create_child_func)(twd->prep_func_res);
469
 
 
470
 
    twd->initialized = 1;
471
 
 
472
 
    safe_cond_signal(&twd->cnd);
473
 
    safe_mutex_unlock(&twd->mtx);
474
 
 
475
 
    res = (*thr_func)(arg);
476
 
    thr_exit_cleanup();
477
 
    return res;
478
 
}
479
 
 
480
 
 
481
 
/*
482
 
 * ----------------------------------------------------------------------------
483
 
 * Exported functions
484
 
 * ----------------------------------------------------------------------------
485
 
 */
486
 
 
487
 
int
488
 
ethr_init(ethr_init_data *id)
489
 
{
490
 
    int res;
491
 
 
492
 
    if (!ethr_not_inited)
493
 
        return EINVAL;
494
 
 
495
 
    ethr_not_inited = 0;
496
 
 
497
 
    res = init_common(id);
498
 
    if (res != 0)
499
 
        goto error;
500
 
 
501
 
#if ETHR_HAVE_PTHREAD_ATFORK
502
 
    init_forksafe();
503
 
#endif
504
 
 
505
 
    no_ethreads = 1;
506
 
    res = ethr_mutex_init(&no_ethrs_mtx);
507
 
    if (res != 0)
508
 
        goto error;
509
 
    res = ethr_mutex_set_forksafe(&no_ethrs_mtx);
510
 
    if (res != 0 && res != ENOTSUP)
511
 
        goto error;
512
 
 
513
 
#ifndef ETHR_HAVE_OPTIMIZED_ATOMIC_OPS
514
 
    {
515
 
        int i;
516
 
        for (i = 0; i < (1 << ETHR_ATOMIC_ADDR_BITS); i++) {
517
 
#ifdef ETHR_HAVE_PTHREAD_SPIN_LOCK
518
 
            res = pthread_spin_init(&ethr_atomic_protection__[i].u.spnlck, 0);
519
 
#else
520
 
            res = ethr_mutex_init(&ethr_atomic_protection__[i].u.mtx);
521
 
#endif
522
 
            if (res != 0)
523
 
                goto error;
524
 
        }
525
 
    }
526
 
#endif
527
 
 
528
 
    return 0;
529
 
 
530
 
 error:
531
 
    ethr_not_inited = 1;
532
 
    return res;
533
 
 
534
 
}
535
 
 
536
 
int
537
 
ethr_thr_create(ethr_tid *tid, void * (*func)(void *), void *arg,
538
 
                ethr_thr_opts *opts)
539
 
{
540
 
    thr_wrap_data_ twd;
541
 
    pthread_attr_t attr;
542
 
    int res, dres;
543
 
    int use_stack_size = (opts && opts->suggested_stack_size >= 0
544
 
                          ? opts->suggested_stack_size
545
 
                          : -1 /* Use system default */);
546
 
 
547
 
#ifdef ETHR_MODIFIED_DEFAULT_STACK_SIZE
548
 
    if (use_stack_size < 0)
549
 
        use_stack_size = ETHR_MODIFIED_DEFAULT_STACK_SIZE;
550
 
#endif
551
 
 
552
 
    twd.initialized = 0;
553
 
    twd.thr_func = func;
554
 
    twd.arg = arg;
555
 
 
556
 
#if ETHR_XCHK
557
 
    if (ethr_not_inited) {
558
 
        ASSERT(0);
559
 
        return EACCES;
560
 
    }
561
 
    if (!tid || !func) {
562
 
        ASSERT(0);
563
 
        return EINVAL;
564
 
    }
565
 
#endif
566
 
 
567
 
    /* Call prepare func if it exist */
568
 
    if (thread_create_prepare_func)
569
 
        twd.prep_func_res = (*thread_create_prepare_func)();
570
 
    else
571
 
        twd.prep_func_res = NULL;
572
 
 
573
 
    /* Set som thread attributes */
574
 
    res = pthread_attr_init(&attr);
575
 
    if (res != 0)
576
 
        goto cleanup_parent_func;
577
 
    res = pthread_mutex_init(&twd.mtx, NULL);
578
 
    if (res != 0)
579
 
        goto cleanup_attr_destroy;
580
 
    res = pthread_cond_init(&twd.cnd, NULL);
581
 
    if (res != 0)
582
 
        goto cleanup_mutex_destroy;
583
 
 
584
 
    /* Schedule child thread in system scope (if possible) ... */
585
 
    res = pthread_attr_setscope(&attr, PTHREAD_SCOPE_SYSTEM);
586
 
    if (res != 0 && res != ENOTSUP)
587
 
        goto cleanup_cond_destroy;
588
 
 
589
 
    if (use_stack_size >= 0) {
590
 
        size_t suggested_stack_size = (size_t) use_stack_size;
591
 
        size_t stack_size;
592
 
#ifdef DEBUG
593
 
        suggested_stack_size /= 2; /* Make sure we got margin */
594
 
#endif
595
 
#ifdef ETHR_STACK_GUARD_SIZE
596
 
        /* The guard is at least on some platforms included in the stack size
597
 
           passed when creating threads */
598
 
        suggested_stack_size += ETHR_B2KW(ETHR_STACK_GUARD_SIZE);
599
 
#endif
600
 
        if (suggested_stack_size < min_stack_size)
601
 
            stack_size = ETHR_KW2B(min_stack_size);
602
 
        else if (suggested_stack_size > max_stack_size)
603
 
            stack_size = ETHR_KW2B(max_stack_size);
604
 
        else
605
 
            stack_size = ETHR_PAGE_ALIGN(ETHR_KW2B(suggested_stack_size));
606
 
        (void) pthread_attr_setstacksize(&attr, stack_size);
607
 
    }
608
 
 
609
 
#ifdef ETHR_STACK_GUARD_SIZE
610
 
    (void) pthread_attr_setguardsize(&attr, ETHR_STACK_GUARD_SIZE);
611
 
#endif
612
 
 
613
 
    /* Detached or joinable... */
614
 
    res = pthread_attr_setdetachstate(&attr,
615
 
                                      (opts && opts->detached
616
 
                                       ? PTHREAD_CREATE_DETACHED
617
 
                                       : PTHREAD_CREATE_JOINABLE));
618
 
    if (res != 0)
619
 
        goto cleanup_cond_destroy;
620
 
    
621
 
    res = pthread_mutex_lock(&twd.mtx);
622
 
 
623
 
    if (res != 0)
624
 
        goto cleanup_cond_destroy;
625
 
 
626
 
    safe_mutex_lock(&no_ethrs_mtx.pt_mtx);
627
 
    if (no_ethreads < ETHR_MAX_THREADS) {
628
 
        no_ethreads++;
629
 
        safe_mutex_unlock(&no_ethrs_mtx.pt_mtx);
630
 
    }
631
 
    else {
632
 
        res = EAGAIN;
633
 
        safe_mutex_unlock(&no_ethrs_mtx.pt_mtx);
634
 
        goto cleanup_mutex_unlock;
635
 
    }
636
 
 
637
 
    res = pthread_create((pthread_t *) tid, &attr, thr_wrapper, (void *) &twd);
638
 
 
639
 
    if (res != 0) {
640
 
        safe_mutex_lock(&no_ethrs_mtx.pt_mtx);
641
 
        ASSERT(no_ethreads > 0);
642
 
        no_ethreads--;
643
 
        safe_mutex_unlock(&no_ethrs_mtx.pt_mtx);
644
 
    }
645
 
    else {
646
 
 
647
 
        /* Wait for child to initialize... */
648
 
        while (!twd.initialized) {
649
 
            res = pthread_cond_wait(&twd.cnd, &twd.mtx);
650
 
            if (res != 0 && res != EINTR)
651
 
                break;
652
 
        }
653
 
 
654
 
    }
655
 
 
656
 
    /* Cleanup... */
657
 
 cleanup_mutex_unlock:
658
 
    dres = pthread_mutex_unlock(&twd.mtx);
659
 
    if (res == 0)
660
 
        res = dres;
661
 
 cleanup_cond_destroy:
662
 
    dres = pthread_cond_destroy(&twd.cnd);
663
 
    if (res == 0)
664
 
        res = dres;
665
 
 cleanup_mutex_destroy:
666
 
    dres = pthread_mutex_destroy(&twd.mtx);
667
 
    if (res == 0)
668
 
        res = dres;
669
 
 cleanup_attr_destroy:
670
 
    dres = pthread_attr_destroy(&attr);
671
 
    if (res == 0)
672
 
        res = dres;
673
 
 cleanup_parent_func:
674
 
    if (thread_create_parent_func)
675
 
        (*thread_create_parent_func)(twd.prep_func_res);
676
 
 
677
 
    return res;
678
 
}
679
 
 
680
 
int
681
 
ethr_thr_join(ethr_tid tid, void **res)
682
 
{
683
 
#if ETHR_XCHK
684
 
    if (ethr_not_inited) {
685
 
        ASSERT(0);
686
 
        return EACCES;
687
 
    }
688
 
#endif
689
 
    return pthread_join((pthread_t) tid, res);
690
 
}
691
 
 
692
 
int
693
 
ethr_thr_detach(ethr_tid tid)
694
 
{
695
 
#if ETHR_XCHK
696
 
    if (ethr_not_inited) {
697
 
        ASSERT(0);
698
 
        return EACCES;
699
 
    }
700
 
#endif
701
 
    return pthread_detach((pthread_t) tid);
702
 
}
703
 
 
704
 
void
705
 
ethr_thr_exit(void *res)
706
 
{
707
 
#if ETHR_XCHK
708
 
    if (ethr_not_inited) {
709
 
        ASSERT(0);
710
 
        return;
711
 
    }
712
 
#endif
713
 
    thr_exit_cleanup();
714
 
    pthread_exit(res);
715
 
}
716
 
 
717
 
ethr_tid
718
 
ethr_self(void)
719
 
{
720
 
    return (ethr_tid) pthread_self();
721
 
}
722
 
 
723
 
int
724
 
ethr_equal_tids(ethr_tid tid1, ethr_tid tid2)
725
 
{
726
 
    return pthread_equal((pthread_t) tid1, (pthread_t) tid2);
727
 
}
728
 
 
729
 
 
730
 
/*
731
 
 * Mutex functions
732
 
 */
733
 
 
734
 
 
735
 
int
736
 
ethr_mutex_init(ethr_mutex *mtx)
737
 
{
738
 
#if ETHR_XCHK
739
 
    if (ethr_not_inited) {
740
 
        ASSERT(0);
741
 
        return EACCES;
742
 
    }
743
 
    if (!mtx) {
744
 
        ASSERT(0);
745
 
        return EINVAL;
746
 
    }
747
 
    mtx->initialized = ETHR_MUTEX_INITIALIZED;
748
 
#endif
749
 
    mtx->prev = NULL;
750
 
    mtx->next = NULL;
751
 
    mtx->is_rec_mtx = 0;
752
 
    return pthread_mutex_init(&mtx->pt_mtx, NULL);
753
 
}
754
 
 
755
 
#ifdef ETHR_HAVE_ETHR_REC_MUTEX_INIT
756
 
 
757
 
int
758
 
ethr_rec_mutex_init(ethr_mutex *mtx)
759
 
{
760
 
#if ETHR_XCHK
761
 
    if (ethr_not_inited) {
762
 
        ASSERT(0);
763
 
        return EACCES;
764
 
    }
765
 
    if (!mtx) {
766
 
        ASSERT(0);
767
 
        return EINVAL;
768
 
    }
769
 
    mtx->initialized = ETHR_MUTEX_INITIALIZED;
770
 
#endif
771
 
    if (rec_mtx_attr_need_init)
772
 
        init_rec_mtx_attr();
773
 
 
774
 
    mtx->prev = NULL;
775
 
    mtx->next = NULL;
776
 
    mtx->is_rec_mtx = 1;
777
 
    return pthread_mutex_init(&mtx->pt_mtx, &rec_mtx_attr);
778
 
}
779
 
 
780
 
#endif /* #if ETHR_HAVE_ETHR_REC_MUTEX_INIT */
781
 
 
782
 
int
783
 
ethr_mutex_destroy(ethr_mutex *mtx)
784
 
{
785
 
#if ETHR_XCHK
786
 
    if (ethr_not_inited) {
787
 
        ASSERT(0);
788
 
        return EACCES;
789
 
    }
790
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
791
 
        ASSERT(0);
792
 
        return EINVAL;
793
 
    }
794
 
#endif
795
 
    if (mtx->next) {
796
 
        ASSERT(mtx->prev);
797
 
        ethr_mutex_unset_forksafe(mtx);
798
 
    }
799
 
#if ETHR_XCHK
800
 
    mtx->initialized = 0;
801
 
#endif
802
 
    return pthread_mutex_destroy(&mtx->pt_mtx);
803
 
}
804
 
 
805
 
int ethr_mutex_set_forksafe(ethr_mutex *mtx)
806
 
{
807
 
    int res;
808
 
#if ETHR_XCHK
809
 
    if (ethr_not_inited) {
810
 
        ASSERT(0);
811
 
        return EACCES;
812
 
    }
813
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
814
 
        ASSERT(0);
815
 
        return EINVAL;
816
 
    }
817
 
#endif
818
 
#if ETHR_HAVE_PTHREAD_ATFORK
819
 
    res = pthread_mutex_lock(&forksafe_mtx.pt_mtx);
820
 
    if (res != 0)
821
 
        return res;
822
 
    if (!forksafe_mtx.next) {
823
 
        ASSERT(!forksafe_mtx.prev);
824
 
        init_forksafe();
825
 
    }
826
 
    if (mtx->next) {
827
 
        /* forksafe already set for this mutex */ 
828
 
        ASSERT(mtx->prev);
829
 
    }
830
 
    else {
831
 
        mtx->next = forksafe_mtx.next;
832
 
        mtx->prev = &forksafe_mtx;
833
 
        forksafe_mtx.next->prev = mtx;
834
 
        forksafe_mtx.next = mtx;
835
 
    }
836
 
 
837
 
    res = pthread_mutex_unlock(&forksafe_mtx.pt_mtx);
838
 
 
839
 
#else /* #if ETHR_HAVE_PTHREAD_ATFORK */
840
 
    res = ENOTSUP;
841
 
#endif /* #if ETHR_HAVE_PTHREAD_ATFORK */
842
 
    return res;
843
 
}
844
 
 
845
 
int ethr_mutex_unset_forksafe(ethr_mutex *mtx)
846
 
{
847
 
    int res;
848
 
#if ETHR_XCHK
849
 
    if (ethr_not_inited) {
850
 
        ASSERT(0);
851
 
        return EACCES;
852
 
    }
853
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
854
 
        ASSERT(0);
855
 
        return EINVAL;
856
 
    }
857
 
#endif
858
 
#if ETHR_HAVE_PTHREAD_ATFORK
859
 
    res = pthread_mutex_lock(&forksafe_mtx.pt_mtx);
860
 
    if (res != 0)
861
 
        return res;
862
 
    if (!forksafe_mtx.next) {
863
 
        ASSERT(!forksafe_mtx.prev);
864
 
        init_forksafe();
865
 
    }
866
 
    if (!mtx->next) {
867
 
        /* forksafe already unset for this mutex */ 
868
 
        ASSERT(!mtx->prev);
869
 
    }
870
 
    else {
871
 
        mtx->prev->next = mtx->next;
872
 
        mtx->next->prev = mtx->prev;
873
 
        mtx->next = NULL;
874
 
        mtx->prev = NULL;
875
 
    }
876
 
    res = pthread_mutex_unlock(&forksafe_mtx.pt_mtx);
877
 
 
878
 
#else /* #if ETHR_HAVE_PTHREAD_ATFORK */
879
 
    res = ENOTSUP;
880
 
#endif /* #if ETHR_HAVE_PTHREAD_ATFORK */
881
 
    return res;
882
 
}
883
 
 
884
 
int
885
 
ethr_mutex_trylock(ethr_mutex *mtx)
886
 
{
887
 
#if ETHR_XCHK
888
 
    if (ethr_not_inited) {
889
 
        ASSERT(0);
890
 
        return EACCES;
891
 
    }
892
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
893
 
        ASSERT(0);
894
 
        return EINVAL;
895
 
    }
896
 
#endif
897
 
    return ethr_mutex_trylock__(mtx);
898
 
}
899
 
 
900
 
int
901
 
ethr_mutex_lock(ethr_mutex *mtx)
902
 
{
903
 
#if ETHR_XCHK
904
 
    if (ethr_not_inited) {
905
 
        ASSERT(0);
906
 
        return EACCES;
907
 
    }
908
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
909
 
        ASSERT(0);
910
 
        return EINVAL;
911
 
    }
912
 
#endif
913
 
    return ethr_mutex_lock__(mtx);
914
 
}
915
 
 
916
 
int
917
 
ethr_mutex_unlock(ethr_mutex *mtx)
918
 
{
919
 
#if ETHR_XCHK
920
 
    if (ethr_not_inited) {
921
 
        ASSERT(0);
922
 
        return EACCES;
923
 
    }
924
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
925
 
        ASSERT(0);
926
 
        return EINVAL;
927
 
    }
928
 
#endif
929
 
    return ethr_mutex_unlock__(mtx);
930
 
}
931
 
 
932
 
/*
933
 
 * Condition variable functions
934
 
 */
935
 
 
936
 
int
937
 
ethr_cond_init(ethr_cond *cnd)
938
 
{
939
 
#if ETHR_XCHK
940
 
    if (ethr_not_inited) {
941
 
        ASSERT(0);
942
 
        return EACCES;
943
 
    }
944
 
    if (!cnd) {
945
 
        ASSERT(0);
946
 
        return EINVAL;
947
 
    }
948
 
    cnd->initialized = ETHR_COND_INITIALIZED;
949
 
#endif
950
 
    return pthread_cond_init(&cnd->pt_cnd, NULL);
951
 
}
952
 
 
953
 
int
954
 
ethr_cond_destroy(ethr_cond *cnd)
955
 
{
956
 
#if ETHR_XCHK
957
 
    if (ethr_not_inited) {
958
 
        ASSERT(0);
959
 
        return EACCES;
960
 
    }
961
 
    if (!cnd || cnd->initialized != ETHR_COND_INITIALIZED) {
962
 
        ASSERT(0);
963
 
        return EINVAL;
964
 
    }
965
 
    cnd->initialized = 0;
966
 
#endif
967
 
    return pthread_cond_destroy(&cnd->pt_cnd);
968
 
}
969
 
 
970
 
int
971
 
ethr_cond_signal(ethr_cond *cnd)
972
 
{
973
 
#if ETHR_XCHK
974
 
    if (ethr_not_inited) {
975
 
        ASSERT(0);
976
 
        return EACCES;
977
 
    }
978
 
    if (!cnd || cnd->initialized != ETHR_COND_INITIALIZED) {
979
 
        ASSERT(0);
980
 
        return EINVAL;
981
 
    }
982
 
#endif
983
 
    return pthread_cond_signal(&cnd->pt_cnd);
984
 
}
985
 
 
986
 
int
987
 
ethr_cond_broadcast(ethr_cond *cnd)
988
 
{
989
 
#if ETHR_XCHK
990
 
    if (ethr_not_inited) {
991
 
        ASSERT(0);
992
 
        return EACCES;
993
 
    }
994
 
    if (!cnd || cnd->initialized != ETHR_COND_INITIALIZED) {
995
 
        ASSERT(0);
996
 
        return EINVAL;
997
 
    }
998
 
#endif
999
 
    return pthread_cond_broadcast(&cnd->pt_cnd);
1000
 
}
1001
 
 
1002
 
int
1003
 
ethr_cond_wait(ethr_cond *cnd, ethr_mutex *mtx)
1004
 
{
1005
 
#if ETHR_XCHK
1006
 
    if (ethr_not_inited) {
1007
 
        ASSERT(0);
1008
 
        return EACCES;
1009
 
    }
1010
 
    if (!cnd
1011
 
        || cnd->initialized != ETHR_COND_INITIALIZED
1012
 
        || !mtx
1013
 
        || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
1014
 
        ASSERT(0);
1015
 
        return EINVAL;
1016
 
    }
1017
 
#endif
1018
 
    return pthread_cond_wait(&cnd->pt_cnd, &mtx->pt_mtx);
1019
 
}
1020
 
 
1021
 
int
1022
 
ethr_cond_timedwait(ethr_cond *cnd, ethr_mutex *mtx, ethr_timeval *timeout)
1023
 
{
1024
 
    struct timespec to;
1025
 
#if ETHR_XCHK
1026
 
    if (ethr_not_inited) {
1027
 
        ASSERT(0);
1028
 
        return EACCES;
1029
 
    }
1030
 
    if (!cnd
1031
 
        || cnd->initialized != ETHR_COND_INITIALIZED
1032
 
        || !mtx
1033
 
        || mtx->initialized != ETHR_MUTEX_INITIALIZED
1034
 
        || !timeout) {
1035
 
        ASSERT(0);
1036
 
        return EINVAL;
1037
 
    }
1038
 
#endif
1039
 
 
1040
 
    to.tv_sec = timeout->tv_sec;
1041
 
    to.tv_nsec = timeout->tv_nsec;
1042
 
 
1043
 
    return pthread_cond_timedwait(&cnd->pt_cnd, &mtx->pt_mtx, &to);
1044
 
}
1045
 
 
1046
 
 
1047
 
#ifdef ETHR_HAVE_PTHREAD_RWLOCK_INIT
1048
 
 
1049
 
int
1050
 
ethr_rwmutex_init(ethr_rwmutex *rwmtx)
1051
 
{
1052
 
#if ETHR_XCHK
1053
 
    if (ethr_not_inited) {
1054
 
        ASSERT(0);
1055
 
        return EACCES;
1056
 
    }
1057
 
    if (!rwmtx) {
1058
 
        ASSERT(0);
1059
 
        return EINVAL;
1060
 
    }
1061
 
    rwmtx->initialized = ETHR_RWMUTEX_INITIALIZED;
1062
 
#endif
1063
 
    return pthread_rwlock_init(&rwmtx->pt_rwlock, NULL);
1064
 
}
1065
 
 
1066
 
int
1067
 
ethr_rwmutex_destroy(ethr_rwmutex *rwmtx)
1068
 
{
1069
 
    int res;
1070
 
#if ETHR_XCHK
1071
 
    if (ethr_not_inited) {
1072
 
        ASSERT(0);
1073
 
        return EACCES;
1074
 
    }
1075
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1076
 
        ASSERT(0);
1077
 
        return EINVAL;
1078
 
    }
1079
 
#endif
1080
 
    res = pthread_rwlock_destroy(&rwmtx->pt_rwlock);
1081
 
#if ETHR_XCHK
1082
 
    rwmtx->initialized = 0;
1083
 
#endif
1084
 
    return res;
1085
 
}
1086
 
 
1087
 
int
1088
 
ethr_rwmutex_tryrlock(ethr_rwmutex *rwmtx)
1089
 
{
1090
 
#if ETHR_XCHK
1091
 
    if (ethr_not_inited) {
1092
 
        ASSERT(0);
1093
 
        return EACCES;
1094
 
    }
1095
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1096
 
        ASSERT(0);
1097
 
        return EINVAL;
1098
 
    }
1099
 
#endif
1100
 
    return ethr_rwmutex_tryrlock__(rwmtx);
1101
 
}
1102
 
 
1103
 
int
1104
 
ethr_rwmutex_rlock(ethr_rwmutex *rwmtx)
1105
 
{
1106
 
#if ETHR_XCHK
1107
 
    if (ethr_not_inited) {
1108
 
        ASSERT(0);
1109
 
        return EACCES;
1110
 
    }
1111
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1112
 
        ASSERT(0);
1113
 
        return EINVAL;
1114
 
    }
1115
 
#endif
1116
 
    return ethr_rwmutex_rlock__(rwmtx);
1117
 
}
1118
 
 
1119
 
int
1120
 
ethr_rwmutex_runlock(ethr_rwmutex *rwmtx)
1121
 
{
1122
 
#if ETHR_XCHK
1123
 
    if (ethr_not_inited) {
1124
 
        ASSERT(0);
1125
 
        return EACCES;
1126
 
    }
1127
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1128
 
        ASSERT(0);
1129
 
        return EINVAL;
1130
 
    }
1131
 
#endif
1132
 
    return ethr_rwmutex_runlock__(rwmtx);
1133
 
}
1134
 
 
1135
 
int
1136
 
ethr_rwmutex_tryrwlock(ethr_rwmutex *rwmtx)
1137
 
{
1138
 
#if ETHR_XCHK
1139
 
    if (ethr_not_inited) {
1140
 
        ASSERT(0);
1141
 
        return EACCES;
1142
 
    }
1143
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1144
 
        ASSERT(0);
1145
 
        return EINVAL;
1146
 
    }
1147
 
#endif
1148
 
    return ethr_rwmutex_tryrwlock__(rwmtx);
1149
 
}
1150
 
 
1151
 
int
1152
 
ethr_rwmutex_rwlock(ethr_rwmutex *rwmtx)
1153
 
{
1154
 
#if ETHR_XCHK
1155
 
    if (ethr_not_inited) {
1156
 
        ASSERT(0);
1157
 
        return EACCES;
1158
 
    }
1159
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1160
 
        ASSERT(0);
1161
 
        return EINVAL;
1162
 
    }
1163
 
#endif
1164
 
    return ethr_rwmutex_rwlock__(rwmtx);
1165
 
}
1166
 
 
1167
 
int
1168
 
ethr_rwmutex_rwunlock(ethr_rwmutex *rwmtx)
1169
 
{
1170
 
#if ETHR_XCHK
1171
 
    if (ethr_not_inited) {
1172
 
        ASSERT(0);
1173
 
        return EACCES;
1174
 
    }
1175
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
1176
 
        ASSERT(0);
1177
 
        return EINVAL;
1178
 
    }
1179
 
#endif
1180
 
    return ethr_rwmutex_rwunlock__(rwmtx);
1181
 
}
1182
 
 
1183
 
#endif /* #ifdef ETHR_HAVE_PTHREAD_RWLOCK_INIT */
1184
 
 
1185
 
/*
1186
 
 * Current time
1187
 
 */
1188
 
 
1189
 
int
1190
 
ethr_time_now(ethr_timeval *time)
1191
 
{
1192
 
    int res;
1193
 
    struct timeval tv;
1194
 
#if ETHR_XCHK
1195
 
    if (ethr_not_inited) {
1196
 
        ASSERT(0);
1197
 
        return EACCES;
1198
 
    }
1199
 
    if (!time) {
1200
 
        ASSERT(0);
1201
 
        return EINVAL;
1202
 
    }
1203
 
#endif
1204
 
 
1205
 
    res = gettimeofday(&tv, NULL);
1206
 
    time->tv_sec = (long) tv.tv_sec;
1207
 
    time->tv_nsec = ((long) tv.tv_usec)*1000;
1208
 
    return res;
1209
 
}
1210
 
 
1211
 
/*
1212
 
 * Thread specific data
1213
 
 */
1214
 
 
1215
 
int
1216
 
ethr_tsd_key_create(ethr_tsd_key *keyp)
1217
 
{
1218
 
#if ETHR_XCHK
1219
 
    if (ethr_not_inited) {
1220
 
        ASSERT(0);
1221
 
        return EACCES;
1222
 
    }
1223
 
    if (!keyp) {
1224
 
        ASSERT(0);
1225
 
        return EINVAL;
1226
 
    }
1227
 
#endif
1228
 
    return pthread_key_create((pthread_key_t *) keyp, NULL);
1229
 
}
1230
 
 
1231
 
int
1232
 
ethr_tsd_key_delete(ethr_tsd_key key)
1233
 
{
1234
 
#if ETHR_XCHK
1235
 
    if (ethr_not_inited) {
1236
 
        ASSERT(0);
1237
 
        return EACCES;
1238
 
    }
1239
 
#endif
1240
 
    return pthread_key_delete((pthread_key_t) key);
1241
 
}
1242
 
 
1243
 
int
1244
 
ethr_tsd_set(ethr_tsd_key key, void *value)
1245
 
{
1246
 
#if ETHR_XCHK
1247
 
    if (ethr_not_inited) {
1248
 
        ASSERT(0);
1249
 
        return EACCES;
1250
 
    }
1251
 
#endif
1252
 
    return pthread_setspecific((pthread_key_t) key, value);
1253
 
}
1254
 
 
1255
 
void *
1256
 
ethr_tsd_get(ethr_tsd_key key)
1257
 
{
1258
 
#if ETHR_XCHK
1259
 
    if (ethr_not_inited) {
1260
 
        ASSERT(0);
1261
 
        return NULL;
1262
 
    }
1263
 
#endif
1264
 
    return pthread_getspecific((pthread_key_t) key);
1265
 
}
1266
 
 
1267
 
/*
1268
 
 * Signal functions
1269
 
 */
1270
 
 
1271
 
#if ETHR_HAVE_ETHR_SIG_FUNCS
1272
 
 
1273
 
int ethr_sigmask(int how, const sigset_t *set, sigset_t *oset)
1274
 
{
1275
 
#if ETHR_XCHK
1276
 
    if (ethr_not_inited) {
1277
 
        ASSERT(0);
1278
 
        return EACCES;
1279
 
    }
1280
 
    if (!set && !oset) {
1281
 
        ASSERT(0);
1282
 
        return EINVAL;
1283
 
    }
1284
 
#endif
1285
 
  return pthread_sigmask(how, set, oset);
1286
 
}
1287
 
 
1288
 
int ethr_sigwait(const sigset_t *set, int *sig)
1289
 
{
1290
 
#if ETHR_XCHK
1291
 
    if (ethr_not_inited) {
1292
 
        ASSERT(0);
1293
 
        return EACCES;
1294
 
    }
1295
 
    if (!set || !sig) {
1296
 
        ASSERT(0);
1297
 
        return EINVAL;
1298
 
    }
1299
 
#endif
1300
 
    if (sigwait(set, sig) < 0)
1301
 
        return errno;
1302
 
    return 0;
1303
 
}
1304
 
 
1305
 
#endif /* #if ETHR_HAVE_ETHR_SIG_FUNCS */
1306
 
 
1307
 
#elif defined(ETHR_WIN32_THREADS)
1308
 
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
1309
 
 * Native win32 threads implementation                                       *
1310
 
\*                                                                           */
1311
 
 
1312
 
#define INVALID_TID -1
1313
 
 
1314
 
/* The spin count values are more or less taken out of the blue */
1315
 
#define ETHR_MUTEX_SPIN_COUNT   5000
1316
 
#define ETHR_COND_SPIN_COUNT    1000
1317
 
 
1318
 
ethr_tid serial_shift; /* Bits to shift serial when constructing a tid */
1319
 
ethr_tid last_serial; /* Last thread table serial used */
1320
 
ethr_tid last_ix; /* Last thread table index used */
1321
 
ethr_tid thr_ix_mask; /* Mask used to mask out thread table index from a tid */
1322
 
 
1323
 
/* Event used for conditional variables. On per thread. */
1324
 
/*typedef struct cnd_wait_event__ cnd_wait_event_;*/
1325
 
struct cnd_wait_event__ {
1326
 
    HANDLE handle;
1327
 
    cnd_wait_event_ *prev;
1328
 
    cnd_wait_event_ *next;
1329
 
    int in_queue;
1330
 
};
1331
 
 
1332
 
/* Thread specific data. Stored in the thread table */
1333
 
typedef struct {
1334
 
    ethr_tid thr_id;
1335
 
    HANDLE thr_handle;
1336
 
    ethr_tid joiner;
1337
 
    void *result;
1338
 
    cnd_wait_event_ wait_event;
1339
 
} thr_data_;
1340
 
 
1341
 
/* Argument passed to thr_wrapper() */
1342
 
typedef struct {
1343
 
    void * (*func)(void *);
1344
 
    void * arg;
1345
 
    thr_data_ *ptd;
1346
 
    thr_data_ *td;
1347
 
    int res;
1348
 
    void *prep_func_res;
1349
 
} thr_wrap_data_;
1350
 
 
1351
 
 
1352
 
static CRITICAL_SECTION thr_table_cs; /* Critical section used to protect
1353
 
                                         the thread table from concurrent
1354
 
                                         accesses. */
1355
 
static CRITICAL_SECTION fake_static_init_cs; /* Critical section used to protect
1356
 
                                        initialazition of 'statically
1357
 
                                        initialized' mutexes */
1358
 
static thr_data_ * thr_table[ETHR_MAX_THREADS]; /* The thread table */
1359
 
 
1360
 
static DWORD tls_own_thr_data;
1361
 
 
1362
 
static thr_data_ main_thr_data;
1363
 
 
1364
 
#define THR_IX(TID)     ((TID) & thr_ix_mask)
1365
 
#define OWN_THR_DATA    ((thr_data_ *) TlsGetValue(tls_own_thr_data))
1366
 
 
1367
 
/*
1368
 
 * ----------------------------------------------------------------------------
1369
 
 * Static functions
1370
 
 * ----------------------------------------------------------------------------
1371
 
 */
1372
 
 
1373
 
static int
1374
 
get_errno(void)
1375
 
{
1376
 
    switch (GetLastError()) {
1377
 
    case ERROR_INVALID_FUNCTION:                return EINVAL;  /* 1    */
1378
 
    case ERROR_FILE_NOT_FOUND:                  return ENOENT;  /* 2    */
1379
 
    case ERROR_PATH_NOT_FOUND:                  return ENOENT;  /* 3    */
1380
 
    case ERROR_TOO_MANY_OPEN_FILES:             return EMFILE;  /* 4    */
1381
 
    case ERROR_ACCESS_DENIED:                   return EACCES;  /* 5    */
1382
 
    case ERROR_INVALID_HANDLE:                  return EBADF;   /* 6    */
1383
 
    case ERROR_ARENA_TRASHED:                   return ENOMEM;  /* 7    */
1384
 
    case ERROR_NOT_ENOUGH_MEMORY:               return ENOMEM;  /* 8    */
1385
 
    case ERROR_INVALID_BLOCK:                   return ENOMEM;  /* 9    */
1386
 
    case ERROR_BAD_ENVIRONMENT:                 return E2BIG;   /* 10   */
1387
 
    case ERROR_BAD_FORMAT:                      return ENOEXEC; /* 11   */
1388
 
    case ERROR_INVALID_ACCESS:                  return EINVAL;  /* 12   */
1389
 
    case ERROR_INVALID_DATA:                    return EINVAL;  /* 13   */
1390
 
    case ERROR_OUTOFMEMORY:                     return ENOMEM;  /* 14   */
1391
 
    case ERROR_INVALID_DRIVE:                   return ENOENT;  /* 15   */
1392
 
    case ERROR_CURRENT_DIRECTORY:               return EACCES;  /* 16   */
1393
 
    case ERROR_NOT_SAME_DEVICE:                 return EXDEV;   /* 17   */
1394
 
    case ERROR_NO_MORE_FILES:                   return ENOENT;  /* 18   */
1395
 
    case ERROR_WRITE_PROTECT:                   return EACCES;  /* 19   */
1396
 
    case ERROR_BAD_UNIT:                        return EACCES;  /* 20   */
1397
 
    case ERROR_NOT_READY:                       return EACCES;  /* 21   */
1398
 
    case ERROR_BAD_COMMAND:                     return EACCES;  /* 22   */
1399
 
    case ERROR_CRC:                             return EACCES;  /* 23   */
1400
 
    case ERROR_BAD_LENGTH:                      return EACCES;  /* 24   */
1401
 
    case ERROR_SEEK:                            return EACCES;  /* 25   */
1402
 
    case ERROR_NOT_DOS_DISK:                    return EACCES;  /* 26   */
1403
 
    case ERROR_SECTOR_NOT_FOUND:                return EACCES;  /* 27   */
1404
 
    case ERROR_OUT_OF_PAPER:                    return EACCES;  /* 28   */
1405
 
    case ERROR_WRITE_FAULT:                     return EACCES;  /* 29   */
1406
 
    case ERROR_READ_FAULT:                      return EACCES;  /* 30   */
1407
 
    case ERROR_GEN_FAILURE:                     return EACCES;  /* 31   */
1408
 
    case ERROR_SHARING_VIOLATION:               return EACCES;  /* 32   */
1409
 
    case ERROR_LOCK_VIOLATION:                  return EACCES;  /* 33   */
1410
 
    case ERROR_WRONG_DISK:                      return EACCES;  /* 34   */
1411
 
    case ERROR_SHARING_BUFFER_EXCEEDED:         return EACCES;  /* 36   */
1412
 
    case ERROR_BAD_NETPATH:                     return ENOENT;  /* 53   */
1413
 
    case ERROR_NETWORK_ACCESS_DENIED:           return EACCES;  /* 65   */
1414
 
    case ERROR_BAD_NET_NAME:                    return ENOENT;  /* 67   */
1415
 
    case ERROR_FILE_EXISTS:                     return EEXIST;  /* 80   */
1416
 
    case ERROR_CANNOT_MAKE:                     return EACCES;  /* 82   */
1417
 
    case ERROR_FAIL_I24:                        return EACCES;  /* 83   */
1418
 
    case ERROR_INVALID_PARAMETER:               return EINVAL;  /* 87   */
1419
 
    case ERROR_NO_PROC_SLOTS:                   return EAGAIN;  /* 89   */
1420
 
    case ERROR_DRIVE_LOCKED:                    return EACCES;  /* 108  */
1421
 
    case ERROR_BROKEN_PIPE:                     return EPIPE;   /* 109  */
1422
 
    case ERROR_DISK_FULL:                       return ENOSPC;  /* 112  */
1423
 
    case ERROR_INVALID_TARGET_HANDLE:           return EBADF;   /* 114  */
1424
 
    case ERROR_WAIT_NO_CHILDREN:                return ECHILD;  /* 128  */
1425
 
    case ERROR_CHILD_NOT_COMPLETE:              return ECHILD;  /* 129  */
1426
 
    case ERROR_DIRECT_ACCESS_HANDLE:            return EBADF;   /* 130  */
1427
 
    case ERROR_NEGATIVE_SEEK:                   return EINVAL;  /* 131  */
1428
 
    case ERROR_SEEK_ON_DEVICE:                  return EACCES;  /* 132  */
1429
 
    case ERROR_DIR_NOT_EMPTY:                   return ENOTEMPTY;/* 145 */
1430
 
    case ERROR_NOT_LOCKED:                      return EACCES;  /* 158  */
1431
 
    case ERROR_BAD_PATHNAME:                    return ENOENT;  /* 161  */
1432
 
    case ERROR_MAX_THRDS_REACHED:               return EAGAIN;  /* 164  */
1433
 
    case ERROR_LOCK_FAILED:                     return EACCES;  /* 167  */
1434
 
    case ERROR_ALREADY_EXISTS:                  return EEXIST;  /* 183  */
1435
 
    case ERROR_INVALID_STARTING_CODESEG:        return ENOEXEC; /* 188  */
1436
 
    case ERROR_INVALID_STACKSEG:                return ENOEXEC; /* 189  */
1437
 
    case ERROR_INVALID_MODULETYPE:              return ENOEXEC; /* 190  */
1438
 
    case ERROR_INVALID_EXE_SIGNATURE:           return ENOEXEC; /* 191  */
1439
 
    case ERROR_EXE_MARKED_INVALID:              return ENOEXEC; /* 192  */
1440
 
    case ERROR_BAD_EXE_FORMAT:                  return ENOEXEC; /* 193  */
1441
 
    case ERROR_ITERATED_DATA_EXCEEDS_64k:       return ENOEXEC; /* 194  */
1442
 
    case ERROR_INVALID_MINALLOCSIZE:            return ENOEXEC; /* 195  */
1443
 
    case ERROR_DYNLINK_FROM_INVALID_RING:       return ENOEXEC; /* 196  */
1444
 
    case ERROR_IOPL_NOT_ENABLED:                return ENOEXEC; /* 197  */
1445
 
    case ERROR_INVALID_SEGDPL:                  return ENOEXEC; /* 198  */
1446
 
    case ERROR_AUTODATASEG_EXCEEDS_64k:         return ENOEXEC; /* 199  */
1447
 
    case ERROR_RING2SEG_MUST_BE_MOVABLE:        return ENOEXEC; /* 200  */
1448
 
    case ERROR_RELOC_CHAIN_XEEDS_SEGLIM:        return ENOEXEC; /* 201  */
1449
 
    case ERROR_INFLOOP_IN_RELOC_CHAIN:          return ENOEXEC; /* 202  */
1450
 
    case ERROR_FILENAME_EXCED_RANGE:            return ENOENT;  /* 206  */
1451
 
    case ERROR_NESTING_NOT_ALLOWED:             return EAGAIN;  /* 215  */
1452
 
    case ERROR_NOT_ENOUGH_QUOTA:                return ENOMEM;  /* 1816 */
1453
 
    default:                                    return EINVAL;
1454
 
    }
1455
 
}
1456
 
 
1457
 
static ETHR_INLINE thr_data_ *
1458
 
tid2thr(ethr_tid tid)
1459
 
{
1460
 
    ethr_tid ix;
1461
 
    thr_data_ *td;
1462
 
    
1463
 
    if (tid < 0)
1464
 
        return NULL;
1465
 
    ix = THR_IX(tid);
1466
 
    if (ix >= ETHR_MAX_THREADS)
1467
 
        return NULL;
1468
 
    td = thr_table[ix];
1469
 
    if (!td)
1470
 
        return NULL;
1471
 
    if (td->thr_id != tid)
1472
 
        return NULL;
1473
 
    return td;
1474
 
}
1475
 
 
1476
 
static ETHR_INLINE void
1477
 
new_tid(ethr_tid *new_tid, ethr_tid *new_serial, ethr_tid *new_ix)
1478
 
{
1479
 
    ethr_tid tmp_serial = last_serial;
1480
 
    ethr_tid tmp_ix = last_ix + 1;
1481
 
    ethr_tid start_ix = tmp_ix;
1482
 
 
1483
 
 
1484
 
    do {
1485
 
        if (tmp_ix >= ETHR_MAX_THREADS) {
1486
 
            tmp_serial++;
1487
 
            if ((tmp_serial << serial_shift) < 0)
1488
 
                tmp_serial = 0;
1489
 
            tmp_ix = 0;
1490
 
        }
1491
 
        if (!thr_table[tmp_ix]) {
1492
 
            *new_tid    = (tmp_serial << serial_shift) | tmp_ix;
1493
 
            *new_serial = tmp_serial;
1494
 
            *new_ix     = tmp_ix;
1495
 
            return;
1496
 
        }
1497
 
        tmp_ix++;
1498
 
    } while (tmp_ix != start_ix);
1499
 
 
1500
 
    *new_tid    = INVALID_TID;
1501
 
    *new_serial = INVALID_TID;
1502
 
    *new_ix     = INVALID_TID;
1503
 
 
1504
 
}
1505
 
 
1506
 
 
1507
 
static void thr_exit_cleanup(thr_data_ *td, void *res)
1508
 
{
1509
 
 
1510
 
    ASSERT(td == OWN_THR_DATA);
1511
 
 
1512
 
    run_exit_handlers();
1513
 
 
1514
 
    EnterCriticalSection(&thr_table_cs);
1515
 
    CloseHandle(td->wait_event.handle);
1516
 
    if (td->thr_handle == INVALID_HANDLE_VALUE) {
1517
 
        /* We are detached; cleanup thread table */
1518
 
        ASSERT(td->joiner == INVALID_TID);
1519
 
        ASSERT(td == thr_table[THR_IX(td->thr_id)]);
1520
 
        thr_table[THR_IX(td->thr_id)] = NULL;
1521
 
        if (td != &main_thr_data)
1522
 
            (*freep)((void *) td);
1523
 
    }
1524
 
    else {
1525
 
        /* Save result and let joining thread cleanup */
1526
 
        td->result = res;
1527
 
    }
1528
 
    LeaveCriticalSection(&thr_table_cs);
1529
 
}
1530
 
 
1531
 
static unsigned __stdcall thr_wrapper(LPVOID args)
1532
 
{
1533
 
    void *(*func)(void*) = ((thr_wrap_data_ *) args)->func;
1534
 
    void *arg = ((thr_wrap_data_ *) args)->arg;
1535
 
    thr_data_ *td = ((thr_wrap_data_ *) args)->td;
1536
 
 
1537
 
    td->wait_event.handle = CreateEvent(NULL, FALSE, FALSE, NULL);
1538
 
    if (td->wait_event.handle == INVALID_HANDLE_VALUE
1539
 
        || !TlsSetValue(tls_own_thr_data, (LPVOID) td)) {
1540
 
        ((thr_wrap_data_ *) args)->res = get_errno();
1541
 
        if (td->wait_event.handle != INVALID_HANDLE_VALUE)
1542
 
            CloseHandle(td->wait_event.handle);
1543
 
        SetEvent(((thr_wrap_data_ *) args)->ptd->wait_event.handle);
1544
 
        _endthreadex((unsigned) 0);
1545
 
        ASSERT(0);
1546
 
    }
1547
 
 
1548
 
    td->wait_event.prev = NULL;
1549
 
    td->wait_event.next = NULL;
1550
 
    td->wait_event.in_queue = 0;
1551
 
 
1552
 
    if (thread_create_child_func)
1553
 
        (*thread_create_child_func)(((thr_wrap_data_ *) args)->prep_func_res);
1554
 
 
1555
 
    ASSERT(td == OWN_THR_DATA);
1556
 
 
1557
 
    ((thr_wrap_data_ *) args)->res = 0;
1558
 
    SetEvent(((thr_wrap_data_ *) args)->ptd->wait_event.handle);
1559
 
 
1560
 
    thr_exit_cleanup(td, (*func)(arg));
1561
 
    return 0;
1562
 
}
1563
 
 
1564
 
int
1565
 
ethr_fake_static_mutex_init(ethr_mutex *mtx)
1566
 
{
1567
 
    EnterCriticalSection((CRITICAL_SECTION *) &fake_static_init_cs);
1568
 
    /* Got here under race conditions; check again... */
1569
 
    if (!mtx->initialized) {
1570
 
        if (!InitializeCriticalSectionAndSpinCount(&mtx->cs,
1571
 
                                                   ETHR_MUTEX_SPIN_COUNT))
1572
 
            return get_errno();
1573
 
        mtx->initialized = ETHR_MUTEX_INITIALIZED;
1574
 
    }
1575
 
    LeaveCriticalSection((CRITICAL_SECTION *) &fake_static_init_cs);
1576
 
    return 0;
1577
 
}
1578
 
 
1579
 
static int
1580
 
fake_static_cond_init(ethr_cond *cnd)
1581
 
{
1582
 
    EnterCriticalSection((CRITICAL_SECTION *) &fake_static_init_cs);
1583
 
    /* Got here under race conditions; check again... */
1584
 
    if (!cnd->initialized) {
1585
 
        if (!InitializeCriticalSectionAndSpinCount(&cnd->cs,
1586
 
                                                   ETHR_COND_SPIN_COUNT))
1587
 
            return get_errno();
1588
 
        cnd->queue = NULL;
1589
 
        cnd->queue_end = NULL;
1590
 
        cnd->initialized = ETHR_COND_INITIALIZED;
1591
 
    }
1592
 
    LeaveCriticalSection((CRITICAL_SECTION *) &fake_static_init_cs);
1593
 
    return 0;
1594
 
}
1595
 
 
1596
 
#ifdef __GNUC__
1597
 
#define LL_LITERAL(X) X##LL
1598
 
#else
1599
 
#define LL_LITERAL(X) X##i64
1600
 
#endif
1601
 
 
1602
 
#define EPOCH_JULIAN_DIFF LL_LITERAL(11644473600)
1603
 
 
1604
 
static ETHR_INLINE void
1605
 
get_curr_time(long *sec, long *nsec)
1606
 
{
1607
 
    SYSTEMTIME t;
1608
 
    FILETIME ft;
1609
 
    LONGLONG lft;
1610
 
 
1611
 
    GetSystemTime(&t);
1612
 
    SystemTimeToFileTime(&t, &ft);
1613
 
    memcpy(&lft, &ft, sizeof(lft));
1614
 
    *nsec = ((long) (lft % LL_LITERAL(10000000)))*100;
1615
 
    *sec = (long) ((lft / LL_LITERAL(10000000)) - EPOCH_JULIAN_DIFF);
1616
 
}
1617
 
 
1618
 
static cnd_wait_event_ *cwe_freelist;
1619
 
static CRITICAL_SECTION cwe_cs;
1620
 
 
1621
 
static int
1622
 
alloc_cwe(cnd_wait_event_ **cwe_res)
1623
 
{
1624
 
    cnd_wait_event_ *cwe;
1625
 
    EnterCriticalSection(&cwe_cs);
1626
 
    cwe = cwe_freelist;
1627
 
    if (cwe) {
1628
 
        cwe_freelist = cwe->next;
1629
 
        LeaveCriticalSection(&cwe_cs);
1630
 
    }
1631
 
    else {
1632
 
        LeaveCriticalSection(&cwe_cs);
1633
 
        cwe = (*allocp)(sizeof(cnd_wait_event_));
1634
 
        if (!cwe)
1635
 
            return ENOMEM;
1636
 
        cwe->handle = CreateEvent(NULL, FALSE, FALSE, NULL);
1637
 
        if (cwe->handle == INVALID_HANDLE_VALUE) {
1638
 
            int res = get_errno();
1639
 
            (*freep)(cwe);
1640
 
            return res;
1641
 
        }
1642
 
    }
1643
 
    *cwe_res = cwe;
1644
 
    return 0;
1645
 
}
1646
 
 
1647
 
static
1648
 
free_cwe(cnd_wait_event_ *cwe)
1649
 
{
1650
 
    EnterCriticalSection(&cwe_cs);
1651
 
    cwe->next = cwe_freelist;
1652
 
    cwe_freelist = cwe;
1653
 
    LeaveCriticalSection(&cwe_cs);
1654
 
}
1655
 
 
1656
 
static ETHR_INLINE int
1657
 
condwait(ethr_cond *cnd,
1658
 
         ethr_mutex *mtx,
1659
 
         int with_timeout,
1660
 
         ethr_timeval *timeout)
1661
 
{
1662
 
    int res;
1663
 
    thr_data_ *td;
1664
 
    cnd_wait_event_ *cwe;
1665
 
    DWORD code;
1666
 
    long time; /* time until timeout in milli seconds */
1667
 
 
1668
 
#if ETHR_XCHK
1669
 
    if (ethr_not_inited) {
1670
 
        ASSERT(0);
1671
 
        return EACCES;
1672
 
    }
1673
 
 
1674
 
    if (!mtx
1675
 
        || mtx->initialized != ETHR_MUTEX_INITIALIZED
1676
 
        || !cnd
1677
 
        || (cnd->initialized && cnd->initialized != ETHR_COND_INITIALIZED)
1678
 
        || (with_timeout && !timeout)) {
1679
 
        ASSERT(0);
1680
 
        return EINVAL;
1681
 
    }
1682
 
#endif
1683
 
 
1684
 
    td = OWN_THR_DATA;
1685
 
    if (td)
1686
 
        cwe = &td->wait_event;
1687
 
    else { /* A non-ethread thread */
1688
 
        res = alloc_cwe(&cwe);
1689
 
        if (res != 0)
1690
 
            return res;
1691
 
    }
1692
 
 
1693
 
    if (!cnd->initialized)
1694
 
        fake_static_cond_init(cnd);
1695
 
    EnterCriticalSection(&cnd->cs);
1696
 
 
1697
 
    ASSERT(!cwe->in_queue);
1698
 
    if (cnd->queue_end) {
1699
 
        ASSERT(cnd->queue);
1700
 
        cwe->prev = cnd->queue_end;
1701
 
        cwe->next = NULL;
1702
 
        cnd->queue_end->next = cwe;
1703
 
        cnd->queue_end = cwe;
1704
 
    }
1705
 
    else {
1706
 
        ASSERT(!cnd->queue);
1707
 
        cwe->prev = NULL;
1708
 
        cwe->next = NULL;
1709
 
        cnd->queue = cwe;
1710
 
        cnd->queue_end = cwe;
1711
 
    }
1712
 
    cwe->in_queue = 1;
1713
 
 
1714
 
    LeaveCriticalSection(&cnd->cs);
1715
 
 
1716
 
    LeaveCriticalSection(&mtx->cs);
1717
 
 
1718
 
    if (!with_timeout)
1719
 
        time = INFINITE;
1720
 
    else {
1721
 
        long sec, nsec;
1722
 
        ASSERT(timeout);
1723
 
        get_curr_time(&sec, &nsec);
1724
 
        time = (timeout->tv_sec - sec)*1000;
1725
 
        time += (timeout->tv_nsec - nsec + 500)/1000000;
1726
 
        if (time < 0)
1727
 
            time = 0;
1728
 
    }
1729
 
 
1730
 
    /* wait for event to signal */
1731
 
    code = WaitForSingleObject(cwe->handle, time);
1732
 
 
1733
 
    EnterCriticalSection(&mtx->cs);
1734
 
 
1735
 
    if (code == WAIT_OBJECT_0) {
1736
 
        /* We were woken by a signal or a broadcast ... */
1737
 
        res = 0;
1738
 
 
1739
 
        /* ... no need to remove event from wait queue since this was
1740
 
           taken care of by the signal or broadcast */
1741
 
#ifdef DEBUG
1742
 
        EnterCriticalSection(&cnd->cs);
1743
 
        ASSERT(!cwe->in_queue);
1744
 
        LeaveCriticalSection(&cnd->cs);
1745
 
#endif
1746
 
 
1747
 
    }
1748
 
    else {
1749
 
        /* We timed out... */
1750
 
        res = ETIMEDOUT;
1751
 
 
1752
 
        /* ... probably have to remove event from wait queue ... */
1753
 
        EnterCriticalSection(&cnd->cs);
1754
 
 
1755
 
        if (cwe->in_queue) { /* ... but we must check that we are in queue
1756
 
                                since a signal or broadcast after timeout
1757
 
                                may have removed us from the queue */
1758
 
            if (cwe->prev) {
1759
 
                cwe->prev->next = cwe->next;
1760
 
            }
1761
 
            else {
1762
 
                ASSERT(cnd->queue == cwe);
1763
 
                cnd->queue = cwe->next;
1764
 
            }
1765
 
 
1766
 
            if (cwe->next) {
1767
 
                cwe->next->prev = cwe->prev;
1768
 
            }
1769
 
            else {
1770
 
                ASSERT(cnd->queue_end == cwe);
1771
 
                cnd->queue_end = cwe->prev;
1772
 
            }
1773
 
            cwe->in_queue = 0;
1774
 
        }
1775
 
 
1776
 
        LeaveCriticalSection(&cnd->cs);
1777
 
 
1778
 
    }
1779
 
 
1780
 
    if (!td)
1781
 
        free_cwe(cwe);
1782
 
 
1783
 
    return res;
1784
 
 
1785
 
}
1786
 
 
1787
 
 
1788
 
/*
1789
 
 * ----------------------------------------------------------------------------
1790
 
 * Exported functions
1791
 
 * ----------------------------------------------------------------------------
1792
 
 */
1793
 
 
1794
 
int
1795
 
ethr_init(ethr_init_data *id)
1796
 
{
1797
 
#ifdef _WIN32_WINNT
1798
 
    DWORD major = (_WIN32_WINNT >> 8) & 0xff;
1799
 
    DWORD minor = _WIN32_WINNT & 0xff;
1800
 
    OSVERSIONINFO os_version;
1801
 
#endif
1802
 
    int err = 0;
1803
 
    thr_data_ *td = &main_thr_data;
1804
 
    unsigned long i;
1805
 
 
1806
 
    if (!ethr_not_inited)
1807
 
        return EINVAL;
1808
 
 
1809
 
#ifdef _WIN32_WINNT
1810
 
    os_version.dwOSVersionInfoSize = sizeof(OSVERSIONINFO);
1811
 
    GetVersionEx(&os_version);
1812
 
    if (os_version.dwPlatformId != VER_PLATFORM_WIN32_NT
1813
 
        || os_version.dwMajorVersion < major
1814
 
        || (os_version.dwMajorVersion == major
1815
 
            && os_version.dwMinorVersion < minor))
1816
 
        return ENOTSUP;
1817
 
#endif
1818
 
 
1819
 
    ASSERT(ETHR_MAX_THREADS > 0);
1820
 
    for (i = ETHR_MAX_THREADS - 1, serial_shift = 0;
1821
 
         i;
1822
 
         serial_shift++, i >>= 1);
1823
 
    thr_ix_mask = ~(~((ethr_tid) 0) << serial_shift);
1824
 
 
1825
 
    tls_own_thr_data = TlsAlloc();
1826
 
    if (tls_own_thr_data == TLS_OUT_OF_INDEXES)
1827
 
        goto error;
1828
 
 
1829
 
    last_serial = 0;
1830
 
    last_ix = 0;
1831
 
 
1832
 
    td->thr_id = 0;
1833
 
    td->thr_handle = GetCurrentThread();
1834
 
    td->joiner = INVALID_TID;
1835
 
    td->result = NULL;
1836
 
    td->wait_event.handle = CreateEvent(NULL, FALSE, FALSE, NULL);
1837
 
    if (td->wait_event.handle == INVALID_HANDLE_VALUE)
1838
 
        goto error;
1839
 
    td->wait_event.prev = NULL;
1840
 
    td->wait_event.next = NULL;
1841
 
    td->wait_event.in_queue = 0;
1842
 
    thr_table[0] = td;
1843
 
 
1844
 
    if (!TlsSetValue(tls_own_thr_data, (LPVOID) td))
1845
 
        goto error;
1846
 
 
1847
 
    ASSERT(td == OWN_THR_DATA);
1848
 
 
1849
 
 
1850
 
    cwe_freelist = NULL;
1851
 
    if (!InitializeCriticalSectionAndSpinCount(&cwe_cs,
1852
 
                                               ETHR_MUTEX_SPIN_COUNT))
1853
 
        goto error;
1854
 
 
1855
 
    for (i = 1; i < ETHR_MAX_THREADS; i++)
1856
 
        thr_table[i] = NULL;
1857
 
 
1858
 
    if (!InitializeCriticalSectionAndSpinCount(&thr_table_cs,
1859
 
                                               ETHR_MUTEX_SPIN_COUNT))
1860
 
        goto error;
1861
 
    if (!InitializeCriticalSectionAndSpinCount(&fake_static_init_cs,
1862
 
                                               ETHR_MUTEX_SPIN_COUNT))
1863
 
        goto error;
1864
 
    ethr_not_inited = 0;
1865
 
 
1866
 
    err = init_common(id);
1867
 
    if (err)
1868
 
        goto error;
1869
 
 
1870
 
    return 0;
1871
 
 
1872
 
 error:
1873
 
    ethr_not_inited = 1;
1874
 
    if (err == 0)
1875
 
        err = get_errno();
1876
 
    ASSERT(err != 0);
1877
 
    if (td->thr_handle != INVALID_HANDLE_VALUE)
1878
 
        CloseHandle(td->thr_handle);
1879
 
    if (td->wait_event.handle != INVALID_HANDLE_VALUE)
1880
 
        CloseHandle(td->wait_event.handle);
1881
 
    return err;
1882
 
}
1883
 
 
1884
 
/*
1885
 
 * Thread functions.
1886
 
 */
1887
 
 
1888
 
int
1889
 
ethr_thr_create(ethr_tid *tid, void * (*func)(void *), void *arg,
1890
 
                ethr_thr_opts *opts)
1891
 
{
1892
 
    int err = 0;
1893
 
    thr_wrap_data_ twd;
1894
 
    thr_data_ *my_td, *child_td = NULL;
1895
 
    ethr_tid child_tid, child_serial, child_ix;
1896
 
    DWORD code;
1897
 
    unsigned ID;
1898
 
    unsigned stack_size = 0; /* 0 = system default */
1899
 
    int use_stack_size = (opts && opts->suggested_stack_size >= 0
1900
 
                          ? opts->suggested_stack_size
1901
 
                          : -1 /* Use system default */);
1902
 
 
1903
 
#ifdef ETHR_MODIFIED_DEFAULT_STACK_SIZE
1904
 
    if (use_stack_size < 0)
1905
 
        use_stack_size = ETHR_MODIFIED_DEFAULT_STACK_SIZE;
1906
 
#endif
1907
 
 
1908
 
#if ETHR_XCHK
1909
 
    if (ethr_not_inited) {
1910
 
        ASSERT(0);
1911
 
        return EACCES;
1912
 
    }
1913
 
    if (!tid || !func) {
1914
 
        ASSERT(0);
1915
 
        return EINVAL;
1916
 
    }
1917
 
#endif
1918
 
 
1919
 
    my_td = OWN_THR_DATA;
1920
 
    if (!my_td) {
1921
 
        /* Only ethreads are allowed to call this function */
1922
 
        ASSERT(0);
1923
 
        return EACCES;
1924
 
    }
1925
 
 
1926
 
    if (use_stack_size >= 0) {
1927
 
        size_t suggested_stack_size = (size_t) use_stack_size;
1928
 
#ifdef DEBUG
1929
 
        suggested_stack_size /= 2; /* Make sure we got margin */
1930
 
#endif
1931
 
        if (suggested_stack_size < min_stack_size)
1932
 
            stack_size = (unsigned) ETHR_KW2B(min_stack_size);
1933
 
        else if (suggested_stack_size > max_stack_size)
1934
 
            stack_size = (unsigned) ETHR_KW2B(max_stack_size);
1935
 
        else
1936
 
            stack_size =
1937
 
                (unsigned) ETHR_PAGE_ALIGN(ETHR_KW2B(suggested_stack_size));
1938
 
    }
1939
 
 
1940
 
    EnterCriticalSection(&thr_table_cs);
1941
 
 
1942
 
    /* Call prepare func if it exist */
1943
 
    if (thread_create_prepare_func)
1944
 
        twd.prep_func_res = (*thread_create_prepare_func)();
1945
 
    else
1946
 
        twd.prep_func_res = NULL;
1947
 
 
1948
 
    /* Find a new thread id to use */
1949
 
    new_tid(&child_tid, &child_serial, &child_ix);
1950
 
    if (child_tid == INVALID_TID) {
1951
 
        err = EAGAIN;
1952
 
        goto error;
1953
 
    }
1954
 
 
1955
 
    ASSERT(child_ix == THR_IX(child_tid));
1956
 
 
1957
 
    *tid = child_tid;
1958
 
 
1959
 
    ASSERT(!thr_table[child_ix]);
1960
 
 
1961
 
    /* Alloc thread data */
1962
 
    thr_table[child_ix] = child_td = (thr_data_ *) (*allocp)(sizeof(thr_data_));
1963
 
    if (!child_td) {
1964
 
        err = ENOMEM;
1965
 
        goto error;
1966
 
    }
1967
 
 
1968
 
    /* Init thread data */
1969
 
 
1970
 
    child_td->thr_id            = child_tid;
1971
 
    child_td->thr_handle        = INVALID_HANDLE_VALUE;
1972
 
    child_td->joiner            = INVALID_TID;
1973
 
    child_td->result            = NULL;
1974
 
    /* 'child_td->wait_event' is initialized by child thread */
1975
 
 
1976
 
 
1977
 
    /* Init thread wrapper data */
1978
 
 
1979
 
    twd.func                    = func;
1980
 
    twd.arg                     = arg;
1981
 
    twd.ptd                     = my_td;
1982
 
    twd.td                      = child_td;
1983
 
    twd.res                     = 0;
1984
 
 
1985
 
    ASSERT(!my_td->wait_event.in_queue);
1986
 
 
1987
 
    /* spawn the thr_wrapper function */
1988
 
    child_td->thr_handle = (HANDLE) _beginthreadex(NULL,
1989
 
                                                   stack_size,
1990
 
                                                   thr_wrapper,
1991
 
                                                   (LPVOID) &twd,
1992
 
                                                   0,
1993
 
                                                   &ID);
1994
 
    if (child_td->thr_handle == (HANDLE) 0) {
1995
 
        child_td->thr_handle = INVALID_HANDLE_VALUE;
1996
 
        goto error;
1997
 
    }
1998
 
 
1999
 
    ASSERT(child_td->thr_handle != INVALID_HANDLE_VALUE);
2000
 
 
2001
 
    /* Wait for child to finish initialization */
2002
 
    code = WaitForSingleObject(my_td->wait_event.handle, INFINITE);
2003
 
    if (twd.res || code != WAIT_OBJECT_0) {
2004
 
        err = twd.res;
2005
 
        goto error;
2006
 
    }
2007
 
 
2008
 
    if (opts && opts->detached) {
2009
 
        CloseHandle(child_td->thr_handle);
2010
 
        child_td->thr_handle = INVALID_HANDLE_VALUE;
2011
 
    }
2012
 
 
2013
 
    last_serial = child_serial;
2014
 
    last_ix     = child_ix;
2015
 
 
2016
 
    ASSERT(thr_table[child_ix] == child_td);
2017
 
 
2018
 
    if (thread_create_parent_func)
2019
 
        (*thread_create_parent_func)(twd.prep_func_res);
2020
 
 
2021
 
    LeaveCriticalSection(&thr_table_cs);
2022
 
 
2023
 
    return 0;
2024
 
 
2025
 
 error:
2026
 
 
2027
 
    if (err == 0)
2028
 
        err = get_errno();
2029
 
    ASSERT(err != 0);
2030
 
 
2031
 
    if (thread_create_parent_func)
2032
 
        (*thread_create_parent_func)(twd.prep_func_res);
2033
 
 
2034
 
    if (child_ix != INVALID_TID) {
2035
 
 
2036
 
        if (child_td) {
2037
 
            ASSERT(thr_table[child_ix] == child_td);
2038
 
 
2039
 
            if (child_td->thr_handle != INVALID_HANDLE_VALUE) {
2040
 
                WaitForSingleObject(child_td->thr_handle, INFINITE);
2041
 
                CloseHandle(child_td->thr_handle);
2042
 
            }
2043
 
 
2044
 
            (*freep)((void *) child_td);
2045
 
            thr_table[child_ix] = NULL;
2046
 
        }
2047
 
    }
2048
 
 
2049
 
    *tid = INVALID_TID;
2050
 
 
2051
 
    LeaveCriticalSection(&thr_table_cs);
2052
 
    return err;
2053
 
}
2054
 
 
2055
 
int ethr_thr_join(ethr_tid tid, void **res)
2056
 
{
2057
 
    int err = 0;
2058
 
    DWORD code;
2059
 
    thr_data_ *td;
2060
 
    thr_data_ *my_td;
2061
 
 
2062
 
#if ETHR_XCHK 
2063
 
    if (ethr_not_inited) {
2064
 
        ASSERT(0);
2065
 
        return EACCES;
2066
 
    }
2067
 
#endif
2068
 
 
2069
 
    my_td = OWN_THR_DATA;
2070
 
 
2071
 
    if (!my_td) {
2072
 
        /* Only ethreads are allowed to call this function */
2073
 
        ASSERT(0);
2074
 
        return EACCES;
2075
 
    }
2076
 
 
2077
 
    EnterCriticalSection(&thr_table_cs);
2078
 
 
2079
 
    td = tid2thr(tid);
2080
 
    if (!td)
2081
 
        err = ESRCH;
2082
 
    else if (td->thr_handle == INVALID_HANDLE_VALUE /* i.e. detached */
2083
 
             || td->joiner != INVALID_TID) /* i.e. someone else is joining */
2084
 
        err = EINVAL;
2085
 
    else if (my_td == td)
2086
 
        err = EDEADLK;
2087
 
    else
2088
 
        td->joiner = my_td->thr_id;
2089
 
 
2090
 
    LeaveCriticalSection(&thr_table_cs);
2091
 
 
2092
 
    if (err)
2093
 
        goto error;
2094
 
 
2095
 
    /* Wait for thread to terminate */
2096
 
    code = WaitForSingleObject(td->thr_handle, INFINITE);
2097
 
    if (code != WAIT_OBJECT_0)
2098
 
        goto error;
2099
 
 
2100
 
    EnterCriticalSection(&thr_table_cs);
2101
 
 
2102
 
    ASSERT(td == tid2thr(tid));
2103
 
    ASSERT(td->thr_handle != INVALID_HANDLE_VALUE);
2104
 
    ASSERT(td->joiner == my_td->thr_id);
2105
 
 
2106
 
    if (res)
2107
 
        *res = td->result;
2108
 
 
2109
 
    CloseHandle(td->thr_handle);
2110
 
    ASSERT(td == thr_table[THR_IX(td->thr_id)]);
2111
 
    thr_table[THR_IX(td->thr_id)] = NULL;
2112
 
    if (td != &main_thr_data)
2113
 
        (*freep)((void *) td);
2114
 
 
2115
 
    LeaveCriticalSection(&thr_table_cs);
2116
 
 
2117
 
    return 0;
2118
 
 
2119
 
 error:
2120
 
    if (err == 0)
2121
 
        err = get_errno();
2122
 
    ASSERT(err != 0);
2123
 
    return err;
2124
 
}
2125
 
 
2126
 
 
2127
 
int
2128
 
ethr_thr_detach(ethr_tid tid)
2129
 
{
2130
 
    int res;
2131
 
    DWORD code;
2132
 
    thr_data_ *td;
2133
 
 
2134
 
#if ETHR_XCHK 
2135
 
    if (ethr_not_inited) {
2136
 
        ASSERT(0);
2137
 
        return EACCES;
2138
 
    }
2139
 
#endif
2140
 
 
2141
 
    if (!OWN_THR_DATA) {
2142
 
        /* Only ethreads are allowed to call this function */
2143
 
        ASSERT(0);
2144
 
        return EACCES;
2145
 
    }
2146
 
 
2147
 
    EnterCriticalSection(&thr_table_cs);
2148
 
 
2149
 
    td = tid2thr(tid);
2150
 
    if (!td)
2151
 
        res = ESRCH;
2152
 
    if (td->thr_handle == INVALID_HANDLE_VALUE /* i.e. detached */
2153
 
        || td->joiner != INVALID_TID) /* i.e. someone is joining */
2154
 
        res = EINVAL;
2155
 
    else {
2156
 
        res = 0;
2157
 
        CloseHandle(td->thr_handle);
2158
 
        td->thr_handle = INVALID_HANDLE_VALUE;
2159
 
    }
2160
 
 
2161
 
    LeaveCriticalSection(&thr_table_cs);
2162
 
 
2163
 
    return res;
2164
 
}
2165
 
 
2166
 
 
2167
 
void
2168
 
ethr_thr_exit(void *res)
2169
 
{
2170
 
    thr_data_ *td;
2171
 
#if ETHR_XCHK
2172
 
    if (ethr_not_inited) {
2173
 
        ASSERT(0);
2174
 
        return;
2175
 
    }
2176
 
#endif
2177
 
    td = OWN_THR_DATA;
2178
 
    if (!td) {
2179
 
        /* Only ethreads are allowed to call this function */
2180
 
        ASSERT(0);
2181
 
        return;
2182
 
    }
2183
 
    thr_exit_cleanup(td, res);
2184
 
    _endthreadex((unsigned) 0);
2185
 
}
2186
 
 
2187
 
ethr_tid
2188
 
ethr_self(void)
2189
 
{
2190
 
    thr_data_ *td;
2191
 
#if ETHR_XCHK
2192
 
    if (ethr_not_inited) {
2193
 
        ASSERT(0);
2194
 
        return INVALID_TID;
2195
 
    }
2196
 
#endif
2197
 
    /* It is okay for non-ethreads (i.e. native win32 threads) to call
2198
 
       ethr_self(). They will however be returned the INVALID_TID. */
2199
 
    td = OWN_THR_DATA;
2200
 
    if (!td)
2201
 
        return INVALID_TID;
2202
 
    return td->thr_id;
2203
 
}
2204
 
 
2205
 
int
2206
 
ethr_equal_tids(ethr_tid tid1, ethr_tid tid2)
2207
 
{
2208
 
    /* INVALID_TID does not equal any tid, not even the INVALID_TID */
2209
 
    return tid1 == tid2 && tid1 != INVALID_TID;
2210
 
}
2211
 
 
2212
 
/*
2213
 
 * Mutex functions.
2214
 
 */
2215
 
 
2216
 
int
2217
 
ethr_mutex_init(ethr_mutex *mtx)
2218
 
{
2219
 
#if ETHR_XCHK 
2220
 
    if (ethr_not_inited) {
2221
 
        ASSERT(0);
2222
 
        return EACCES;
2223
 
    }
2224
 
    if (!mtx) {
2225
 
        ASSERT(0);
2226
 
        return EINVAL;
2227
 
    }
2228
 
#endif
2229
 
    if (!InitializeCriticalSectionAndSpinCount(&mtx->cs, ETHR_MUTEX_SPIN_COUNT))
2230
 
        return get_errno();
2231
 
    mtx->initialized = ETHR_MUTEX_INITIALIZED;
2232
 
#if ETHR_XCHK
2233
 
    mtx->is_rec_mtx = 0;
2234
 
#endif
2235
 
    return 0;
2236
 
}
2237
 
 
2238
 
int
2239
 
ethr_rec_mutex_init(ethr_mutex *mtx)
2240
 
{
2241
 
    int res;
2242
 
    res = ethr_mutex_init(mtx);
2243
 
#if ETHR_XCHK
2244
 
    mtx->is_rec_mtx = 1;
2245
 
#endif
2246
 
    return res;
2247
 
}
2248
 
 
2249
 
int
2250
 
ethr_mutex_destroy(ethr_mutex *mtx)
2251
 
{
2252
 
#if ETHR_XCHK 
2253
 
    if (ethr_not_inited) {
2254
 
        ASSERT(0);
2255
 
        return EACCES;
2256
 
    }
2257
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
2258
 
        ASSERT(0);
2259
 
        return EINVAL;
2260
 
    }
2261
 
#endif
2262
 
    DeleteCriticalSection(&mtx->cs);
2263
 
    mtx->initialized = 0;
2264
 
    return 0;
2265
 
}
2266
 
 
2267
 
int ethr_mutex_set_forksafe(ethr_mutex *mtx)
2268
 
{
2269
 
#if ETHR_XCHK 
2270
 
    if (ethr_not_inited) {
2271
 
        ASSERT(0);
2272
 
        return EACCES;
2273
 
    }
2274
 
#endif
2275
 
    return 0; /* No fork() */
2276
 
}
2277
 
 
2278
 
int ethr_mutex_unset_forksafe(ethr_mutex *mtx)
2279
 
{
2280
 
#if ETHR_XCHK 
2281
 
    if (ethr_not_inited) {
2282
 
        ASSERT(0);
2283
 
        return EACCES;
2284
 
    }
2285
 
#endif
2286
 
    return 0; /* No fork() */
2287
 
}
2288
 
 
2289
 
int
2290
 
ethr_mutex_trylock(ethr_mutex *mtx)
2291
 
{
2292
 
#if ETHR_XCHK
2293
 
    if (ethr_not_inited) {
2294
 
        ASSERT(0);
2295
 
        return EACCES;
2296
 
    }
2297
 
    if (!mtx
2298
 
        || (mtx->initialized && mtx->initialized != ETHR_MUTEX_INITIALIZED)) {
2299
 
        ASSERT(0);
2300
 
        return EINVAL;
2301
 
    }
2302
 
#endif
2303
 
    if (!mtx->initialized) {
2304
 
        int res = ethr_fake_static_mutex_init(mtx);
2305
 
        if (res != 0)
2306
 
            return res;
2307
 
    }
2308
 
    return ethr_mutex_trylock__(mtx);
2309
 
}
2310
 
 
2311
 
int
2312
 
ethr_mutex_lock(ethr_mutex *mtx)
2313
 
{
2314
 
    int res;
2315
 
#if ETHR_XCHK
2316
 
    if (ethr_not_inited) {
2317
 
        ASSERT(0);
2318
 
        return EACCES;
2319
 
    }
2320
 
    if (!mtx
2321
 
        || (mtx->initialized && mtx->initialized != ETHR_MUTEX_INITIALIZED)) {
2322
 
        ASSERT(0);
2323
 
        return EINVAL;
2324
 
    }
2325
 
#endif
2326
 
    return ethr_mutex_lock__(mtx);
2327
 
}
2328
 
 
2329
 
int
2330
 
ethr_mutex_unlock(ethr_mutex *mtx)
2331
 
{
2332
 
#if ETHR_XCHK
2333
 
    int res;
2334
 
    if (ethr_not_inited) {
2335
 
        ASSERT(0);
2336
 
        return EACCES;
2337
 
    }
2338
 
    if (!mtx || mtx->initialized != ETHR_MUTEX_INITIALIZED) {
2339
 
        ASSERT(0);
2340
 
        return EINVAL;
2341
 
    }
2342
 
#endif
2343
 
    return ethr_mutex_unlock__(mtx);
2344
 
}
2345
 
 
2346
 
/*
2347
 
 * Condition variable functions.
2348
 
 */
2349
 
 
2350
 
int
2351
 
ethr_cond_init(ethr_cond *cnd)
2352
 
{
2353
 
#if ETHR_XCHK 
2354
 
    if (ethr_not_inited) {
2355
 
        ASSERT(0);
2356
 
        return EACCES;
2357
 
    }
2358
 
    if (!cnd) {
2359
 
        ASSERT(0);
2360
 
        return EINVAL;
2361
 
    }
2362
 
#endif
2363
 
    if (!InitializeCriticalSectionAndSpinCount(&cnd->cs, ETHR_COND_SPIN_COUNT))
2364
 
        return get_errno();
2365
 
    cnd->queue = NULL;
2366
 
    cnd->queue_end = NULL;
2367
 
    cnd->initialized = ETHR_COND_INITIALIZED;
2368
 
    return 0;
2369
 
}
2370
 
 
2371
 
int
2372
 
ethr_cond_destroy(ethr_cond *cnd)
2373
 
{
2374
 
#if ETHR_XCHK 
2375
 
    if (ethr_not_inited) {
2376
 
        ASSERT(0);
2377
 
        return EACCES;
2378
 
    }
2379
 
    if (!cnd
2380
 
        || (cnd->initialized && cnd->initialized != ETHR_COND_INITIALIZED)
2381
 
        || cnd->queue) {
2382
 
        ASSERT(0);
2383
 
        return EINVAL;
2384
 
    }
2385
 
#endif
2386
 
    DeleteCriticalSection(&cnd->cs);
2387
 
    cnd->initialized = 0;
2388
 
    return 0;
2389
 
}
2390
 
 
2391
 
int
2392
 
ethr_cond_signal(ethr_cond *cnd)
2393
 
{
2394
 
    cnd_wait_event_ *cwe;
2395
 
#if ETHR_XCHK 
2396
 
    if (ethr_not_inited) {
2397
 
        ASSERT(0);
2398
 
        return EACCES;
2399
 
    }
2400
 
    if (!cnd
2401
 
        || (cnd->initialized && cnd->initialized != ETHR_COND_INITIALIZED)) {
2402
 
        ASSERT(0);
2403
 
        return EINVAL;
2404
 
    }
2405
 
#endif
2406
 
    if (!cnd->initialized) {
2407
 
        int res = fake_static_cond_init(cnd);
2408
 
        if (res != 0)
2409
 
            return res;
2410
 
    }
2411
 
    EnterCriticalSection(&cnd->cs);
2412
 
    cwe = cnd->queue;
2413
 
    if (cwe) {
2414
 
        ASSERT(cwe->in_queue);
2415
 
        SetEvent(cnd->queue->handle);
2416
 
        if (cwe->next)
2417
 
            cwe->next->prev = NULL;
2418
 
        else {
2419
 
            ASSERT(cnd->queue_end == cnd->queue);
2420
 
            cnd->queue_end = NULL;
2421
 
        }
2422
 
        cnd->queue = cwe->next;
2423
 
        cwe->in_queue = 0;
2424
 
    }
2425
 
    LeaveCriticalSection(&cnd->cs);
2426
 
    return 0;
2427
 
}
2428
 
 
2429
 
int
2430
 
ethr_cond_broadcast(ethr_cond *cnd)
2431
 
{
2432
 
    cnd_wait_event_ *cwe;
2433
 
 
2434
 
#if ETHR_XCHK 
2435
 
    if (ethr_not_inited) {
2436
 
        ASSERT(0);
2437
 
        return EACCES;
2438
 
    }
2439
 
    if (!cnd
2440
 
        || (cnd->initialized && cnd->initialized != ETHR_COND_INITIALIZED)) {
2441
 
        ASSERT(0);
2442
 
        return EINVAL;
2443
 
    }
2444
 
#endif
2445
 
    if (!cnd->initialized) {
2446
 
        int res = fake_static_cond_init(cnd);
2447
 
        if (res != 0)
2448
 
            return res;
2449
 
    }
2450
 
    EnterCriticalSection(&cnd->cs);
2451
 
    for (cwe = cnd->queue; cwe; cwe = cwe->next) {
2452
 
        ASSERT(cwe->in_queue);
2453
 
        SetEvent(cwe->handle);
2454
 
        cwe->in_queue = 0;
2455
 
    }
2456
 
    cnd->queue = NULL;
2457
 
    cnd->queue_end = NULL;
2458
 
    LeaveCriticalSection(&cnd->cs);
2459
 
    return 0;
2460
 
 
2461
 
}
2462
 
 
2463
 
int
2464
 
ethr_cond_wait(ethr_cond *cnd, ethr_mutex *mtx)
2465
 
{
2466
 
    return condwait(cnd, mtx, 0, NULL);
2467
 
}
2468
 
 
2469
 
int
2470
 
ethr_cond_timedwait(ethr_cond *cnd, ethr_mutex *mtx, ethr_timeval *timeout)
2471
 
{
2472
 
    return condwait(cnd, mtx, 1, timeout);
2473
 
}
2474
 
 
2475
 
int
2476
 
ethr_time_now(ethr_timeval *time)
2477
 
{
2478
 
#if ETHR_XCHK 
2479
 
    if (ethr_not_inited) {
2480
 
        ASSERT(0);
2481
 
        return EACCES;
2482
 
    }
2483
 
    if (!time) {
2484
 
        ASSERT(0);
2485
 
        return EINVAL;
2486
 
    }
2487
 
#endif
2488
 
    get_curr_time(&time->tv_sec, &time->tv_nsec);
2489
 
    return 0;
2490
 
}
2491
 
 
2492
 
/*
2493
 
 * Thread specific data
2494
 
 */
2495
 
 
2496
 
int
2497
 
ethr_tsd_key_create(ethr_tsd_key *keyp)
2498
 
{
2499
 
    DWORD key;
2500
 
#if ETHR_XCHK
2501
 
    if (ethr_not_inited) {
2502
 
        ASSERT(0);
2503
 
        return EACCES;
2504
 
    }
2505
 
    if (!keyp) {
2506
 
        ASSERT(0);
2507
 
        return EINVAL;
2508
 
    }
2509
 
#endif
2510
 
    key = TlsAlloc();
2511
 
    if (key == TLS_OUT_OF_INDEXES)
2512
 
        return get_errno();
2513
 
    *keyp = (ethr_tsd_key) key;
2514
 
    return 0;
2515
 
}
2516
 
 
2517
 
int
2518
 
ethr_tsd_key_delete(ethr_tsd_key key)
2519
 
{
2520
 
#if ETHR_XCHK
2521
 
    if (ethr_not_inited) {
2522
 
        ASSERT(0);
2523
 
        return EACCES;
2524
 
    }
2525
 
#endif
2526
 
    if (!TlsFree((DWORD) key))
2527
 
        return get_errno();
2528
 
    return 0;
2529
 
}
2530
 
 
2531
 
int
2532
 
ethr_tsd_set(ethr_tsd_key key, void *value)
2533
 
{
2534
 
#if ETHR_XCHK
2535
 
    if (ethr_not_inited) {
2536
 
        ASSERT(0);
2537
 
        return EACCES;
2538
 
    }
2539
 
#endif
2540
 
    if (!TlsSetValue((DWORD) key, (LPVOID) value))
2541
 
        return get_errno();
2542
 
    return 0;
2543
 
}
2544
 
 
2545
 
void *
2546
 
ethr_tsd_get(ethr_tsd_key key)
2547
 
{
2548
 
#if ETHR_XCHK
2549
 
    if (ethr_not_inited) {
2550
 
        ASSERT(0);
2551
 
        return NULL;
2552
 
    }
2553
 
#endif
2554
 
    return (void *) TlsGetValue((DWORD) key);
2555
 
}
2556
 
 
2557
 
/* Misc */
2558
 
 
2559
 
#ifndef ETHR_HAVE_OPTIMIZED_LOCKS
2560
 
 
2561
 
int
2562
 
ethr_do_spinlock_init(ethr_spinlock_t *lock)
2563
 
{
2564
 
#if ETHR_XCHK 
2565
 
    if (ethr_not_inited) {
2566
 
        ASSERT(0);
2567
 
        return EACCES;
2568
 
    }
2569
 
    if (!lock) {
2570
 
        ASSERT(0);
2571
 
        return EINVAL;
2572
 
    }
2573
 
#endif
2574
 
    if (InitializeCriticalSectionAndSpinCount(&lock->cs, INT_MAX))
2575
 
        return 0;
2576
 
    else
2577
 
        return get_errno();
2578
 
}
2579
 
 
2580
 
int
2581
 
ethr_do_rwlock_init(ethr_rwlock_t *lock)
2582
 
{
2583
 
#if ETHR_XCHK 
2584
 
    if (ethr_not_inited) {
2585
 
        ASSERT(0);
2586
 
        return EACCES;
2587
 
    }
2588
 
    if (!lock) {
2589
 
        ASSERT(0);
2590
 
        return EINVAL;
2591
 
    }
2592
 
#endif
2593
 
    lock->counter = 0;
2594
 
    if (InitializeCriticalSectionAndSpinCount(&lock->cs, INT_MAX))
2595
 
        return 0;
2596
 
    else
2597
 
        return get_errno();    
2598
 
}
2599
 
 
2600
 
#endif /* #ifndef ETHR_HAVE_OPTIMIZED_ATOMIC_OPS */
2601
 
 
2602
 
#else
2603
 
#error "Missing thread implementation"
2604
 
#endif
2605
 
 
2606
 
/* Atomics */
2607
 
 
2608
 
int
2609
 
ethr_atomic_init(ethr_atomic_t *var, long i)
2610
 
{
2611
 
#if ETHR_XCHK
2612
 
    if (ethr_not_inited) {
2613
 
       ASSERT(0);
2614
 
       return EACCES;
2615
 
    }  
2616
 
    if (!var) {
2617
 
       ASSERT(0);
2618
 
       return EINVAL;
2619
 
    }  
2620
 
#endif
2621
 
    return ethr_atomic_init__(var, i);
2622
 
}
2623
 
 
2624
 
int
2625
 
ethr_atomic_set(ethr_atomic_t *var, long i)
2626
 
{
2627
 
#if ETHR_XCHK
2628
 
    if (ethr_not_inited) {
2629
 
       ASSERT(0);
2630
 
       return EACCES;
2631
 
    }  
2632
 
    if (!var) {
2633
 
       ASSERT(0);
2634
 
       return EINVAL;
2635
 
    }  
2636
 
#endif
2637
 
    return ethr_atomic_set__(var, i);
2638
 
}
2639
 
 
2640
 
int
2641
 
ethr_atomic_read(ethr_atomic_t *var, long *i)
2642
 
{
2643
 
#if ETHR_XCHK
2644
 
    if (ethr_not_inited) {
2645
 
       ASSERT(0);
2646
 
       return EACCES;
2647
 
    }  
2648
 
    if (!var || !i) {
2649
 
       ASSERT(0);
2650
 
       return EINVAL;
2651
 
    }  
2652
 
#endif
2653
 
    return ethr_atomic_read__(var, i);
2654
 
}
2655
 
 
2656
 
 
2657
 
int
2658
 
ethr_atomic_addtest(ethr_atomic_t *var, long incr, long *testp)
2659
 
{
2660
 
#if ETHR_XCHK
2661
 
    if (ethr_not_inited) {
2662
 
       ASSERT(0);
2663
 
       return EACCES;
2664
 
    }  
2665
 
    if (!var || !testp) {
2666
 
       ASSERT(0);
2667
 
       return EINVAL;
2668
 
    }  
2669
 
#endif
2670
 
    return ethr_atomic_addtest__(var, incr, testp);
2671
 
}   
2672
 
    
2673
 
int
2674
 
ethr_atomic_inctest(ethr_atomic_t *incp, long *testp)
2675
 
{
2676
 
#if ETHR_XCHK
2677
 
    if (ethr_not_inited) {
2678
 
        ASSERT(0);
2679
 
        return EACCES;
2680
 
    }
2681
 
    if (!incp || !testp) {
2682
 
        ASSERT(0);
2683
 
        return EINVAL;
2684
 
    }
2685
 
#endif
2686
 
    return ethr_atomic_inctest__(incp, testp);
2687
 
}
2688
 
 
2689
 
int
2690
 
ethr_atomic_dectest(ethr_atomic_t *decp, long *testp)
2691
 
{
2692
 
#if ETHR_XCHK
2693
 
    if (ethr_not_inited) {
2694
 
        ASSERT(0);
2695
 
        return EACCES;
2696
 
    }
2697
 
    if (!decp || !testp) {
2698
 
        ASSERT(0);
2699
 
        return EINVAL;
2700
 
    }
2701
 
#endif
2702
 
    return ethr_atomic_dectest__(decp, testp);
2703
 
}
2704
 
 
2705
 
int
2706
 
ethr_atomic_add(ethr_atomic_t *var, long incr)
2707
 
{
2708
 
#if ETHR_XCHK
2709
 
    if (ethr_not_inited) {
2710
 
       ASSERT(0);
2711
 
       return EACCES;
2712
 
    }  
2713
 
    if (!var) {
2714
 
       ASSERT(0);
2715
 
       return EINVAL;
2716
 
    }  
2717
 
#endif
2718
 
    return ethr_atomic_add__(var, incr);
2719
 
}   
2720
 
    
2721
 
int 
2722
 
ethr_atomic_inc(ethr_atomic_t *incp)
2723
 
{
2724
 
#if ETHR_XCHK
2725
 
    if (ethr_not_inited) {
2726
 
        ASSERT(0);
2727
 
        return EACCES;
2728
 
    }
2729
 
    if (!incp) {
2730
 
        ASSERT(0);
2731
 
        return EINVAL;
2732
 
    }
2733
 
#endif
2734
 
    return ethr_atomic_inc__(incp);
2735
 
}
2736
 
 
2737
 
int
2738
 
ethr_atomic_dec(ethr_atomic_t *decp)
2739
 
{
2740
 
#if ETHR_XCHK
2741
 
    if (ethr_not_inited) {
2742
 
        ASSERT(0);
2743
 
        return EACCES;
2744
 
    }
2745
 
    if (!decp) {
2746
 
        ASSERT(0);
2747
 
        return EINVAL;
2748
 
    }
2749
 
#endif
2750
 
    return ethr_atomic_dec__(decp);
2751
 
}
2752
 
 
2753
 
int
2754
 
ethr_atomic_and_old(ethr_atomic_t *var, long mask, long *old)
2755
 
{
2756
 
#if ETHR_XCHK
2757
 
    if (ethr_not_inited) {
2758
 
        ASSERT(0);
2759
 
        return EACCES;
2760
 
    }
2761
 
    if (!var || !old) {
2762
 
        ASSERT(0);
2763
 
        return EINVAL;
2764
 
    }
2765
 
#endif
2766
 
    return ethr_atomic_and_old__(var, mask, old);
2767
 
}
2768
 
 
2769
 
int
2770
 
ethr_atomic_or_old(ethr_atomic_t *var, long mask, long *old)
2771
 
{
2772
 
#if ETHR_XCHK
2773
 
    if (ethr_not_inited) {
2774
 
        ASSERT(0);
2775
 
        return EACCES;
2776
 
    }
2777
 
    if (!var || !old) {
2778
 
        ASSERT(0);
2779
 
        return EINVAL;
2780
 
    }
2781
 
#endif
2782
 
    return ethr_atomic_or_old__(var, mask, old);
2783
 
}
2784
 
 
2785
 
int
2786
 
ethr_atomic_xchg(ethr_atomic_t *var, long new, long *old)
2787
 
{
2788
 
#if ETHR_XCHK 
2789
 
    if (ethr_not_inited) {
2790
 
        ASSERT(0);
2791
 
        return EACCES;
2792
 
    }  
2793
 
    if (!var || !old) {
2794
 
        ASSERT(0);
2795
 
        return EINVAL;
2796
 
    }  
2797
 
#endif
2798
 
    return ethr_atomic_xchg__(var, new, old);
2799
 
}   
2800
 
 
2801
 
int
2802
 
ethr_atomic_cmpxchg(ethr_atomic_t *var, long new, long expected, long *old)
2803
 
{
2804
 
#if ETHR_XCHK 
2805
 
    if (ethr_not_inited) {
2806
 
        ASSERT(0);
2807
 
        return EACCES;
2808
 
    }  
2809
 
    if (!var || !old) {
2810
 
        ASSERT(0);
2811
 
        return EINVAL;
2812
 
    }  
2813
 
#endif
2814
 
    return ethr_atomic_cmpxchg__(var, new, expected, old);
2815
 
}
2816
 
 
2817
 
/* Spinlocks and rwspinlocks */
2818
 
 
2819
 
int
2820
 
ethr_spinlock_init(ethr_spinlock_t *lock)
2821
 
{
2822
 
#if ETHR_XCHK 
2823
 
    if (ethr_not_inited) {
2824
 
        ASSERT(0);
2825
 
        return EACCES;
2826
 
    }
2827
 
    if (!lock) {
2828
 
        ASSERT(0);
2829
 
        return EINVAL;
2830
 
    }
2831
 
#endif
2832
 
    return ethr_spinlock_init__(lock);
2833
 
}
2834
 
 
2835
 
int
2836
 
ethr_spinlock_destroy(ethr_spinlock_t *lock)
2837
 
{
2838
 
#if ETHR_XCHK 
2839
 
    if (ethr_not_inited) {
2840
 
        ASSERT(0);
2841
 
        return EACCES;
2842
 
    }
2843
 
    if (!lock) {
2844
 
        ASSERT(0);
2845
 
        return EINVAL;
2846
 
    }
2847
 
#endif
2848
 
    return ethr_spinlock_destroy__(lock);
2849
 
}
2850
 
 
2851
 
 
2852
 
int
2853
 
ethr_spin_unlock(ethr_spinlock_t *lock)
2854
 
{
2855
 
#if ETHR_XCHK 
2856
 
    if (ethr_not_inited) {
2857
 
        ASSERT(0);
2858
 
        return EACCES;
2859
 
    }
2860
 
    if (!lock) {
2861
 
        ASSERT(0);
2862
 
        return EINVAL;
2863
 
    }
2864
 
#endif
2865
 
    return ethr_spin_unlock__(lock);
2866
 
}
2867
 
 
2868
 
int
2869
 
ethr_spin_lock(ethr_spinlock_t *lock)
2870
 
{
2871
 
#if ETHR_XCHK 
2872
 
    if (ethr_not_inited) {
2873
 
        ASSERT(0);
2874
 
        return EACCES;
2875
 
    }
2876
 
    if (!lock) {
2877
 
        ASSERT(0);
2878
 
        return EINVAL;
2879
 
    }
2880
 
#endif
2881
 
    return ethr_spin_lock__(lock);
2882
 
}
2883
 
 
2884
 
int
2885
 
ethr_rwlock_init(ethr_rwlock_t *lock)
2886
 
{
2887
 
#if ETHR_XCHK 
2888
 
    if (ethr_not_inited) {
2889
 
        ASSERT(0);
2890
 
        return EACCES;
2891
 
    }
2892
 
    if (!lock) {
2893
 
        ASSERT(0);
2894
 
        return EINVAL;
2895
 
    }
2896
 
#endif
2897
 
    return ethr_rwlock_init__(lock);
2898
 
}
2899
 
 
2900
 
int
2901
 
ethr_rwlock_destroy(ethr_rwlock_t *lock)
2902
 
{
2903
 
#if ETHR_XCHK 
2904
 
    if (ethr_not_inited) {
2905
 
        ASSERT(0);
2906
 
        return EACCES;
2907
 
    }
2908
 
    if (!lock) {
2909
 
        ASSERT(0);
2910
 
        return EINVAL;
2911
 
    }
2912
 
#endif
2913
 
    return ethr_rwlock_destroy__(lock);
2914
 
}
2915
 
 
2916
 
int
2917
 
ethr_read_unlock(ethr_rwlock_t *lock)
2918
 
{
2919
 
#if ETHR_XCHK 
2920
 
    if (ethr_not_inited) {
2921
 
        ASSERT(0);
2922
 
        return EACCES;
2923
 
    }
2924
 
    if (!lock) {
2925
 
        ASSERT(0);
2926
 
        return EINVAL;
2927
 
    }
2928
 
#endif
2929
 
    return ethr_read_unlock__(lock);
2930
 
}
2931
 
 
2932
 
int
2933
 
ethr_read_lock(ethr_rwlock_t *lock)
2934
 
{
2935
 
#if ETHR_XCHK 
2936
 
    if (ethr_not_inited) {
2937
 
        ASSERT(0);
2938
 
        return EACCES;
2939
 
    }
2940
 
    if (!lock) {
2941
 
        ASSERT(0);
2942
 
        return EINVAL;
2943
 
    }
2944
 
#endif
2945
 
    return ethr_read_lock__(lock);
2946
 
}
2947
 
 
2948
 
int
2949
 
ethr_write_unlock(ethr_rwlock_t *lock)
2950
 
{
2951
 
#if ETHR_XCHK 
2952
 
    if (ethr_not_inited) {
2953
 
        ASSERT(0);
2954
 
        return EACCES;
2955
 
    }
2956
 
    if (!lock) {
2957
 
        ASSERT(0);
2958
 
        return EINVAL;
2959
 
    }
2960
 
#endif
2961
 
    return ethr_write_unlock__(lock);
2962
 
}
2963
 
 
2964
 
int
2965
 
ethr_write_lock(ethr_rwlock_t *lock)
2966
 
{
2967
 
#if ETHR_XCHK 
2968
 
    if (ethr_not_inited) {
2969
 
        ASSERT(0);
2970
 
        return EACCES;
2971
 
    }
2972
 
    if (!lock) {
2973
 
        ASSERT(0);
2974
 
        return EINVAL;
2975
 
    }
2976
 
#endif
2977
 
    return ethr_write_lock__(lock);
2978
 
}
2979
 
 
2980
 
 
2981
 
int
2982
 
ethr_gate_init(ethr_gate *gp)
2983
 
{
2984
 
    int res;
2985
 
#if ETHR_XCHK 
2986
 
    if (ethr_not_inited) {
2987
 
        ASSERT(0);
2988
 
        return EACCES;
2989
 
    }
2990
 
    if (!gp) {
2991
 
        ASSERT(0);
2992
 
        return EINVAL;
2993
 
    }
2994
 
#endif
2995
 
    res = ethr_mutex_init(&gp->mtx);
2996
 
    if (res != 0)
2997
 
        return res;
2998
 
    res = ethr_cond_init(&gp->cnd);
2999
 
    if (res != 0) {
3000
 
        ethr_mutex_destroy(&gp->mtx);
3001
 
        return res;
3002
 
    }
3003
 
    gp->open = 0;
3004
 
    return 0;
3005
 
}
3006
 
 
3007
 
int
3008
 
ethr_gate_destroy(ethr_gate *gp)
3009
 
{
3010
 
    int res, dres;
3011
 
#if ETHR_XCHK 
3012
 
    if (ethr_not_inited) {
3013
 
        ASSERT(0);
3014
 
        return EACCES;
3015
 
    }
3016
 
    if (!gp) {
3017
 
        ASSERT(0);
3018
 
        return EINVAL;
3019
 
    }
3020
 
#endif
3021
 
    res = ethr_mutex_destroy(&gp->mtx);
3022
 
    dres = ethr_cond_destroy(&gp->cnd);
3023
 
    if (res == 0)
3024
 
        res = dres;
3025
 
    gp->open = 0;
3026
 
    return res;
3027
 
}
3028
 
 
3029
 
int
3030
 
ethr_gate_close(ethr_gate *gp)
3031
 
{
3032
 
    int res;
3033
 
#if ETHR_XCHK 
3034
 
    if (ethr_not_inited) {
3035
 
        ASSERT(0);
3036
 
        return EACCES;
3037
 
    }
3038
 
    if (!gp) {
3039
 
        ASSERT(0);
3040
 
        return EINVAL;
3041
 
    }
3042
 
#endif
3043
 
    res = ethr_mutex_lock__(&gp->mtx);
3044
 
    if (res != 0)
3045
 
        return res;
3046
 
    gp->open = 0;
3047
 
    res = ethr_mutex_unlock__(&gp->mtx);
3048
 
    return res;
3049
 
}
3050
 
 
3051
 
int
3052
 
ethr_gate_let_through(ethr_gate *gp, unsigned no)
3053
 
{
3054
 
    int res, ures;
3055
 
#if ETHR_XCHK 
3056
 
    if (ethr_not_inited) {
3057
 
        ASSERT(0);
3058
 
        return EACCES;
3059
 
    }
3060
 
    if (!gp) {
3061
 
        ASSERT(0);
3062
 
        return EINVAL;
3063
 
    }
3064
 
#endif
3065
 
    res = ethr_mutex_lock__(&gp->mtx);
3066
 
    if (res != 0)
3067
 
        return res;
3068
 
    gp->open += no;
3069
 
    res = (gp->open == 1
3070
 
           ? ethr_cond_signal(&gp->cnd)
3071
 
           : ethr_cond_broadcast(&gp->cnd));
3072
 
    ures = ethr_mutex_unlock__(&gp->mtx);
3073
 
    if (res != 0)
3074
 
        res = ures;
3075
 
    return res;
3076
 
}
3077
 
 
3078
 
int
3079
 
ethr_gate_swait(ethr_gate *gp, int spincount)
3080
 
{
3081
 
    int res, ures, n;
3082
 
#if ETHR_XCHK 
3083
 
    if (ethr_not_inited) {
3084
 
        ASSERT(0);
3085
 
        return EACCES;
3086
 
    }
3087
 
    if (!gp) {
3088
 
        ASSERT(0);
3089
 
        return EINVAL;
3090
 
    }
3091
 
#endif
3092
 
    n = spincount;
3093
 
    res = ethr_mutex_lock__(&gp->mtx);
3094
 
    if (res != 0)
3095
 
        return res;
3096
 
    while (n >= 0 && !gp->open) {
3097
 
        res = ethr_mutex_unlock__(&gp->mtx);
3098
 
        if (res != 0)
3099
 
            return res;
3100
 
        res = ethr_mutex_lock__(&gp->mtx);
3101
 
        if (res != 0)
3102
 
            return res;
3103
 
        n--;
3104
 
    }
3105
 
    while (!gp->open) {
3106
 
        res = ethr_cond_wait(&gp->cnd, &gp->mtx);
3107
 
        if (res != 0 && res != EINTR)
3108
 
            goto done;
3109
 
    }
3110
 
    gp->open--;
3111
 
 done:
3112
 
    ures = ethr_mutex_unlock__(&gp->mtx);
3113
 
    if (res == 0)
3114
 
        res = ures;
3115
 
    return res;
3116
 
}
3117
 
 
3118
 
 
3119
 
int
3120
 
ethr_gate_wait(ethr_gate *gp)
3121
 
{
3122
 
    return ethr_gate_swait(gp, 0);
3123
 
}
3124
 
 
3125
 
 
3126
 
/* rwmutex fallback */
3127
 
#ifdef ETHR_USE_RWMTX_FALLBACK
3128
 
 
3129
 
int
3130
 
ethr_rwmutex_init(ethr_rwmutex *rwmtx)
3131
 
{
3132
 
    int res;
3133
 
#if ETHR_XCHK
3134
 
    if (!rwmtx) {
3135
 
        ASSERT(0);
3136
 
        return EINVAL;
3137
 
    }
3138
 
#endif
3139
 
    res = ethr_mutex_init(&rwmtx->mtx);
3140
 
    if (res != 0)
3141
 
        return res;
3142
 
    ethr_cond_init(&rwmtx->rcnd);
3143
 
    if (res != 0)
3144
 
        goto error_cleanup1;
3145
 
    res = ethr_cond_init(&rwmtx->wcnd);
3146
 
    if (res != 0)
3147
 
        goto error_cleanup2;
3148
 
    rwmtx->readers = 0;
3149
 
    rwmtx->waiting_readers = 0;
3150
 
    rwmtx->waiting_writers = 0;
3151
 
#if ETHR_XCHK
3152
 
    rwmtx->initialized = ETHR_RWMUTEX_INITIALIZED;
3153
 
#endif
3154
 
    return 0;
3155
 
 error_cleanup2:
3156
 
    ethr_cond_destroy(&rwmtx->rcnd);
3157
 
 error_cleanup1:
3158
 
    ethr_mutex_destroy(&rwmtx->mtx);
3159
 
    return res;
3160
 
}
3161
 
 
3162
 
int
3163
 
ethr_rwmutex_destroy(ethr_rwmutex *rwmtx)
3164
 
{
3165
 
    int res, pres;
3166
 
#if ETHR_XCHK
3167
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3168
 
        ASSERT(0);
3169
 
        return EINVAL;
3170
 
    }
3171
 
    rwmtx->initialized = 0;
3172
 
#endif
3173
 
    res = ethr_mutex_destroy(&rwmtx->mtx);
3174
 
    pres = ethr_cond_destroy(&rwmtx->rcnd);
3175
 
    if (res == 0)
3176
 
        res = pres;
3177
 
    pres = ethr_cond_destroy(&rwmtx->wcnd);
3178
 
    if (res == 0)
3179
 
        res = pres;
3180
 
    return res;
3181
 
}
3182
 
 
3183
 
int
3184
 
ethr_rwmutex_tryrlock(ethr_rwmutex *rwmtx)
3185
 
{
3186
 
    int res;
3187
 
#if ETHR_XCHK
3188
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3189
 
        ASSERT(0);
3190
 
        return EINVAL;
3191
 
    }
3192
 
#endif
3193
 
    res = ethr_mutex_trylock__(&rwmtx->mtx);
3194
 
    if (res != 0)
3195
 
        return res;
3196
 
    if (!rwmtx->waiting_writers) {
3197
 
        res = ethr_mutex_unlock__(&rwmtx->mtx);
3198
 
        if (res == 0)
3199
 
            return EBUSY;
3200
 
        return res;
3201
 
    }
3202
 
    rwmtx->readers++;
3203
 
    return ethr_mutex_unlock__(&rwmtx->mtx);
3204
 
}
3205
 
 
3206
 
int
3207
 
ethr_rwmutex_rlock(ethr_rwmutex *rwmtx)
3208
 
{
3209
 
    int res;
3210
 
#if ETHR_XCHK
3211
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3212
 
        ASSERT(0);
3213
 
        return EINVAL;
3214
 
    }
3215
 
#endif
3216
 
    res = ethr_mutex_lock__(&rwmtx->mtx);
3217
 
    if (res != 0)
3218
 
        return res;
3219
 
    while (rwmtx->waiting_writers) {
3220
 
        rwmtx->waiting_readers++;
3221
 
        res = ethr_cond_wait(&rwmtx->rcnd, &rwmtx->mtx);
3222
 
        rwmtx->waiting_readers--;
3223
 
        if (res != 0 && res != EINTR) {
3224
 
            (void) ethr_mutex_unlock__(&rwmtx->mtx);
3225
 
            return res;
3226
 
        }
3227
 
    }
3228
 
    rwmtx->readers++;
3229
 
    return ethr_mutex_unlock__(&rwmtx->mtx);
3230
 
}
3231
 
 
3232
 
int
3233
 
ethr_rwmutex_runlock(ethr_rwmutex *rwmtx)
3234
 
{
3235
 
    int res, ures;
3236
 
#if ETHR_XCHK
3237
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3238
 
        ASSERT(0);
3239
 
        return EINVAL;
3240
 
    }
3241
 
#endif
3242
 
    res = ethr_mutex_lock__(&rwmtx->mtx);
3243
 
    if (res != 0)
3244
 
        return res;
3245
 
    rwmtx->readers--;
3246
 
    if (!rwmtx->readers && rwmtx->waiting_writers)
3247
 
        res = ethr_cond_signal(&rwmtx->wcnd);
3248
 
    ures = ethr_mutex_unlock__(&rwmtx->mtx);
3249
 
    if (res == 0)
3250
 
        res = ures;
3251
 
    return res;
3252
 
}
3253
 
 
3254
 
int
3255
 
ethr_rwmutex_tryrwlock(ethr_rwmutex *rwmtx)
3256
 
{
3257
 
    int res;
3258
 
#if ETHR_XCHK
3259
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3260
 
        ASSERT(0);
3261
 
        return EINVAL;
3262
 
    }
3263
 
#endif
3264
 
    res = ethr_mutex_trylock__(&rwmtx->mtx);
3265
 
    if (res != 0)
3266
 
        return res;
3267
 
    if (!rwmtx->readers && !rwmtx->waiting_writers)
3268
 
        return 0;
3269
 
    else {
3270
 
        res = ethr_mutex_unlock__(&rwmtx->mtx);
3271
 
        if (res == 0)
3272
 
            return EBUSY;
3273
 
        return res;
3274
 
    }
3275
 
}
3276
 
 
3277
 
int
3278
 
ethr_rwmutex_rwlock(ethr_rwmutex *rwmtx)
3279
 
{
3280
 
    int res;
3281
 
#if ETHR_XCHK
3282
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3283
 
        ASSERT(0);
3284
 
        return EINVAL;
3285
 
    }
3286
 
#endif
3287
 
    res = ethr_mutex_lock__(&rwmtx->mtx);
3288
 
    if (res != 0)
3289
 
        return res;
3290
 
    if (!rwmtx->readers && !rwmtx->waiting_writers) 
3291
 
        return 0;
3292
 
    
3293
 
    while (rwmtx->readers) {
3294
 
        rwmtx->waiting_writers++;
3295
 
        res = ethr_cond_wait(&rwmtx->wcnd, &rwmtx->mtx);
3296
 
        rwmtx->waiting_writers--;
3297
 
        if (res != 0 && res != EINTR) {
3298
 
            (void) ethr_rwmutex_rwunlock(rwmtx);
3299
 
            return res;
3300
 
        }
3301
 
    }
3302
 
    return 0;
3303
 
}
3304
 
 
3305
 
int
3306
 
ethr_rwmutex_rwunlock(ethr_rwmutex *rwmtx)
3307
 
{
3308
 
    int res, ures;
3309
 
#if ETHR_XCHK
3310
 
    if (!rwmtx || rwmtx->initialized != ETHR_RWMUTEX_INITIALIZED) {
3311
 
        ASSERT(0);
3312
 
        return EINVAL;
3313
 
    }
3314
 
#endif
3315
 
    res = 0;
3316
 
    if (rwmtx->waiting_writers)
3317
 
        res = ethr_cond_signal(&rwmtx->wcnd);
3318
 
    else if (rwmtx->waiting_readers)
3319
 
        res = ethr_cond_broadcast(&rwmtx->rcnd);
3320
 
    ures = ethr_mutex_unlock__(&rwmtx->mtx);
3321
 
    if (res == 0)
3322
 
        res = ures;
3323
 
    return res;
3324
 
}
3325
 
 
3326
 
#endif /* #ifdef ETHR_USE_RWMTX_FALLBACK */
3327
 
 
3328
 
void
3329
 
ethr_compiler_barrier(void)
3330
 
{
3331
 
 
3332
 
}
3333
 
 
3334
 
#ifdef DEBUG
3335
 
 
3336
 
#include <stdio.h>
3337
 
int ethr_assert_failed(char *f, int l, char *a)
3338
 
{
3339
 
    fprintf(stderr, "%s:%d: Assertion failed: %s\n", f, l, a);
3340
 
    abort();
3341
 
    return 0;
3342
 
}
3343
 
 
3344
 
#endif
3345
 
 
3346