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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/sys.h

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
19
19
#define __SYS_H__
20
20
 
21
21
/* xxxP __VXWORKS__ */
 
22
#ifdef VXWORKS
 
23
#include <vxWorks.h>
 
24
#endif
 
25
 
 
26
#ifdef ERTS_SMP
 
27
/*
 
28
 * Currently we always need the child waiter thread when smp support
 
29
 * is enabled...
 
30
 */
 
31
#undef ENABLE_CHILD_WAITER_THREAD
 
32
#define ENABLE_CHILD_WAITER_THREAD 1
 
33
#endif
 
34
 
 
35
/* The ERTS_TIMER_TREAD #define must be visible to the
 
36
   erl_${OS}_sys.h #include files: it controls whether
 
37
   certain optional facilities should be defined or not. */
 
38
#ifdef ERTS_SMP
 
39
/* #define ERTS_TIMER_THREAD No timer thread for now (bugs present) */
 
40
#endif
22
41
 
23
42
#if defined (__WIN32__)
24
43
#  include "erl_win_sys.h"
33
52
#endif
34
53
#endif
35
54
 
 
55
/*
 
56
 * To allow building of Universal Binaries for Mac OS X,
 
57
 * we must not depend on the endian detected by the configure script.
 
58
 */
 
59
#if defined(__APPLE__)
 
60
#  if defined(__BIG_ENDIAN__) && !defined(WORDS_BIGENDIAN)
 
61
#    define WORDS_BIGENDIAN 1
 
62
#  elif !defined(__BIG_ENDIAN__) && defined(WORDS_BIGENDIAN)
 
63
#    undef WORDS_BIGENDIAN
 
64
#  endif
 
65
#endif
 
66
 
 
67
/*
 
68
 * Make sure that ENOTSUP is defined.
 
69
 */
 
70
#ifndef ENOTSUP
 
71
#  ifdef EOPNOTSUPP
 
72
#    define ENOTSUP EOPNOTSUPP
 
73
#else
 
74
#    define ENOTSUP -1738659
 
75
#  endif
 
76
#endif
 
77
 
36
78
#ifdef ERTS_INLINE
37
79
#  ifndef ERTS_CAN_INLINE
38
80
#    define ERTS_CAN_INLINE 1
50
92
#  endif
51
93
#endif
52
94
 
 
95
#if defined(DEBUG) || defined(ERTS_ENABLE_LOCK_CHECK)
 
96
#  undef ERTS_CAN_INLINE
 
97
#  define ERTS_CAN_INLINE 0
 
98
#  undef ERTS_INLINE
 
99
#  define ERTS_INLINE
 
100
#endif
 
101
 
 
102
#if ERTS_CAN_INLINE
 
103
#define ERTS_GLB_INLINE static ERTS_INLINE
 
104
#else
 
105
#define ERTS_GLB_INLINE
 
106
#endif
 
107
 
 
108
#define ERTS_GLB_INLINE_INCL_FUNC_DEF \
 
109
  (ERTS_CAN_INLINE || defined(ERTS_DO_INCL_GLB_INLINE_FUNC_DEF))
 
110
 
 
111
#ifndef ERTS_EXIT_AFTER_DUMP
 
112
#  define ERTS_EXIT_AFTER_DUMP exit
 
113
#endif
 
114
 
