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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_vm.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:
18
18
#ifndef __ERL_VM_H__
19
19
#define __ERL_VM_H__
20
20
 
 
21
#if defined(HYBRID)
 
22
/* # define CHECK_FOR_HOLES */
 
23
#endif
 
24
 
 
25
#if defined(DEBUG) && !defined(CHECK_FOR_HOLES)
 
26
# define CHECK_FOR_HOLES
 
27
#endif
 
28
 
 
29
 
21
30
/* #define HEAP_FRAG_ELIM_TEST 1 */
22
31
 
23
 
#if defined(HEAP_FRAG_ELIM_TEST) && (defined(HIPE) || defined(SHARED_HEAP))
24
 
#  undef HEAP_FRAG_ELIM_TEST
 
32
#if defined(HYBRID)
 
33
/* #  define INCREMENTAL 1    */ /* Incremental garbage collection */
 
34
/* #  define INC_TIME_BASED 1 */ /* Time-based incremental GC (vs Work-based) */
 
35
#endif
 
36
 
 
37
#if defined(HEAP_FRAG_ELIM_TEST) && defined(HIPE)
 
38
#error Heap-fragment elimination (nofrag) cannot be combined with HIPE yet
25
39
#endif
26
40
 
27
41
#define BEAM 1
28
42
#define EMULATOR "BEAM"
29
43
#define SEQ_TRACE 1
30
44
 
31
 
#define CONTEXT_REDS 1000       /* Swap process out after this number       */
32
 
#define MAX_ARG 256             /* Max number of arguments allowed */
 
45
#define CONTEXT_REDS 2000       /* Swap process out after this number */
 
46
#define MAX_ARG 256             /* Max number of arguments allowed */
33
47
#define MAX_REG 1024            /* Max number of x(N) registers used */
34
48
 
35
 
#define INPUT_REDUCTIONS   (2 * CONTEXT_REDS)
36
 
 
37
 
#define H_DEFAULT_SIZE  233     /* default (heap + stack) min size */
38
 
 
39
 
#ifdef SHARED_HEAP
40
 
#define S_DEFAULT_SIZE  233     /* default stack size */
41
 
#define SH_DEFAULT_SIZE 121393  /* default shared heap min size */
42
 
#endif
43
 
 
44
 
#define CP_SIZE                 1
 
49
/*
 
50
 * The new arithmetic operations need some extra X registers in the register array.
 
51
 */
 
52
#define ERTS_X_REGS_ALLOCATED (MAX_REG+2)
 
53
 
 
54
#ifndef ERTS_SMP
 
55
#define INPUT_REDUCTIONS (2 * CONTEXT_REDS)
 
56
#endif
 
57
 
 
58
#define H_DEFAULT_SIZE  233     /* default (heap + stack) min size */
 
59
 
 
60
#ifdef HYBRID
 
61
#  define SH_DEFAULT_SIZE  2629425 /* default message area min size */
 
62
#endif
 
63
 
 
64
#ifdef INCREMENTAL
 
65
#  define INC_NoPAGES       256   /* Number of pages in the old generation */
 
66
#  define INC_PAGESIZE      32768 /* The size of each page */
 
67
#  define INC_STORAGE_SIZE  1024  /* The size of gray stack and similar */
 
68
#endif
 
69
 
 
70
#define CP_SIZE 1
 
71
 
 
72
#ifdef DEBUG
 
73
/*
 
74
 * Debug HAlloc that initialize all memory to bad things.
 
75
 *
 
76
 * To get information about where memory is allocated, insert the two
 
77
 * lines below directly after the memset line and use the flag +va.
 
78
 *
 
79
         VERBOSE(DEBUG_ALLOCATION,("HAlloc @ 0x%08lx (%d) %s:%d\n",     \
 
80
                 (unsigned long)HEAP_TOP(p),(sz),__FILE__,__LINE__)),   \
 
81
 */
 
82
#ifdef CHECK_FOR_HOLES
 
83
#define HAlloc(p, sz)                                           \
 
84
    (ASSERT_EXPR((sz) >= 0),                                    \
 
85
     ((((HEAP_LIMIT(p) - HEAP_TOP(p)) < (sz)))                  \
 
86
      ? erts_heap_alloc((p),(sz))                               \
 
87
      : (erts_set_hole_marker(HEAP_TOP(p), (sz)),               \
 
88
         HEAP_TOP(p) = HEAP_TOP(p) + (sz), HEAP_TOP(p) - (sz))))
 
89
#else
 
90
#define HAlloc(p, sz)                                                   \
 
