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

« back to all changes in this revision

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

  • 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
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
20
20
#ifndef __SYS_H__
21
21
#define __SYS_H__
22
22
 
 
23
 
23
24
#if defined(VALGRIND) && !defined(NO_FPE_SIGNALS)
24
25
#  define NO_FPE_SIGNALS
25
26
#endif
26
27
 
27
 
/* Never use elib-malloc when purify-memory-tracing */
28
 
#if defined(PURIFY)
29
 
#undef ENABLE_ELIB_MALLOC
30
 
#undef ELIB_HEAP_SBRK
31
 
#undef ELIB_ALLOC_IS_CLIB
32
 
#endif
33
 
 
34
 
 
35
28
/* xxxP __VXWORKS__ */
36
29
#ifdef VXWORKS
37
30
#include <vxWorks.h>
46
39
#define ENABLE_CHILD_WAITER_THREAD 1
47
40
#endif
48
41
 
49
 
/* The ERTS_TIMER_TREAD #define must be visible to the
50
 
   erl_${OS}_sys.h #include files: it controls whether
51
 
   certain optional facilities should be defined or not. */
52
 
#if defined(ERTS_SMP) && 0
53
 
#define ERTS_TIMER_THREAD
54
 
#endif
55
 
 
56
42
#if defined (__WIN32__)
57
43
#  include "erl_win_sys.h"
58
44
#elif defined (VXWORKS) 
59
45
#  include "erl_vxworks_sys.h"
60
 
#elif defined (_OSE_) 
61
 
#  include "erl_ose_sys.h"
62
46
#else 
63
47
#  include "erl_unix_sys.h"
64
48
#ifndef UNIX
172
156
 
173
157
#include <stdarg.h>
174
158
 
175
 
#if defined(__STDC__) || defined(_MSC_VER)
176
 
#  define EXTERN_FUNCTION(t, f, x)  extern t f x
177
 
#  define FUNCTION(t, f, x) t f x
178
 
#  define _DOTS_ ...
179
 
#  define _VOID_      void
180
 
#elif defined(__cplusplus)
181
 
#  define EXTERN_FUNCTION(f, x) extern "C" { f x }
182
 
#  define FUNCTION(t, f, x) t f x
183
 
#  define _DOTS_ ...
184
 
#  define _VOID_    void
185
 
#else
186
 
#  define EXTERN_FUNCTION(t, f, x) extern t f (/*x*/)
187
 
#  define FUNCTION(t, f, x) t f (/*x*/)
188
 
#  define _DOTS_
189
 
#  define _VOID_
190
 
#endif
191
 
 
192
159
/* This isn't sys-dependent, but putting it here benefits sys.c and drivers
193
160
   - allow use of 'const' regardless of compiler */
194
161
 
198
165
 
199
166
#ifdef VXWORKS
200
167
/* Replace VxWorks' printf with a real one that does fprintf(stdout, ...) */
201
 
EXTERN_FUNCTION(int, real_printf, (const char *fmt, ...));
 
168
int real_printf(const char *fmt, ...);
202
169
#  define printf real_printf
203
170
#endif
204
171
 
230
197
** Data types:
231
198
**
232
199
** Eterm: A tagged erlang term (possibly 64 bits)
 
200
** BeamInstr: A beam code instruction unit, possibly larger than Eterm, not smaller.
233
201
** UInt:  An unsigned integer exactly as large as an Eterm.
234
202
** SInt:  A signed integer exactly as large as an eterm and therefor large
235
203
**        enough to hold the return value of the signed_val() macro.
 
204
** UWord: An unsigned integer at least as large as a void * and also as large
 
205
**          or larger than an Eterm
 
206
** SWord: A signed integer at least as large as a void * and also as large
 
207
**          or larger than an Eterm
236
208
** Uint32: An unsigned integer of 32 bits exactly
237
209
** Sint32: A signed integer of 32 bits exactly
238
210
** Uint16: An unsigned integer of 16 bits exactly
239
211
** Sint16: A signed integer of 16 bits exactly.
240
212
*/
241
213
 
 
214
#if !((SIZEOF_VOID_P >= 4) && (SIZEOF_VOID_P == SIZEOF_SIZE_T) \
 
215
      && ((SIZEOF_VOID_P == SIZEOF_INT) || (SIZEOF_VOID_P == SIZEOF_LONG)))
 
216
#error Cannot handle this combination of int/long/void*/size_t sizes
 