53
115
#ifdef DEBUG
54
116
#  define ASSERT(e) \
55
117
  if (e) { \
111
173
 
112
174
#if __GNUC__
113
175
#  define __noreturn __attribute__((noreturn))
 
176
#  undef __deprecated
114
177
#  if __GNUC__ >= 3
115
178
#    define __deprecated __attribute__((deprecated))
116
179
#  else
121
184
#  define __deprecated
122
185
#endif
123
186
 
 
187
#ifdef ERTS_SMP
 
188
void erts_wake_io_thread(void);
 
189
#endif
 
190
 
124
191
/*
125
192
** Data types:
126
193
**
204
271
#error 64-bit architecture, but no appropriate type to use for Uint64 and Sint64 found 
205
272
#endif
206
273
 
 
274
#include "erl_lock_check.h"
 
275
#include "erl_smp.h"
 
276
 
 
277
#ifdef ERTS_SMP
 
278
extern erts_smp_atomic_t erts_writing_erl_crash_dump;
 
279
#define ERTS_IS_CRASH_DUMPING \
 
280
  ((int) erts_smp_atomic_read(&erts_writing_erl_crash_dump))
 
281
#else
 
282
extern volatile int erts_writing_erl_crash_dump;
 
283
#define ERTS_IS_CRASH_DUMPING erts_writing_erl_crash_dump
 
284
#endif
 
285
 
207
286
/* Deal with memcpy() vs bcopy() etc. We want to use the mem*() functions,
208
287
   but be able to fall back on bcopy() etc on systems that don't have
209
288
   mem*(), but this doesn't work to well with memset()/bzero() - thus the
223
302
 
224
303
#ifdef ISC32                    /* Too much for the Makefile... */
225
304
#  define signal        sigset
226
 
#  define lgamma        undef_math_func_1
227
 
#  define asinh undef_math_func_1
228
 
#  define acosh undef_math_func_1
229
 
#  define atanh undef_math_func_1
 
305
#  define NO_ASINH
 
306
#  define NO_ACOSH
 
307
#  define NO_ATANH
230
308
#  define NO_FTRUNCATE
231
309
#  define SIG_SIGHOLD
232
310
#  define _POSIX_SOURCE 
235
313
 
236
314
#ifdef QNX                      /* Too much for the Makefile... */
237
315
#  define SYS_SELECT_H
238
 
#  define erf   undef_math_func_1
239
 
#  define erfc  undef_math_func_1
240
 
#  define lgamma        undef_math_func_1
 
316
#  define NO_ERF
 
317
#  define NO_ERFC
241
318
/* This definition doesn't take NaN into account, but matherr() gets those */
242
319
#  define finite(x) (fabs(x) != HUGE_VAL)
243
320
#  define USE_MATHERR
305
382
#  endif /* !__WIN32__ */
306
383
# endif /* _OSE_ */
307
384
#endif /* WANT_NONBLOCKING */
308
 
     
 
385
 
 
386
 
 
387
void __noreturn erl_exit(int n, char*, ...);
 
388
 
 
389
/* Some special erl_exit() codes: */
 
390
#define ERTS_INTR_EXIT  INT_MIN         /* called from signal handler */
 
391
#define ERTS_ABORT_EXIT (INT_MIN + 1)   /* no crash dump; only abort() */
 
392
#define ERTS_DUMP_EXIT  (127)           /* crash dump; then exit() */
 
393
 
 
394
 
 
395
#ifndef ERTS_SMP
309
396
EXTERN_FUNCTION(int, check_async_ready, (_VOID_));
310
 
 
311
397
#ifdef USE_THREADS
312
 
 
313
398
EXTERN_FUNCTION(void, sys_async_ready, (int hndl));
314
 
 
315
 
#endif
316
 
 
317
 
/* Memory allocated from system dependent code (declared in utils.c) */
318
 
extern Uint erts_sys_misc_mem_sz;
319
 
 
320
 
/* Io constants to sys_printf and sys_putc */
321
 
 
322
 
typedef enum {
323
 
    CBUF = 0,
324
 
    COUT = 1,
325
 
    CERR = 2
326
 
} CIO;
 
399
#endif
 
400
#endif
 
401
 
 
402
#ifdef ERTS_SMP
 
403
void erts_io_lock(void);
 
404
void erts_io_unlock(void);
 
405
#endif
 
406
 
 
407
ERTS_GLB_INLINE void erts_smp_io_lock(void);
 
408
ERTS_GLB_INLINE void erts_smp_io_unlock(void);
 
409
 
 
410
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
 
411
 
 
412
ERTS_GLB_INLINE void
 
413
erts_smp_io_lock(void)
 
414
{
 
415
#ifdef ERTS_SMP
 
416
    erts_io_lock();
 
417
#endif
 
418
}
 
419
 
 
420
ERTS_GLB_INLINE void
 
421
erts_smp_io_unlock(void)
 
422
{
 
423
#ifdef ERTS_SMP
 
424
    erts_io_unlock();
 
425
#endif
 
426
}
 
427
 
 
428
#endif
 
429
 
 
430
Eterm erts_check_io_info(void *p);
 
431
 
 
432
/* Size of misc memory allocated from system dependent code */
 
433
Uint erts_sys_misc_mem_sz(void);
 
434
 
 
435
/* print stuff is declared here instead of in global.h, so sys stuff won't
 
436
   have to include global.h */
 
437
#include "erl_printf.h"
 
438
 
 
439
/* Io constants to erts_print and erts_putc */
 
440
#define ERTS_PRINT_STDERR       (2)
 
441
#define ERTS_PRINT_STDOUT       (1)
 
442
#define ERTS_PRINT_INVALID      (0) /* Don't want to use 0 since CBUF was 0 */
 
443
#define ERTS_PRINT_FILE         (-1)
 
444
#define ERTS_PRINT_SBUF         (-2)
 
445
#define ERTS_PRINT_SNBUF        (-3)
 
446
#define ERTS_PRINT_DSBUF        (-4)
 
447
 
 
448
#define ERTS_PRINT_MIN          ERTS_PRINT_DSBUF
 
449
 
 
450
typedef struct {
 
451
    char *buf;
 
452
    size_t size;
 
453
} erts_print_sn_buf;
 
454
 
 
455
int erts_print(int to, void *arg, char *format, ...);   /* in utils.c */
 
456
int erts_putc(int to, void *arg, char);                 /* in utils.c */
 
457
 
 
458
/* logger stuff is declared here instead of in global.h, so sys files
 
459
   won't have to include global.h */
 
460
 
 
461
erts_dsprintf_buf_t *erts_create_logger_dsbuf(void);
 
462
int erts_send_info_to_logger(Eterm, erts_dsprintf_buf_t *);
 
463
int erts_send_warning_to_logger(Eterm, erts_dsprintf_buf_t *);
 
464
int erts_send_error_to_logger(Eterm, erts_dsprintf_buf_t *);
 
465
int erts_send_info_to_logger_str(Eterm, char *); 
 
466
int erts_send_warning_to_logger_str(Eterm, char *);
 
467
int erts_send_error_to_logger_str(Eterm, char *);
 
468
int erts_send_info_to_logger_nogl(erts_dsprintf_buf_t *);
 
469
int erts_send_warning_to_logger_nogl(erts_dsprintf_buf_t *);
 
470
int erts_send_error_to_logger_nogl(erts_dsprintf_buf_t *);
 
471
int erts_send_info_to_logger_str_nogl(char *);
 
472
int erts_send_warning_to_logger_str_nogl(char *);
 
473
int erts_send_error_to_logger_str_nogl(char *);
327
474
 
328
475
typedef struct preload {
329
476
    char *name;                 /* Name of module */
360
507
} SysDriverOpts;
361
508
 
362
509
 
363
 
extern int cerr_pos;
364
 
 
365
510
extern char os_type[];
366
511
 
367
512
extern int sys_init_time(void);
368
 
extern void erts_deliver_time(SysTimeval *);
 
513
#if defined(ERTS_TIMER_THREAD)
 
514
#define erts_deliver_time()
 
515
#else
 
516
extern void erts_deliver_time(void);
 
517
#endif
369
518
extern void erts_time_remaining(SysTimeval *);
370
519
extern int erts_init_time_sup(void);
371
520
extern void erts_sys_init_float(void);
 
521
extern void erts_thread_init_float(void);
 
522
 
 
523
/* Dynamic library/driver loading */
 
524
extern void erl_sys_ddll_init(void); /* to initialize mutexes etc */
 
525
extern int erts_sys_ddll_open(char *path, void **handle);
 
526
extern int erts_sys_ddll_load_driver_init(void *handle, void **function);
 
527
extern int erts_sys_ddll_close(void *handle);
 
528
extern void *erts_sys_ddll_call_init(void *function);
 
529
extern int erts_sys_ddll_sym(void *handle, char *name, void **function);
 
530
extern char *erts_sys_ddll_error(int code);
 
531
 
372
532
 
373
533
/*
374
534
 * System interfaces for startup/sae code (functions found in respective sys.c)
375
535
 */
 
536
 
 
537
extern void erts_sys_pre_init(void);
376
538
extern void erl_sys_init(void);
377
539
extern void erl_sys_args(int *argc, char **argv);
378
540
extern void erl_sys_schedule(int);
382
544
void sys_tty_reset(void);
383
545
#endif
384
546
 
 
547
#ifdef ERTS_SMP
 
548
extern erts_smp_tid_t erts_io_thr_tid; /* io.c */
 
549
#endif
385
550
 
386
551
EXTERN_FUNCTION(int, sys_max_files, (_VOID_));
387
 
void sys_init_io(byte*, Uint);
 
552
void sys_init_io(void);
388
553
Preload* sys_preloaded(void);
389
554
EXTERN_FUNCTION(unsigned char*, sys_preload_begin, (Preload*));
390
555
EXTERN_FUNCTION(void, sys_preload_end, (Preload*));
399
564
                   int *hour, int *minute, int *second);