91
    (ASSERT_EXPR((sz) >= 0),                                            \
 
92
     ((((HEAP_LIMIT(p) - HEAP_TOP(p)) < (sz)))                          \
 
93
      ? erts_heap_alloc((p),(sz))                                       \
 
94
      : (memset(HEAP_TOP(p),DEBUG_BAD_BYTE,(sz)*sizeof(Eterm*)),        \
 
95
         HEAP_TOP(p) = HEAP_TOP(p) + (sz), HEAP_TOP(p) - (sz))))
 
96
#endif
 
97
#else
45
98
 
46
99
/*
47
100
 * Allocate heap memory, first on the ordinary heap;
48
101
 * failing that, in a heap fragment.
49
102
 */
50
 
#define HAlloc(p, sz)                                   \
51
 
  (ASSERT_EXPR((sz) >= 0),                              \
52
 
   ((((HEAP_LIMIT(p) - HEAP_TOP(p)) <= (sz)))           \
53
 
    ? erts_heap_alloc((p),(sz))                         \
54
 
    : (HEAP_TOP(p) = HEAP_TOP(p) + (sz), HEAP_TOP(p) - (sz))))
55
 
 
56
 
#define HRelease(p, ptr)                                \
57
 
  if (HEAP_START(p) <= (ptr) && (ptr) < HEAP_TOP(p)) {  \
58
 
      HEAP_TOP(p) = (ptr);                              \
59
 
  } else {}
60
 
 
61
 
#define HeapWordsLeft(p)                                \
62
 
  (HEAP_LIMIT(p) - HEAP_TOP(p))
63
 
 
64
 
#ifdef SHARED_HEAP
65
 
#  define ARITH_HEAP(p)     erts_global_arith_heap
66
 
#  define ARITH_AVAIL(p)    erts_global_arith_avail
67
 
#  define ARITH_LOWEST_HTOP(p) erts_global_arith_lowest_htop
68
 
#  define ARITH_CHECK_ME(p) erts_global_arith_check_me
69
 
extern Eterm* erts_global_arith_heap;
70
 
extern Uint erts_global_arith_avail;
71
 
extern Eterm* erts_global_arith_lowest_htop;
72
 
#  ifdef DEBUG
73
 
extern Eterm* erts_global_arith_check_me;
74
 
#  endif
75
 
#else
76
 
#  define ARITH_HEAP(p)     (p)->arith_heap
77
 
#  define ARITH_AVAIL(p)    (p)->arith_avail
78
 
#  define ARITH_LOWEST_HTOP(p) (p)->arith_lowest_htop
 
103
#define HAlloc(p, sz)                                                   \
 
104
    (ASSERT_EXPR((sz) >= 0),                                            \
 
105
     ((((HEAP_LIMIT(p) - HEAP_TOP(p)) < (sz)))                          \
 
106
      ? erts_heap_alloc((p),(sz))                                       \
 
107
      : (HEAP_TOP(p) = HEAP_TOP(p) + (sz), HEAP_TOP(p) - (sz))))
 
108
 
 
109
#endif /* DEBUG */
 
110
 
 
111
#define HRelease(p, endp, ptr)                                  \
 
112
  if ((ptr) == (endp)) {                                        \
 
113
     ;                                                          \
 
114
  } else if (HEAP_START(p) <= (ptr) && (ptr) < HEAP_TOP(p)) {   \
 
115
     HEAP_TOP(p) = (ptr);                                       \
 
116
  } else {                                                      \
 
117
     erts_arith_shrink(p, ptr);                                 \
 
118
  }
 
119
 
 
120
#define HeapWordsLeft(p) (HEAP_LIMIT(p) - HEAP_TOP(p))
 
121
 
 
122
#define ARITH_HEAP(p)     (p)->arith_heap
 
123
#define ARITH_AVAIL(p)    (p)->arith_avail
 
124
#ifdef DEBUG
79
125
#  define ARITH_CHECK_ME(p) (p)->arith_check_me
80
126
#endif
81
127
 
82
128
/* Allocate memory on secondary arithmetic heap. */
83
129
 
84
 
#if defined(DEBUG)
85
 
#  define ARITH_MARKER 0xaf5e78cc
 
130
#if defined(DEBUG) || defined(CHECK_FOR_HOLES)
 
131
# define ERTS_HOLE_MARKER (((0xcafebabeUL << 24) << 8) | 0xaf5e78ccUL)
 
132
#endif
 
133
 
 
134
#if defined(DEBUG)
 
135
# define ARITH_MARKER (((0xcafebabeUL << 24) << 8) | 0xaf5e78ccUL)
 