217
#endif
 
218
 
242
219
#if SIZEOF_VOID_P == 8
243
220
#undef  ARCH_32
244
221
#define ARCH_64
248
225
#else
249
226
#error Neither 32 nor 64 bit architecture
250
227
#endif
 
228
#if defined(ARCH_64) && defined(HALFWORD_HEAP_EMULATOR)
 
229
#    define HALFWORD_HEAP 1
 
230
#    define HALFWORD_ASSERT 0
 
231
#    define ASSERT_HALFWORD(COND) ASSERT(COND)
 
232
#else
 
233
#    define HALFWORD_HEAP 0
 
234
#    define HALFWORD_ASSERT 0
 
235
#    define ASSERT_HALFWORD(COND)
 
236
#endif
251
237
 
252
238
#if SIZEOF_VOID_P != SIZEOF_SIZE_T
253
239
#error sizeof(void*) != sizeof(size_t)
254
240
#endif
255
241
 
 
242
#if HALFWORD_HEAP
 
243
 
 
244
#if SIZEOF_INT == 4
 
245
typedef unsigned int Eterm;
 
246
typedef unsigned int Uint;
 
247
typedef int          Sint;
 
248
#define ERTS_SIZEOF_ETERM SIZEOF_INT
 
249
#else
 
250
#error Found no appropriate type to use for 'Eterm', 'Uint' and 'Sint'
 
251
#endif
 
252
 
 
253
#if SIZEOF_VOID_P == SIZEOF_LONG
 
254
typedef unsigned long UWord;
 
255
typedef long          SWord;
 
256
#elif SIZEOF_VOID_P == SIZEOF_INT
 
257
typedef unsigned int UWord;
 
258
typedef int          SWord;
 
259
#else
 
260
#error Found no appropriate type to use for 'Eterm', 'Uint' and 'Sint'
 
261
#endif
 
262
 
 
263
#else /* !HALFWORD_HEAP */
 
264
 
256
265
#if SIZEOF_VOID_P == SIZEOF_LONG
257
266
typedef unsigned long Eterm;
258
267
typedef unsigned long Uint;
267
276
#error Found no appropriate type to use for 'Eterm', 'Uint' and 'Sint'
268
277
#endif
269
278
 
 
279
typedef Uint UWord;
 
280
typedef Sint SWord;
 
281
 
 
282
#endif /* HALFWORD_HEAP */
 
283
 
 
284
typedef UWord BeamInstr;
 
285
 
270
286
#ifndef HAVE_INT64
271
287
#if SIZEOF_LONG == 8
272
288
#define HAVE_INT64 1
311
327
#error 64-bit architecture, but no appropriate type to use for Uint64 and Sint64 found 
312
328
#endif
313
329
 
314
 
#if defined(ARCH_64)
315
 
#  define ERTS_WORD_ALIGN_PAD_SZ(X) \
 
330
#  define ERTS_EXTRA_DATA_ALIGN_SZ(X) \
316
331
    (((size_t) 8) - (((size_t) (X)) & ((size_t) 7)))
317
 
#elif defined(ARCH_32)
318
 
#  define ERTS_WORD_ALIGN_PAD_SZ(X) \
319
 
    (((size_t) 4) - (((size_t) (X)) & ((size_t) 3)))
320
 
#else
321
 
#error "Not supported..."
322
 
#endif
323
332
 
324
333
#include "erl_lock_check.h"
 
334
 
 
335
/* needed by erl_smp.h */
 
336
int erts_send_warning_to_logger_str_nogl(char *);
 
337
 
325
338
#include "erl_smp.h"
326
339
 
327
340
#ifdef ERTS_WANT_BREAK_HANDLING
328
341
#  ifdef ERTS_SMP
329
 
extern erts_smp_atomic_t erts_break_requested;
330
 
#    define ERTS_BREAK_REQUESTED ((int) erts_smp_atomic_read(&erts_break_requested))
 
342
extern erts_smp_atomic32_t erts_break_requested;
 
343
#    define ERTS_BREAK_REQUESTED ((int) erts_smp_atomic32_read(&erts_break_requested))
331
344
#  else
332
345
extern volatile int erts_break_requested;
333
346
#    define ERTS_BREAK_REQUESTED erts_break_requested
340
353
#    define ERTS_GOT_SIGUSR1 0
341
354
#  else
342
355
#    ifdef ERTS_SMP
343
 