400
565
void get_universaltime(int *year, int *month, int *day, 
401
566
                       int *hour, int *minute, int *second);
402
 
int univ_to_local(int *year, int *month, int *day, 
403
 
                  int *hour, int *minute, int *second);
404
 
int local_to_univ(int *year, int *month, int *day, 
405
 
                  int *hour, int *minute, int *second, int isdst);
 
567
int univ_to_local(Sint *year, Sint *month, Sint *day, 
 
568
                  Sint *hour, Sint *minute, Sint *second);
 
569
int local_to_univ(Sint *year, Sint *month, Sint *day, 
 
570
                  Sint *hour, Sint *minute, Sint *second, int isdst);
406
571
void get_now(Uint*, Uint*, Uint*);
407
572
EXTERN_FUNCTION(void, set_break_quit, (void (*)(void), void (*)(void)));
408
573
 
419
584
EXTERN_FUNCTION(void, init_sys_float, (void));
420
585
EXTERN_FUNCTION(int, sys_chars_to_double, (char*, double*));
421
586
EXTERN_FUNCTION(int, sys_double_to_chars, (double, char*));
422
 
EXTERN_FUNCTION(void, sys_printf, (CIO, char*, _DOTS_));
423
 
EXTERN_FUNCTION(void, sys_putc, (int, CIO));
424
587
EXTERN_FUNCTION(void, sys_get_pid, (char *));
425
588
EXTERN_FUNCTION(int, sys_putenv, (char *));
426
589
 
 
590
/* utils.c */
 