136
#endif
 
137
 
 
138
#if !defined(HEAP_FRAG_ELIM_TEST)
 
139
#if defined(DEBUG)
86
140
#  define ArithCheck(p) \
87
141
      ASSERT(ARITH_CHECK_ME(p)[0] == ARITH_MARKER);
88
 
#  define ArithAlloc(p, need) \
89
 
   (ASSERT_EXPR((need) >= 0), \
90
 
    ((ARITH_AVAIL(p) < (need)) ? \
91
 
     erts_arith_alloc((p), (p)->htop, (need)) : \
92
 
     ((ARITH_HEAP(p) += (need)), (ARITH_AVAIL(p) -= (need)), \
93
 
      (ARITH_CHECK_ME(p) = ARITH_HEAP(p)), \
 
142
#  define ArithAlloc(p, need)                                   \
 
143
   (ASSERT_EXPR((need) >= 0),                                   \
 
144
    ((ARITH_AVAIL(p) < (need)) ?                                \
 
145
     erts_heap_alloc((p), (need)) :                             \
 
146
     ((ARITH_HEAP(p) += (need)), (ARITH_AVAIL(p) -= (need)),    \
 
147
      (ARITH_CHECK_ME(p) = ARITH_HEAP(p)),                      \
94
148
      (ARITH_HEAP(p) - (need)))))
95
149
#else
96
150
#  define ArithCheck(p)
97
 
#  define ArithAlloc(p, need) \
98
 
    ((ARITH_AVAIL(p) < (need)) ? \
99
 
      erts_arith_alloc((p), (p)->htop, (need)) : \
100
 
      ((ARITH_HEAP(p) += (need)), \
101
 
       (ARITH_AVAIL(p) -= (need)), \
 
151
#  define ArithAlloc(p, need)                   \
 
152
    ((ARITH_AVAIL(p) < (need)) ?                \
 
153
      erts_heap_alloc((p), (need)) :            \
 
154
      ((ARITH_HEAP(p) += (need)),               \
 
155
       (ARITH_AVAIL(p) -= (need)),              \
102
156
       (ARITH_HEAP(p) - (need))))
103
157
#endif
 
158
#endif
104
159
 
105
160
/*
106
161
 * Description for each instruction (defined here because the name and
109
164
 
110
165
typedef struct op_entry {
111
166
   char* name;                  /* Name of instruction. */
112
 
   unsigned mask[2];            /* Signature mask. */
 
167
   unsigned mask[3];            /* Signature mask. */
113
168
   int sz;                      /* Number of loaded words. */
114
169
   char* pack;                  /* Instructions for packing engine. */
115
170
   char* sign;                  /* Signature string. */
119
174
extern OpEntry opc[];           /* Description of all instructions. */
120
175
extern int num_instructions;    /* Number of instruction in opc[]. */
121
176
 
122
 
/* some constants for various  table sizes etc */
 
177
/* some constants for various table sizes etc */
123
178
 
124
179
#define ATOM_TEXT_SIZE  32768   /* Increment for allocating atom text space */
125
180
 
126
 
/*
127
 
 * Temporary buffer used in a lot of places.  In some cases, this size
128
 
 * will be an absolute resource limit (buffers for pathnames, for instance).
129
 
 * In others, memory must be allocated if the buffer is not enough.
130
 
 * 
131
 
 * Decreasing the size of it below 16384 is not allowed.
132
 
 */
133
 
 
134
 
#define TMP_BUF_SIZE 65536
135
 
 
136
181
#define ITIME 100               /* Number of milliseconds per clock tick    */
137
 
#define BG_PROPORTION 8         /* Do bg processes after this # fg          */
138
182
#define MAX_PORT_LINK 8         /* Maximum number of links to a port        */
139
183
 
140
184
extern int H_MIN_SIZE;          /* minimum (heap + stack) */
155
199
#define make_signed_24(x,y,z) ((sint32) (((x) << 24) | ((y) << 16) | ((z) << 8)) >> 8)
156
200
#define make_signed_32(x3,x2,x1,x0) ((sint32) (((x3) << 24) | ((x2) << 16) | ((x1) << 8) | (x0)))
157
201
 
158
 
#ifdef DEBUG
159
 
#define VERBOSE(x) do { if (verbose) x } while(0)
160
 
#else
161
 
#define VERBOSE(x)
162
 
#endif
163
 
 
164
 
int big_to_double(Eterm x, double* resp);
165
 
 
166
202
#include "erl_term.h"
167
203
 
168
204
#endif  /* __ERL_VM_H__ */