extern erts_smp_atomic_t erts_got_sigusr1;
344
 
#      define ERTS_GOT_SIGUSR1 ((int) erts_smp_atomic_read(&erts_got_sigusr1))
 
356
extern erts_smp_atomic32_t erts_got_sigusr1;
 
357
#      define ERTS_GOT_SIGUSR1 ((int) erts_smp_atomic32_read(&erts_got_sigusr1))
345
358
#    else
346
359
extern volatile int erts_got_sigusr1;
347
360
#      define ERTS_GOT_SIGUSR1 erts_got_sigusr1
408
421
   in non-blocking mode - and ioctl FIONBIO on AIX *doesn't* work for
409
422
   pipes or ttys (O_NONBLOCK does)!!! For now, we'll use FIONBIO for AIX. */
410
423
 
411
 
# ifdef _OSE_
412
 
static const int zero_value = 0, one_value = 1;
413
 
#      define SET_BLOCKING(fd)          ioctl((fd), FIONBIO, (char*)&zero_value)
414
 
#      define SET_NONBLOCKING(fd)       ioctl((fd), FIONBIO, (char*)&one_value)
415
 
#      define ERRNO_BLOCK EWOULDBLOCK
416
 
# else
417
 
 
418
424
#  ifdef __WIN32__
419
425
 
420
426
static unsigned long zero_value = 0, one_value = 1;
455
461
#      endif /* !NB_FIONBIO */
456
462
#    endif /* _WXWORKS_ */
457
463
#  endif /* !__WIN32__ */
458
 
# endif /* _OSE_ */
459
464
#endif /* WANT_NONBLOCKING */
460
465
 
461
 
extern erts_cpu_info_t *erts_cpuinfo; /* erl_init.c */
462
 
 
463
466
__decl_noreturn void __noreturn erl_exit(int n, char*, ...);
464
467
 
465
468
/* Some special erl_exit() codes: */
518
521
int erts_send_warning_to_logger_nogl(erts_dsprintf_buf_t *);
519
522
int erts_send_error_to_logger_nogl(erts_dsprintf_buf_t *);
520
523
int erts_send_info_to_logger_str_nogl(char *);
521
 
int erts_send_warning_to_logger_str_nogl(char *);
 
524
/* needed by erl_smp.h (declared above)
 
525
   int erts_send_warning_to_logger_str_nogl(char *); */
522
526
int erts_send_error_to_logger_str_nogl(char *);
523
527
 