591
 
427
592
/* Options to sys_alloc_opt */
428
593
#define SYS_ALLOC_OPT_TRIM_THRESHOLD 0
429
594
#define SYS_ALLOC_OPT_TOP_PAD        1
447
612
 
448
613
EXTERN_FUNCTION(void, sys_alloc_stat, (SysAllocStat *));
449
614
 
 
615
/* Block the whole system... */
 
616
 
 
617
#define ERTS_BS_FLG_ALLOW_GC                            (((Uint32) 1) << 0)
 
618
#define ERTS_BS_FLG_ALLOW_IO                            (((Uint32) 1) << 1)
 
619
 
 
620
/* Activities... */
 
621
typedef enum {
 
622
    ERTS_ACTIVITY_UNDEFINED,    /* Undefined activity */
 
623
    ERTS_ACTIVITY_WAIT,         /* Waiting */
 
624
    ERTS_ACTIVITY_GC,           /* Garbage collecting */
 
625
    ERTS_ACTIVITY_IO            /* I/O including message passing to erl procs */
 
626
} erts_activity_t;
 
627
 
 
628
#ifdef ERTS_SMP
 
629
 
 
630
typedef enum {
 
631
    ERTS_ACT_ERR_LEAVE_WAIT_UNLOCKED,
 
632
    ERTS_ACT_ERR_LEAVE_UNKNOWN_ACTIVITY,
 
633
    ERTS_ACT_ERR_ENTER_UNKNOWN_ACTIVITY
 
634
} erts_activity_error_t;
 
