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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_bits.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:
16
16
 *     $Id$
17
17
 */
18
18
 
 
19
#ifndef __ERL_BITS_H__
 
20
#define __ERL_BITS_H__
 
21
 
19
22
/*
20
23
 * This structure represents a binary to be matched.
21
24
 */
23
26
typedef struct erl_bin_match_buffer {
24
27
    Eterm orig;                 /* Original binary term. */
25
28
    byte* base;                 /* Current position in binary. */
26
 
    unsigned offset;            /* Offset in bits. */
 
29
    Uint offset;                /* Offset in bits. */
27
30
    size_t size;                /* Size of binary in bits. */
28
31
} ErlBinMatchBuffer;
29
32
 
30
 
#define erts_InitMatchBuf(Src, Fail)                            \
31
 
do {                                                            \
32
 
    Eterm _Bin = (Src);                                         \
33
 
    if (!is_binary(_Bin)) {                                     \
34
 
        Fail;                                                   \
35
 
    } else {                                                    \
36
 
        Eterm _orig;                                            \
37
 
        Uint _offs;                                             \
38
 
                                                                \
39
 
        GET_REAL_BIN(_Bin, _orig, _offs);                       \
40
 
        erts_mb.orig = _orig;                                   \
41
 
        erts_mb.base = binary_bytes(_orig);                     \
42
 
        erts_mb.offset = 8 * _offs;                             \
43
 
        erts_mb.size = binary_size(_Bin) * 8 + erts_mb.offset;  \
44
 
    }                                                           \
 
33
struct erl_bits_state {
 
34
    /*
 
35
     * Used for matching.
 
36
     */
 
37
    ErlBinMatchBuffer erts_mb_; /* Current match buffer. */
 
38
    ErlBinMatchBuffer erts_save_mb_[MAX_REG]; /* Saved match buffers. */
 
39
    /*
 
40
     * Used for building binaries.
 
41
     */
 
42
    byte *byte_buf_;
 
43
    int byte_buf_len_;
 
44
    /*
 
45
     * Used for building binaries using the new instruction set.
 
46
     */
 
47
    byte* erts_current_bin_;    /* Pointer to beginning of current binary. */
 
48
    /*
 
49
     * Offset in bits into the current binary (new instruction set) or
 
50
     * buffer (old instruction set).
 
51
     */
 
52
    unsigned erts_bin_offset_;
 
53
    /*
 
54
     * The following variables are only used for building binaries
 
55
     * using the old instructions.
 
56
     */
 
57
    byte* erts_bin_buf_;
 
58
    unsigned erts_bin_buf_len_;
 
59
};
 
60
 
 
61
typedef struct erl_bin_match_struct{
 
62
  Eterm thing_word;
 
63
  ErlBinMatchBuffer mb; /* Present match buffer */
 
64
  Eterm save_offset[1]; /* Saved offsets */
 
65
} ErlBinMatchState;
 
66
 
 
67
#define ERL_BIN_MATCHSTATE_SIZE(_Max) ((sizeof(ErlBinMatchState) + (_Max-1)*sizeof(Eterm))/sizeof(Eterm)) 
 
68
#define HEADER_BIN_MATCHSTATE(_Max) _make_header(ERL_BIN_MATCHSTATE_SIZE(_Max)-1, _TAG_HEADER_BIN_MATCHSTATE)
 
69
 
 
70
#define make_matchstate(_Ms) make_boxed((Eterm*)(_Ms))  
 
71
#define ms_matchbuffer(_Ms) &(((ErlBinMatchState*)(_Ms - TAG_PRIMARY_BOXED))->mb)
 
72
 
 
73
 
 
74
#if defined(ERTS_SMP)
 
75
#define ERL_BITS_REENTRANT
 
76
#else
 
77
/* uncomment to test the reentrant API in the non-SMP runtime system */
 
78
/* #define ERL_BITS_REENTRANT */
 
79
#endif
 
80
 
 
81
#ifdef ERL_BITS_REENTRANT
 
82
 
 
83
/*
 
84
 * Reentrant API with the state passed as a parameter.
 
85
 * (Except when the current Process* already is a parameter.)
 
86
 */
 
87
#ifdef ERTS_SMP
 
88
/* the state resides in the current process' scheduler data */
 
89
#define ERL_BITS_DECLARE_STATEP                 struct erl_bits_state *EBS
 
90
#define ERL_BITS_RELOAD_STATEP(P)               do{EBS = &(P)->scheduler_data->erl_bits_state;}while(0)
 
91
#define ERL_BITS_DEFINE_STATEP(P)               struct erl_bits_state *EBS = &(P)->scheduler_data->erl_bits_state
 
92
#else
 
93
/* reentrant API but with a hidden single global state, for testing only */
 
94
extern struct erl_bits_state ErlBitsState_;
 
95
#define ERL_BITS_DECLARE_STATEP                 struct erl_bits_state *EBS = &ErlBitsState_
 
96
#define ERL_BITS_RELOAD_STATEP(P)               do{}while(0)
 
97
#define ERL_BITS_DEFINE_STATEP(P)               ERL_BITS_DECLARE_STATEP
 
98
#endif
 
99
#define ErlBitsState                            (*EBS)
 
100
 
 
101
#define ERL_BITS_PROTO_0                        struct erl_bits_state *EBS
 
102
#define ERL_BITS_PROTO_1(PARM1)                 struct erl_bits_state *EBS, PARM1
 
103
#define ERL_BITS_PROTO_2(PARM1,PARM2)           struct erl_bits_state *EBS, PARM1, PARM2
 
104
#define ERL_BITS_PROTO_3(PARM1,PARM2,PARM3)     struct erl_bits_state *EBS, PARM1, PARM2, PARM3
 
105
#define ERL_BITS_ARGS_0                         EBS
 
106
#define ERL_BITS_ARGS_1(ARG1)                   EBS, ARG1
 
107
#define ERL_BITS_ARGS_2(ARG1,ARG2)              EBS, ARG1, ARG2
 
108
#define ERL_BITS_ARGS_3(ARG1,ARG2,ARG3)         EBS, ARG1, ARG2, ARG3
 
109
 
 
110
#else   /* ERL_BITS_REENTRANT */
 
111
 
 
112
/*
 
113
 * Non-reentrant API with a single global state.
 
114
 */
 
115
extern struct erl_bits_state ErlBitsState;
 
116
#define ERL_BITS_DECLARE_STATEP                 /*empty*/
 
117
#define ERL_BITS_RELOAD_STATEP(P)               do{}while(0)
 
118
#define ERL_BITS_DEFINE_STATEP(P)               /*empty*/
 
119
 
 
120
#define ERL_BITS_PROTO_0                        void
 
121
#define ERL_BITS_PROTO_1(PARM1)                 PARM1
 
122
#define ERL_BITS_PROTO_2(PARM1,PARM2)           PARM1, PARM2
 
123
#define ERL_BITS_PROTO_3(PARM1,PARM2,PARM3)     PARM1, PARM2, PARM3
 
124
#define ERL_BITS_ARGS_0                         /*empty*/
 
125
#define ERL_BITS_ARGS_1(ARG1)                   ARG1
 
126
#define ERL_BITS_ARGS_2(ARG1,ARG2)              ARG1, ARG2
 
127
#define ERL_BITS_ARGS_3(ARG1,ARG2,ARG3)         ARG1, ARG2, ARG3
 
128
 
 
129
#endif  /* ERL_BITS_REENTRANT */
 
130
 
 
131
#if !defined(HEAP_FRAG_ELIM_TEST)
 
132
 
 
133
#define erts_mb                 (ErlBitsState.erts_mb_)
 
134
#define erts_save_mb            (ErlBitsState.erts_save_mb_)
 
135
#define erts_bin_offset         (ErlBitsState.erts_bin_offset_)
 
136
#define erts_current_bin        (ErlBitsState.erts_current_bin_)
 
137
#define erts_bin_buf            (ErlBitsState.erts_bin_buf_)
 
138
#define erts_bin_buf_len        (ErlBitsState.erts_bin_buf_len_)
 
139
 
 
140
#define erts_InitMatchBuf(Src, Fail)                                    \
 
141
do {                                                                    \
 
142
    Eterm _Bin = (Src);                                                 \
 
143
    if (!is_binary(_Bin)) {                                             \
 
144
        Fail;                                                           \
 
145
    } else {                                                            \
 
146
        Eterm _orig;                                                    \
 
147
        Uint _offs;                                                     \
 
148
        Uint _bitoffs;                                                  \
 
149
        Uint _bitsize;                                                  \
 
150
                                                                        \
 
151
        ERTS_GET_REAL_BIN(_Bin, _orig, _offs, _bitoffs, _bitsize);      \
 
152
        erts_mb.orig = _orig;                                           \
 
153
        erts_mb.base = binary_bytes(_orig);                             \
 
154
        erts_mb.offset = 8 * _offs+_bitoffs;                            \
 
155
        erts_mb.size = binary_size(_Bin) * 8 + erts_mb.offset+_bitsize; \
 
156
    }                                                                   \
45
157
} while (0)
 
158
#endif
 
159
 
 
160
#define copy_binary_to_buffer(DstBuffer, DstBufOffset, SrcBuffer, SrcBufferOffset, NumBits) \
 
161
  do {                                                                                      \
 
162
    if (BIT_OFFSET(DstBufOffset) == 0 && (SrcBufferOffset == 0) &&                          \
 
163
        (BIT_OFFSET(NumBits)==0)) {                                                         \
 
164
      sys_memcpy(DstBuffer+BYTE_OFFSET(DstBufOffset),                                       \
 
165
                 SrcBuffer, NBYTES(NumBits));                                               \
 
166
    } else {                                                                                \
 
167
      erts_copy_bits(SrcBuffer, SrcBufferOffset, 1,                                         \
 
168
        (byte*)DstBuffer, DstBufOffset, 1, NumBits);                                        \
 
169
    }                                                                                       \
 
170
  }  while (0)
46
171
 
47
172
void erts_init_bits(void);      /* Initialization once. */
 
173
#ifdef ERTS_SMP
 
174
void erts_bits_init_state(ERL_BITS_PROTO_0);
 
175
void erts_bits_destroy_state(ERL_BITS_PROTO_0);
 
176
#endif
 
177
 
 
178
 
 
179
/*
 
180
 * NBYTES(x) returns the number of bytes needed to store x bits.
 
181
 */
 
182
 
 
183
#define NBYTES(x)  (((x) + 7) >> 3) 
 
184
#define BYTE_OFFSET(ofs) ((unsigned) (ofs) >> 3)
 
185
#define BIT_OFFSET(ofs) ((ofs) & 7)
 
186
 
 
187
/*
 
188
 * Return number of Eterm words needed for allocation with HAlloc(),
 
189
 * given a number of bytes.
 
190
 */
 
191
#define WSIZE(n) ((n + sizeof(Eterm) - 1) / sizeof(Eterm))
48
192
 
49
193
/*
50
194
 * Binary matching.
51
195
 */
52
196
 
53
 
extern ErlBinMatchBuffer erts_mb;
54
 
extern ErlBinMatchBuffer erts_save_mb[MAX_REG];
55
 
 
56
 
int erts_bs_start_match(Eterm Bin);
57
 
int erts_bs_skip_bits(Uint num_bits);
58
 
int erts_bs_skip_bits_all(void);
59
 
int erts_bs_test_tail(Uint num_bits);
60
 
void erts_bs_save(int index);
61
 
void erts_bs_restore(int index);
 
197
int erts_bs_start_match(ERL_BITS_PROTO_1(Eterm Bin));
 
198
int erts_bs_skip_bits(ERL_BITS_PROTO_1(Uint num_bits));
 
199
int erts_bs_skip_bits_all(ERL_BITS_PROTO_0);
 
200
int erts_bs_test_tail(ERL_BITS_PROTO_1(Uint num_bits));
 
201
void erts_bs_save(ERL_BITS_PROTO_1(int index));
 
202
void erts_bs_restore(ERL_BITS_PROTO_1(int index));
62
203
Eterm erts_bs_get_integer(Process *p, Uint num_bits, unsigned flags);
63
204
Eterm erts_bs_get_binary(Process *p, Uint num_bits, unsigned flags);
64
205
Eterm erts_bs_get_float(Process *p, Uint num_bits, unsigned flags);
65
206
Eterm erts_bs_get_binary_all(Process *p);
66
207
 
67
 
/*
68
 
 * Binary construction.
69
 
 */
70
 
 
71
 
extern byte* erts_bin_buf;
72
 
extern unsigned erts_bin_buf_len;
73
 
extern unsigned erts_bin_offset;
74
 
 
75
 
void erts_bs_init(void);
 
208
 
 
209
Eterm erts_bs_start_match_2(Process *p, Eterm Bin, Uint Max);
 
210
void erts_bs_save_2(int index, ErlBinMatchState* ms);
 
211
void erts_bs_restore_2(int index, ErlBinMatchState* ms);
 
212
Eterm erts_bs_get_integer_2(Process *p, Uint num_bits, unsigned flags, ErlBinMatchBuffer* mb);
 
213
Eterm erts_bs_get_binary_2(Process *p, Uint num_bits, unsigned flags, ErlBinMatchBuffer* mb);
 
214
Eterm erts_bs_get_float_2(Process *p, Uint num_bits, unsigned flags, ErlBinMatchBuffer* mb);
 
215
Eterm erts_bs_get_binary_all_2(Process *p, ErlBinMatchBuffer* mb);
 
216
 
 
217
/*
 
218
 * Binary construction, new instruction set.
 
219
 */
 
220
 
 
221
int erts_new_bs_put_integer(ERL_BITS_PROTO_3(Eterm Integer, Uint num_bits, unsigned flags));
 
222
int erts_new_bs_put_binary(ERL_BITS_PROTO_2(Eterm Bin, Uint num_bits));
 
223
int erts_new_bs_put_binary_all(ERL_BITS_PROTO_1(Eterm Bin));
 
224
int erts_new_bs_put_float(Process *c_p, Eterm Float, Uint num_bits, int flags);
 
225
void erts_new_bs_put_string(ERL_BITS_PROTO_2(byte* iptr, Uint num_bytes));
 
226
 
 
227
/*
 
228
 * Binary construction, old instruction set.
 
229
 */
 
230
 
 
231
void erts_bs_init(ERL_BITS_PROTO_0);
76
232
Eterm erts_bs_final(Process* p);
 
233
Eterm erts_bs_final2(Process* p, Eterm bin);
77
234
Uint erts_bits_bufs_size(void);
78
 
int erts_bs_put_integer(Eterm Integer, Uint num_bits, unsigned flags);
79
 
int erts_bs_put_binary(Eterm Bin, Uint num_bits);
80
 
int erts_bs_put_binary_all(Eterm Bin);
81
 
int erts_bs_put_float(Eterm Float, Uint num_bits, int flags);
82
 
void erts_bs_put_string(byte* iptr, Uint num_bytes);
83
 
 
84
 
/*
85
 
 * Flags for bs_get_* instructions.
 
235
int erts_bs_put_integer(ERL_BITS_PROTO_3(Eterm Integer, Uint num_bits, unsigned flags));
 
236
int erts_bs_put_binary(ERL_BITS_PROTO_2(Eterm Bin, Uint num_bits));
 
237
int erts_bs_put_binary_all(ERL_BITS_PROTO_1(Eterm Bin));
 
238
int erts_bs_put_float(Process *c_p, Eterm Float, Uint num_bits, int flags);
 
239
void erts_bs_put_string(ERL_BITS_PROTO_2(byte* iptr, Uint num_bytes));
 
240
 
 
241
/*
 
242
 * Common utilities.
 
243
 */
 
244
void erts_copy_bits(byte* src, size_t soffs, int sdir,
 
245
                    byte* dst, size_t doffs,int ddir, size_t n);        
 
246
int erts_cmp_bits(byte* a_ptr, size_t a_offs, byte* b_ptr, size_t b_offs, size_t size); 
 
247
 
 
248
/*
 
249
 * Flags for bs_get_* / bs_put_* / bs_init* instructions.
86
250
 */
87
251
 
88
252
#define BSF_ALIGNED 1           /* Field is guaranteed to be byte-aligned. */
90
254
#define BSF_SIGNED 4            /* Field is signed (otherwise unsigned). */
91
255
#define BSF_EXACT 8             /* Size in bs_init is exact. */
92
256
#define BSF_NATIVE 16           /* Native endian. */
 
257
 
 
258
#endif /* __ERL_BITS_H__ */