524
528
typedef struct preload {
533
537
 * None of the drivers use all of the fields.
534
538
 */
535
539
 
536
 
/* OSE: Want process_type and priority in here as well! Needs updates in erl_bif_ports.c! */
537
 
 
538
540
typedef struct _SysDriverOpts {
539
541
    int ifd;                    /* Input file descriptor (fd driver). */
540
542
    int ofd;                    /* Outputfile descriptor (fd driver). */
551
553
    char *wd;                   /* Working directory. */
552
554
    unsigned spawn_type;        /* Bitfield of ERTS_SPAWN_DRIVER | 
553
555
                                   ERTS_SPAWN_EXTERNAL | both*/ 
554
 
 
555
 
#ifdef _OSE_
556
 
    enum PROCESS_TYPE process_type;
557
 
    OSPRIORITY priority;
558
 
#endif /* _OSE_ */
559
 
 
560
556
} SysDriverOpts;
561
557
 
562
558
extern char *erts_default_arg0;
564
560
extern char os_type[];
565
561
 
566
562
extern int sys_init_time(void);
567
 
#if defined(ERTS_TIMER_THREAD)
568
 
#define erts_deliver_time()
569
 
#else
570
563
extern void erts_deliver_time(void);
571
 
#endif
572
564
extern void erts_time_remaining(SysTimeval *);
573
565
extern int erts_init_time_sup(void);
574
566
extern void erts_sys_init_float(void);
616
608
 
617
609
 
618
610
/*
619
 
 * System interfaces for startup/sae code (functions found in respective sys.c)
 
611
 * System interfaces for startup.
620
612
 */
621
613
 
622
614
 
633
625
extern void erl_sys_init(void);
634
626
extern void erl_sys_args(int *argc, char **argv);
635
627
extern void erl_sys_schedule(int);
636
 
#ifdef _OSE_
637
 
extern void erl_sys_init_final(void);
638
 
#else
639
 
void sys_tty_reset(void);
640
 
#endif
 
628
void sys_tty_reset(int);
641
629
 
642
 
EXTERN_FUNCTION(int, sys_max_files, (_VOID_));
 
630
int sys_max_files(void);
643
631
void sys_init_io(void);
644
632
Preload* sys_preloaded(void);
645
 
EXTERN_FUNCTION(unsigned char*, sys_preload_begin, (Preload*));
646
 
EXTERN_FUNCTION(void, sys_preload_end, (Preload*));
647
 
EXTERN_FUNCTION(int, sys_get_key, (int));
 
633
unsigned char* sys_preload_begin(Preload*);
 
634
void sys_preload_end(Preload*);
 
635
int sys_get_key(int);
648
636
void elapsed_time_both(unsigned long *ms_user, unsigned long *ms_sys, 
649
637
                       unsigned long *ms_user_diff, unsigned long *ms_sys_diff);
650
638
void wall_clock_elapsed_time_both(unsigned long *ms_total, 
661
649
                  Sint *hour, Sint *minute, Sint *second, int isdst);
662
650
void get_now(Uint*, Uint*, Uint*);
663
651
void get_sys_now(Uint*, Uint*, Uint*);
664
 
EXTERN_FUNCTION(void, set_break_quit, (void (*)(void), void (*)(void)));
 
652
void set_break_quit(void (*)(void), void (*)(void));
665
653
 
666
654
void os_flavor(char*, unsigned);
667
655
void os_version(int*, int*, int*);
701
689
#define ERTS_DEFAULT_MMAP_THRESHOLD  (128 * 1024)
702
690
#define ERTS_DEFAULT_MMAP_MAX        64
703
691
 
704
 
EXTERN_FUNCTION(int, sys_alloc_opt, (int, int));
 
692
int sys_alloc_opt(int, int);
705
693
 
706
694
typedef struct {
707
695
  Sint trim_threshold;
710
698
  Sint mmap_max;
711
699
} SysAllocStat;
712
700
 
713
 
EXTERN_FUNCTION(void, sys_alloc_stat, (SysAllocStat *));
 
701
void sys_alloc_stat(SysAllocStat *);
714
702
 
715
703
/* Block the whole system... */
716
704
 
734
722
} erts_activity_error_t;
735
723
 
736
724
typedef struct {
737
 
    erts_smp_atomic_t do_block;
 
725
    erts_smp_atomic32_t do_block;
738
726
    struct {
739
 
        erts_smp_atomic_t wait;
740
 
        erts_smp_atomic_t gc;
741
 
        erts_smp_atomic_t io;
 
727
        erts_smp_atomic32_t wait;
 
728
        erts_smp_atomic32_t gc;
 
729
        erts_smp_atomic32_t io;
742
730
    } in_activity;
743
731
} erts_system_block_state_t;
744
732
 