635
 
 
636
typedef struct {
 
637
    erts_smp_atomic_t do_block;
 
638
    struct {
 
639
        erts_smp_atomic_t wait;
 
640
        erts_smp_atomic_t gc;
 
641
        erts_smp_atomic_t io;
 
642
    } in_activity;
 
643
} erts_system_block_state_t;
 
644
 
 
645
extern erts_system_block_state_t erts_system_block_state;
 
646
 
 
647
int erts_is_system_blocked(erts_activity_t allowed_activities);
 
648
void erts_block_me(void (*prepare)(void *), void (*resume)(void *), void *arg);
 
649
void erts_register_blockable_thread(void);
 
650
void erts_unregister_blockable_thread(void);
 
651
void erts_note_activity_begin(erts_activity_t activity);
 
652
void
 
653
erts_check_block(erts_activity_t old_activity,
 
654
                 erts_activity_t new_activity,
 
655
                 int locked,
 
656
                 void (*prepare)(void *),
 
657
                 void (*resume)(void *),
 
658
                 void *arg);
 
659
void erts_block_system(Uint32 allowed_activities);
 
660
int erts_emergency_block_system(long timeout, Uint32 allowed_activities);
 
661
void erts_release_system(void);
 
662
void erts_system_block_init(void);
 
663
void erts_set_activity_error(erts_activity_error_t, char *, int);
 
664
#ifdef ERTS_ENABLE_LOCK_CHECK
 
665
void erts_lc_activity_change_begin(void);
 
666
void erts_lc_activity_change_end(void);
 
667
#endif
 
668
#endif
 
669
 
 
670
#define erts_smp_activity_begin(NACT, PRP, RSM, ARG)            \
 
671
  erts_smp_set_activity(ERTS_ACTIVITY_UNDEFINED,                \
 
672
                        (NACT),                                 \
 
673
                        0,                                      \
 
674
                        (PRP),                                  \
 
675
                        (RSM),                                  \
 
676
                        (ARG),                                  \
 
677
                        __FILE__,                               \
 
678
                        __LINE__)
 
679
#define erts_smp_activity_change(OACT, NACT, PRP, RSM, ARG)     \
 
680
  erts_smp_set_activity((OACT),                                 \
 
681
                        (NACT),                                 \
 
682
                        0,                                      \
 
683
                        (PRP),                                  \
 
684
                        (RSM),                                  \
 
685
                        (ARG),                                  \
 
686
                        __FILE__,                               \
 
687
                        __LINE__)
 
688
#define erts_smp_activity_end(OACT, PRP, RSM, ARG)              \
 
689
  erts_smp_set_activity((OACT),                                 \
 
690
                        ERTS_ACTIVITY_UNDEFINED,                \
 
691
                        0,                                      \
 
692
                        (PRP),                                  \
 
693
                        (RSM),                                  \
 
694
                        (ARG),                                  \
 
695
                        __FILE__,                               \
 
696
                        __LINE__)
 
697
 
 
698
#define erts_smp_locked_activity_begin(NACT)                    \
 
699
  erts_smp_set_activity(ERTS_ACTIVITY_UNDEFINED,                \
 
700
                        (NACT),                                 \
 
701
                        1,                                      \
 
702
                        NULL,                                   \
 
703
                        NULL,                                   \
 
704
                        NULL,                                   \
 
705
                        __FILE__,                               \
 
706
                        __LINE__)
 
707
#define erts_smp_locked_activity_change(OACT, NACT)             \
 