889
877
erts_smp_pending_system_block(void)
890
878
{
891
879
#ifdef ERTS_SMP
892
 
    return erts_smp_atomic_read(&erts_system_block_state.do_block);
 
880
    return (int) erts_smp_atomic32_read(&erts_system_block_state.do_block);
893
881
#else
894
882
    return 0;
895
883
#endif
925
913
    case ERTS_ACTIVITY_UNDEFINED:
926
914
        break;
927
915
    case ERTS_ACTIVITY_WAIT:
928
 
        erts_smp_atomic_dec(&erts_system_block_state.in_activity.wait);
 
916
        erts_smp_atomic32_dec(&erts_system_block_state.in_activity.wait);
929
917
        if (locked) {
930
918
            /* You are not allowed to leave activity waiting
931
919
             * without supplying the possibility to block
936
924
        }
937
925
        break;
938
926
    case ERTS_ACTIVITY_GC:
939
 
        erts_smp_atomic_dec(&erts_system_block_state.in_activity.gc);
 
927
        erts_smp_atomic32_dec(&erts_system_block_state.in_activity.gc);
940
928
        break;
941
929
    case ERTS_ACTIVITY_IO:
942
 
        erts_smp_atomic_dec(&erts_system_block_state.in_activity.io);
 
930
        erts_smp_atomic32_dec(&erts_system_block_state.in_activity.io);
943
931
        break;
944
932
    default:
945
933
        erts_set_activity_error(ERTS_ACT_ERR_LEAVE_UNKNOWN_ACTIVITY,
955
943
    case ERTS_ACTIVITY_UNDEFINED:
956
944
        break;
957
945
    case ERTS_ACTIVITY_WAIT:
958
 
        erts_smp_atomic_inc(&erts_system_block_state.in_activity.wait);
 
946
        erts_smp_atomic32_inc(&erts_system_block_state.in_activity.wait);
959
947
        break;
960
948
    case ERTS_ACTIVITY_GC:
961
 
        erts_smp_atomic_inc(&erts_system_block_state.in_activity.gc);
 
949
        erts_smp_atomic32_inc(&erts_system_block_state.in_activity.gc);
962
950
        break;
963
951
    case ERTS_ACTIVITY_IO:
964
 
        erts_smp_atomic_inc(&erts_system_block_state.in_activity.io);
 
952
        erts_smp_atomic32_inc(&erts_system_block_state.in_activity.io);
965
953
        break;
966
954
    default:
967
955
        erts_set_activity_error(ERTS_ACT_ERR_ENTER_UNKNOWN_ACTIVITY,
996
984
 
997
985
typedef erts_smp_atomic_t erts_refc_t;
998
986
 
999
 
ERTS_GLB_INLINE void erts_refc_init(erts_refc_t *refcp, long val);
1000
 
ERTS_GLB_INLINE void erts_refc_inc(erts_refc_t *refcp, long min_val);
1001
 
ERTS_GLB_INLINE long erts_refc_inctest(erts_refc_t *refcp, long min_val);
1002
 
ERTS_GLB_INLINE void erts_refc_dec(erts_refc_t *refcp, long min_val);
1003
 
ERTS_GLB_INLINE long erts_refc_dectest(erts_refc_t *refcp, long min_val);
1004
 
ERTS_GLB_INLINE void erts_refc_add(erts_refc_t *refcp, long diff, long min_val);
1005
 
ERTS_GLB_INLINE long erts_refc_read(erts_refc_t *refcp, long min_val);
 
987
ERTS_GLB_INLINE void erts_refc_init(erts_refc_t *refcp, erts_aint_t val);
 
988
ERTS_GLB_INLINE void erts_refc_inc(erts_refc_t *refcp, erts_aint_t min_val);
 
989
ERTS_GLB_INLINE erts_aint_t erts_refc_inctest(erts_refc_t *refcp,
 
990
                                              erts_aint_t min_val);
 
991
ERTS_GLB_INLINE void erts_refc_dec(erts_refc_t *refcp, erts_aint_t min_val);
 
992
ERTS_GLB_INLINE erts_aint_t erts_refc_dectest(erts_refc_t *refcp,
 
993
                                              erts_aint_t min_val);
 
994
ERTS_GLB_INLINE void erts_refc_add(erts_refc_t *refcp, erts_aint_t diff,
 
995
                                   erts_aint_t min_val);
 
996
ERTS_GLB_INLINE erts_aint_t erts_refc_read(erts_refc_t *refcp,
 
997
                                           erts_aint_t min_val);
1006
998
 
1007
999
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
1008
1000
 
1009
1001
ERTS_GLB_INLINE void
1010
 
erts_refc_init(erts_refc_t *refcp, long val)
 
1002
erts_refc_init(erts_refc_t *refcp, erts_aint_t val)
1011
1003
{
1012
1004
    erts_smp_atomic_init((erts_smp_atomic_t *) refcp, val);
1013
1005
}
1014
1006
 
1015
1007
ERTS_GLB_INLINE void
1016
 
erts_refc_inc(erts_refc_t *refcp, long min_val)
 
1008
erts_refc_inc(erts_refc_t *refcp, erts_aint_t min_val)
1017
1009
{
1018
1010
#ifdef ERTS_REFC_DEBUG
1019
 
    long val = erts_smp_atomic_inctest((erts_smp_atomic_t *) refcp);
 
1011
    erts_aint_t val = erts_smp_atomic_inctest((erts_smp_atomic_t *) refcp);
1020
1012
    if (val < min_val)
1021
1013
        erl_exit(ERTS_ABORT_EXIT,
1022
1014
                 "erts_refc_inc(): Bad refc found (refc=%ld < %ld)!\n",
1026
1018
#endif
1027
1019
}
1028
1020
 
1029
 
ERTS_GLB_INLINE long
1030
 
erts_refc_inctest(erts_refc_t *refcp, long min_val)
 
1021
ERTS_GLB_INLINE erts_aint_t
 
1022
erts_refc_inctest(erts_refc_t *refcp, erts_aint_t min_val)
1031
1023
{
1032
 
    long val = erts_smp_atomic_inctest((erts_smp_atomic_t *) refcp);
 
1024
    erts_aint_t val = erts_smp_atomic_inctest((erts_smp_atomic_t *) refcp);
1033
1025
#ifdef ERTS_REFC_DEBUG
1034
1026
    if (val < min_val)
1035
1027
        erl_exit(ERTS_ABORT_EXIT,
1040
1032
}
1041
1033
 
1042
1034
ERTS_GLB_INLINE void
1043
 
erts_refc_dec(erts_refc_t *refcp, long min_val)
 
1035
erts_refc_dec(erts_refc_t *refcp, erts_aint_t min_val)
1044
1036
{
1045
1037
#ifdef ERTS_REFC_DEBUG
1046
 
    long val = erts_smp_atomic_dectest((erts_smp_atomic_t *) refcp);
 
1038
    erts_aint_t val = erts_smp_atomic_dectest((erts_smp_atomic_t *) refcp);
1047
1039
    if (val < min_val)
1048
1040
        erl_exit(ERTS_ABORT_EXIT,
1049
1041
                 "erts_refc_dec(): Bad refc found (refc=%ld < %ld)!\n",
1053
1045
#endif
1054
1046
}
1055
1047
 
1056
 
ERTS_GLB_INLINE long
1057
 
erts_refc_dectest(erts_refc_t *refcp, long min_val)
 
1048
ERTS_GLB_INLINE erts_aint_t
 
1049
erts_refc_dectest(erts_refc_t *refcp, erts_aint_t min_val)
1058
1050
{
1059
 
    long val = erts_smp_atomic_dectest((erts_smp_atomic_t *) refcp);
 
1051
    erts_aint_t val = erts_smp_atomic_dectest((erts_smp_atomic_t *) refcp);
1060
1052
#ifdef ERTS_REFC_DEBUG
1061
1053
    if (val < min_val)
1062
1054
        erl_exit(ERTS_ABORT_EXIT,
1067
1059
}
1068
1060
 
1069
1061
ERTS_GLB_INLINE void
1070
 
erts_refc_add(erts_refc_t *refcp, long diff, long min_val)
 
1062
erts_refc_add(erts_refc_t *refcp, erts_aint_t diff, erts_aint_t min_val)
1071
1063
{
1072
1064
#ifdef ERTS_REFC_DEBUG
1073
 
    long val = erts_smp_atomic_addtest((erts_smp_atomic_t *) refcp, diff);
 
1065
    erts_aint_t val = erts_smp_atomic_addtest((erts_smp_atomic_t *) refcp, diff);
1074
1066
    if (val < min_val)
1075
1067
        erl_exit(ERTS_ABORT_EXIT,
1076
1068
                 "erts_refc_add(%ld): Bad refc found (refc=%ld < %ld)!\n",
1080
1072
#endif
1081
1073
}
1082
1074
 
1083
 
ERTS_GLB_INLINE long
1084
 
erts_refc_read(erts_refc_t *refcp, long min_val)
 
1075
ERTS_GLB_INLINE erts_aint_t
 
1076
erts_refc_read(erts_refc_t *refcp, erts_aint_t min_val)
1085
1077
{
1086
 
    long val = erts_smp_atomic_read((erts_smp_atomic_t *) refcp);
 
1078
    erts_aint_t val = erts_smp_atomic_read((erts_smp_atomic_t *) refcp);
1087
1079
#ifdef ERTS_REFC_DEBUG
1088
1080
    if (val < min_val)
1089
1081
        erl_exit(ERTS_ABORT_EXIT,
1099
1091
extern int erts_use_kernel_poll;
1100
1092
#endif
1101
1093
 
1102
 
void elib_ensure_initialized(void);
1103
 
 
1104
 
 
1105
 
#if (defined(VXWORKS) || defined(_OSE_))
 
1094
#if defined(VXWORKS)
1106
1095
/* NOTE! sys_calloc2 does not exist on other 
1107
1096
   platforms than VxWorks and OSE */
1108
 
EXTERN_FUNCTION(void*, sys_calloc2, (Uint, Uint));
 
1097
void* sys_calloc2(Uint, Uint);
1109
1098
#endif /* VXWORKS || OSE */
1110
1099
 
1111
1100
 
1145
1134
 
1146
1135
/* Standard set of integer macros  .. */
1147
1136
 
1148
 
#define get_int64(s) ((((unsigned char*) (s))[0] << 56) | \
1149
 
                      (((unsigned char*) (s))[1] << 48) | \
1150
 
                      (((unsigned char*) (s))[2] << 40) | \
1151
 
                      (((unsigned char*) (s))[3] << 32) | \
1152
 
                      (((unsigned char*) (s))[4] << 24) | \
1153
 
                      (((unsigned char*) (s))[5] << 16) | \
1154
 
                      (((unsigned char*) (s))[6] << 8)  | \
1155
 
                      (((unsigned char*) (s))[7]))
 
1137
#define get_int64(s) (((Uint64)(((unsigned char*) (s))[0]) << 56) | \
 
1138
                      (((Uint64)((unsigned char*) (s))[1]) << 48) | \
 
1139
                      (((Uint64)((unsigned char*) (s))[2]) << 40) | \
 
1140
                      (((Uint64)((unsigned char*) (s))[3]) << 32) | \
 
1141
                      (((Uint64)((unsigned char*) (s))[4]) << 24) | \
 
1142
                      (((Uint64)((unsigned char*) (s))[5]) << 16) | \
 
1143
                      (((Uint64)((unsigned char*) (s))[6]) << 8)  | \
 
1144
                      (((Uint64)((unsigned char*) (s))[7])))
1156
1145
 
1157
1146
#define put_int64(i, s) do {((char*)(s))[0] = (char)((Sint64)(i) >> 56) & 0xff;\
1158
1147
                            ((char*)(s))[1] = (char)((Sint64)(i) >> 48) & 0xff;\
1175
1164
                            ((char*)(s))[3] = (char)(i)         & 0xff;} \
1176
1165
                        while (0)
1177
1166
 
 
1167
#define get_int24(s) ((((unsigned char*) (s))[0] << 16) | \
 
1168
                      (((unsigned char*) (s))[1] << 8)  | \
 
1169
                      (((unsigned char*) (s))[2]))
 
1170
 
 
1171
#define put_int24(i, s) do {((char*)(s))[0] = (char)((i) >> 16) & 0xff;  \
 
1172
                            ((char*)(s))[1] = (char)((i) >> 8)  & 0xff;  \
 
1173
                            ((char*)(s))[2] = (char)(i)         & 0xff;} \
 
1174
                        while (0)
 
1175
 
1178
1176
#define get_int16(s) ((((unsigned char*)  (s))[0] << 8) | \
1179
1177
                      (((unsigned char*)  (s))[1]))
1180
1178
 
1188
1186
 
1189
1187
#define put_int8(i, s) do {((unsigned char*)(s))[0] = (i) & 0xff;} while (0)
1190
1188
 
 
1189
 