708
  erts_smp_set_activity((OACT),                                 \
 
709
                        (NACT),                                 \
 
710
                        1,                                      \
 
711
                        NULL,                                   \
 
712
                        NULL,                                   \
 
713
                        NULL,                                   \
 
714
                        __FILE__,                               \
 
715
                        __LINE__)
 
716
#define erts_smp_locked_activity_end(OACT)                      \
 
717
  erts_smp_set_activity((OACT),                                 \
 
718
                        ERTS_ACTIVITY_UNDEFINED,                \
 
719
                        1,                                      \
 
720
                        NULL,                                   \
 
721
                        NULL,                                   \
 
722
                        NULL,                                   \
 
723
                        __FILE__,                               \
 
724
                        __LINE__)
 
725
 
 
726
 
 
727
ERTS_GLB_INLINE int erts_smp_is_system_blocked(erts_activity_t allowed_activities);
 
728
ERTS_GLB_INLINE void erts_smp_block_system(Uint32 allowed_activities);
 
729
ERTS_GLB_INLINE int erts_smp_emergency_block_system(long timeout,
 
730
                                                    Uint32 allowed_activities);
 
731
ERTS_GLB_INLINE void erts_smp_release_system(void);
 
732
ERTS_GLB_INLINE int erts_smp_pending_system_block(void);
 
733
ERTS_GLB_INLINE void erts_smp_chk_system_block(void (*prepare)(void *),
 
734
                                               void (*resume)(void *),
 
735
                                               void *arg);
 
736
ERTS_GLB_INLINE void
 
737
erts_smp_set_activity(erts_activity_t old_activity,
 
738
                      erts_activity_t new_activity,
 
739
                      int locked,
 
740
                      void (*prepare)(void *),
 
741
                      void (*resume)(void *),
 
742
                      void *arg,
 
743
                      char *file,
 
744
                      int line);
 
745
 
 
746
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
 
747
 
 
748
 
 
749
ERTS_GLB_INLINE int
 
750
erts_smp_is_system_blocked(erts_activity_t allowed_activities)
 
751
{
 
752
#ifdef ERTS_SMP
 
753
    return erts_is_system_blocked(allowed_activities);
 
754
#else
 
755
    return 1;
 
756
#endif
 
757
}
 
758
 
 
759
ERTS_GLB_INLINE void
 
760
erts_smp_block_system(Uint32 allowed_activities)
 
761
{
 
762
#ifdef ERTS_SMP
 
763
    erts_block_system(allowed_activities);
 
764
#endif
 
765
}
 
766
 
 
767
ERTS_GLB_INLINE int
 
768
erts_smp_emergency_block_system(long timeout, Uint32 allowed_activities)
 
769
{
 
770
#ifdef ERTS_SMP
 
771
    return erts_emergency_block_system(timeout, allowed_activities);
 
772
#else
 
773
    return 0;
 
774
#endif
 
775
}
 
776
 
 
777
ERTS_GLB_INLINE void
 
778
erts_smp_release_system(void)
 
779
{
 
780
#ifdef ERTS_SMP
 
781
    erts_release_system();
 
782
#endif
 
783
}
 
784
 
 
785
ERTS_GLB_INLINE int
 
786
erts_smp_pending_system_block(void)
 
787
{
 
788
#ifdef ERTS_SMP
 
789
    return erts_smp_atomic_read(&erts_system_block_state.do_block);
 
790
#else
 
791
    return 0;
 
792
#endif
 
793
}
 
794
 
 
795
 
 
796
ERTS_GLB_INLINE void
 
797
erts_smp_chk_system_block(void (*prepare)(void *),
 
798
                          void (*resume)(void *),
 
799
                          void *arg)
 
800
{
 
801
#ifdef ERTS_SMP
 
802
    if (erts_smp_pending_system_block())
 
803
        erts_block_me(prepare, resume, arg);
 
804
#endif
 
805
}
 
806
 
 
807
ERTS_GLB_INLINE void
 
808
erts_smp_set_activity(erts_activity_t old_activity,
 
809
                      erts_activity_t new_activity,
 
810
                      int locked,
 
811
                      void (*prepare)(void *),
 
812
                      void (*resume)(void *),
 
813
                      void *arg,
 
814
                      char *file,
 
815
                      int line)
 