1191
1190
/*
1192
1191
 * Use DEBUGF as you would use printf, but use double parentheses:
1193
1192
 *
1197
1196
 */
1198
1197
 
1199
1198
#ifdef DEBUG
1200
 
EXTERN_FUNCTION(void, erl_debug, (char* format, ...));
1201
 
EXTERN_FUNCTION(void, erl_bin_write, (unsigned char *, int, int));
 
1199
void erl_debug(char* format, ...);
 
1200
void erl_bin_write(unsigned char *, int, int);
1202
1201
 
1203
1202
#  define DEBUGF(x) erl_debug x
1204
1203
#else
1252
1251
 
1253
1252
#endif
1254
1253
 
 
1254
/************************************************************************
 
1255
 * Find out the native filename encoding of the process (look at locale of 
 
1256
 * Unix processes and just do UTF16 on windows 
 
1257
 ************************************************************************/
 
1258
#define ERL_FILENAME_UNKNOWN 0
 
1259
#define ERL_FILENAME_LATIN1 1
 
1260
#define ERL_FILENAME_UTF8 2
 
1261
#define ERL_FILENAME_UTF8_MAC 3
 
1262
#define ERL_FILENAME_WIN_WCHAR 4
 
1263
 
 
1264
int erts_get_native_filename_encoding(void);
 
1265
/* The set function is only to be used by erl_init! */
 
1266
void erts_set_user_requested_filename_encoding(int encoding); 
 
1267
int erts_get_user_requested_filename_encoding(void);
 
1268
 
 
1269
void erts_init_sys_common_misc(void);
1255
1270
 
1256
1271
#endif
1257
1272