816
{
 
817
#ifdef ERTS_SMP
 
818
#ifdef ERTS_ENABLE_LOCK_CHECK
 
819
    erts_lc_activity_change_begin();
 
820
#endif
 
821
    switch (old_activity) {
 
822
    case ERTS_ACTIVITY_UNDEFINED:
 
823
        break;
 
824
    case ERTS_ACTIVITY_WAIT:
 
825
        erts_smp_atomic_dec(&erts_system_block_state.in_activity.wait);
 
826
        if (locked) {
 
827
            /* You are not allowed to leave activity waiting
 
828
             * without supplying the possibility to block
 
829
             * unlocked.
 
830
             */
 
831
            erts_set_activity_error(ERTS_ACT_ERR_LEAVE_WAIT_UNLOCKED,
 
832
                                    file, line);
 
833
        }
 
834
        break;
 
835
    case ERTS_ACTIVITY_GC:
 
836
        erts_smp_atomic_dec(&erts_system_block_state.in_activity.gc);
 
837
        break;
 
838
    case ERTS_ACTIVITY_IO:
 
839
        erts_smp_atomic_dec(&erts_system_block_state.in_activity.io);
 
840
        break;
 
841
    default:
 
842
        erts_set_activity_error(ERTS_ACT_ERR_LEAVE_UNKNOWN_ACTIVITY,
 
843
                                file, line);
 
844
        break;
 
845
    }
 
846
 
 
847
    if (erts_smp_pending_system_block())
 
848
        erts_check_block(old_activity,new_activity,locked,prepare,resume,arg);
 
849
 
 
850
    switch (new_activity) {
 
851
    case ERTS_ACTIVITY_UNDEFINED:
 
852
        break;
 
853
    case ERTS_ACTIVITY_WAIT:
 
854
        erts_smp_atomic_inc(&erts_system_block_state.in_activity.wait);
 
855
        break;
 
856
    case ERTS_ACTIVITY_GC:
 
857
        erts_smp_atomic_inc(&erts_system_block_state.in_activity.gc);
 
858
        break;
 
859
    case ERTS_ACTIVITY_IO:
 
860
        erts_smp_atomic_inc(&erts_system_block_state.in_activity.io);
 
861
        break;
 
862
    default:
 
863
        erts_set_activity_error(ERTS_ACT_ERR_ENTER_UNKNOWN_ACTIVITY,
 
864
                                file, line);
 
865
        break;
 
866
    }
 
867
 
 
868
    switch (new_activity) {
 
869
    case ERTS_ACTIVITY_WAIT:
 
870
    case ERTS_ACTIVITY_GC:
 
871
    case ERTS_ACTIVITY_IO:
 
872
        if (erts_smp_pending_system_block())
 
873
            erts_note_activity_begin(new_activity);
 
874
        break;
 
875
    default:
 
876
        break;
 
877
    }
 
878
 
 
879
#ifdef ERTS_ENABLE_LOCK_CHECK
 
880
    erts_lc_activity_change_end();
 
881
#endif
 
882
 
 
883
#endif
 
884
}
 
885
 
 
886
#endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
 
887
 
 
888
#if defined(DEBUG) || defined(ERTS_ENABLE_LOCK_CHECK)
 
889
#undef ERTS_REFC_DEBUG
 
890
#define ERTS_REFC_DEBUG
 
891
#endif
 
892
 
 
893
typedef erts_smp_atomic_t erts_refc_t;
 
894
 
 
895
ERTS_GLB_INLINE void erts_refc_init(erts_refc_t *refcp, long val);
 
896
ERTS_GLB_INLINE void erts_refc_inc(erts_refc_t *refcp, long min_val);
 
897
ERTS_GLB_INLINE long erts_refc_inctest(erts_refc_t *refcp, long min_val);
 
898
ERTS_GLB_INLINE void erts_refc_dec(erts_refc_t *refcp, long min_val);
 
899
ERTS_GLB_INLINE long erts_refc_dectest(erts_refc_t *refcp, long min_val);
 
900
ERTS_GLB_INLINE long erts_refc_read(erts_refc_t *refcp, long min_val);
 
901
 
 
902
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
 
903
 
 
904
ERTS_GLB_INLINE void
 
905
erts_refc_init(erts_refc_t *refcp, long val)
 
906
{
 
907
    erts_smp_atomic_init((erts_smp_atomic_t *) refcp, val);
 
908
}
 
909
 
 
910
ERTS_GLB_INLINE void
 
911
erts_refc_inc(erts_refc_t *refcp, long min_val)
 
912
{
 
913
#ifdef ERTS_REFC_DEBUG
 
914
    long val = erts_smp_atomic_inctest((erts_smp_atomic_t *) refcp);
 
915
    if (val < min_val)
 
916
        erl_exit(ERTS_ABORT_EXIT,
 
917
                 "erts_refc_inc(): Bad refc found (refc=%ld < %ld)!\n",
 
918
                 val, min_val);
 
919
#else
 
920
    erts_smp_atomic_inc((erts_smp_atomic_t *) refcp);
 
921
#endif
 
922
}
 
923
 
 
924
ERTS_GLB_INLINE long
 
925
erts_refc_inctest(erts_refc_t *refcp, long min_val)
 
926
{
 
927
    long val = erts_smp_atomic_inctest((erts_smp_atomic_t *) refcp);
 
928
#ifdef ERTS_REFC_DEBUG
 
929
    if (val < min_val)
 
930
        erl_exit(ERTS_ABORT_EXIT,
 
931
                 "erts_refc_inctest(): Bad refc found (refc=%ld < %ld)!\n",
 
932
                 val, min_val);
 
933
#endif
 
934
    return val;
 
935
}
 
936
 
 
937
ERTS_GLB_INLINE void
 
938
erts_refc_dec(erts_refc_t *refcp, long min_val)
 
939
{
 
940
#ifdef ERTS_REFC_DEBUG
 
941
    long val = erts_smp_atomic_dectest((erts_smp_atomic_t *) refcp);
 
942
    if (val < min_val)
 
943
        erl_exit(ERTS_ABORT_EXIT,
 
944
                 "erts_refc_dec(): Bad refc found (refc=%ld < %ld)!\n",
 
945
                 val, min_val);
 
946
#else
 
947
    erts_smp_atomic_dec((erts_smp_atomic_t *) refcp);
 
948
#endif
 
949
}
 
950
 
 
951
ERTS_GLB_INLINE long
 
952
erts_refc_dectest(erts_refc_t *refcp, long min_val)
 
953
{
 
954
    long val = erts_smp_atomic_dectest((erts_smp_atomic_t *) refcp);
 
955
#ifdef ERTS_REFC_DEBUG
 
956
    if (val < min_val)
 
957
        erl_exit(ERTS_ABORT_EXIT,
 
958
                 "erts_refc_dectest(): Bad refc found (refc=%ld < %ld)!\n",
 
959
                 val, min_val);
 
960
#endif
 
961
    return val;
 
962
}
 
963
 
 
964
ERTS_GLB_INLINE long
 
965
erts_refc_read(erts_refc_t *refcp, long min_val)
 
966
{
 
967
    long val = erts_smp_atomic_read((erts_smp_atomic_t *) refcp);
 
968
#ifdef ERTS_REFC_DEBUG
 
969
    if (val < min_val)
 
970
        erl_exit(ERTS_ABORT_EXIT,
 
971
                 "erts_refc_read(): Bad refc found (refc=%ld < %ld)!\n",
 
972
                 val, min_val);
 
973
#endif
 
974
    return val;
 
975
}
 
976
 
 
977
#endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
 
978
 
 
979
#ifdef ERTS_ENABLE_KERNEL_POLL
 
980
extern int erts_use_kernel_poll;
 
981
#endif
 
982
 
450
983
void elib_ensure_initialized(void);
451
984
 
452
985