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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/big.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:
32
32
 
33
33
/* #define DEBUG_OP */          /* Count arithmetic operations */
34
34
 
 
35
#if defined(ARCH_64)
 
36
#define D_EXP      32
 
37
#else
35
38
#define D_EXP      16
36
 
#define D_BASE     (1<<D_EXP)
 
39
#endif
 
40
#define D_BASE     (1L<<D_EXP)
37
41
 
 
42
#if defined(ARCH_64)
 
43
#define D_DECIMAL_EXP   9
 
44
#define D_DECIMAL_BASE  1000000000
 
45
#else
38
46
#define D_DECIMAL_EXP   4           /* 10^4 == 10000 */
39
47
#define D_DECIMAL_BASE  10000       /* Max decimal exponent in a digit */
 
48
#endif
40
49
 
41
50
/* macros for bignum objects */
42
51
#define big_v(x)       BIG_V(big_val(x))
55
64
#define BIG_DIGITS_PER_WORD (sizeof(Uint)/sizeof(digit_t))
56
65
 
57
66
/* FIXME: */
58
 
#ifdef ARCH_64
59
 
#define BIG_SIZE(xp) \
60
 
( 4*BIG_ARITY(xp) -  \
61
 
 ((BIG_DIGIT(xp, 4*BIG_ARITY(xp)-1) == 0) ? \
62
 
  ((BIG_DIGIT(xp, 4*BIG_ARITY(xp)-2) == 0) ? \
63
 
   ((BIG_DIGIT(xp, 4*BIG_ARITY(xp)-3) == 0) ? 3 : 2) : 1) : 0))
64
 
#else
65
67
#define BIG_SIZE(xp) \
66
68
( 2*BIG_ARITY(xp)  -  ((BIG_DIGIT(xp, 2*BIG_ARITY(xp)-1) == 0) ? 1 : 0))
67
 
#endif
68
69
 
69
70
/* Check for small */
70
71
#define IS_USMALL(sgn,x)  ((sgn) ? ((x) <= MAX_SMALL+1) : ((x) <= MAX_SMALL))
71
72
#define IS_SSMALL(x)      (((x) >= MIN_SMALL) && ((x) <= MAX_SMALL))
72
73
 
73
74
/* The heap size needed for a bignum is
74
 
** Number of digits 'x' in words = (x+1)/2 plus 
75
 
** The thing word
76
 
**
77
 
** FIXME: 
78
 
** Replace with: ( ((x)+sizeof(Uint)-1) / sizeof(Uint) ) + 1
79
 
*/
80
 
#ifdef ARCH_64
81
 
#define BIG_NEED_SIZE(x) ((((x)+3) >> 2) + 1)
82
 
#else
 
75
 * Number of digits 'x' in words = (x+1)/2 plus 
 
76
 * The thing word
 
77
 *
 
78
 */
83
79
#define BIG_NEED_SIZE(x)  ((((x)+1) >> 1) + 1)
84
 
#endif
85
80
 
 
81
#define BIG_UINT_HEAP_SIZE (1 + 1)      /* always, since sizeof(Uint) <= sizeof(Eterm) */
86
82
 
87
83
/* sizeof(digit_t) <= sizeof(D_BASE-1) */
88
84
 
 
85
#if defined(ARCH_64)
 
86
typedef Uint32 digit_t;
 
87
typedef Uint64   reg_t;
 
88
#else
89
89
typedef Uint32   reg_t;    /* register type 32 bit */
90
90
typedef Uint16 digit_t;  /* digit type    16 bit */
 
91
#endif
91
92
typedef Uint  dsize_t;   /* Vector size type */
92
93
 
93
94
 
138
139
** DREM
139
140
*/
140
141
#define DSUM(a,b,c1,c0) do { \
141
 
     reg_t _t = (a)+(b); \
 
142
     reg_t _t = ((reg_t)(a))+(b); \
142
143
     c0 = DLOW(_t); \
143
144
     c1 = DHIGH(_t); \
144
145
     } while(0)
145
146
#define DSUMc(a,b,c,s) do { \
146
 
       reg_t _t = (a)+(b); \
 
147
       reg_t _t = ((reg_t)(a))+(b); \
147
148
       if (c) _t += (c); \
148
149
       s = DLOW(_t); \
149
150
       c = DHIGH(_t); \
150
151
     }  while(0)
151
152
#define DMULc(a,b,c,p) do { \
152
 
        reg_t _t = (a)*(b); \
 
153
        reg_t _t = ((reg_t)(a))*(b); \
153
154
        if (c) _t += (c); \
154
155
        p = DLOW(_t); \
155
156
        c = DHIGH(_t); \
156
157
     } while(0)
157
158
#define DMUL(a,b,c1,c0) do { \
158
 
        reg_t _t = (a)*(b); \
 
159
        reg_t _t = ((reg_t)(a))*(b); \
159
160
        c0 = DLOW(_t); \
160
161
        c1 = DHIGH(_t); \
161
162
     } while(0)
162
163
 
163
164
#define DSUBb(a,b,r,d) do { \
164
 
         reg_t _t = (b)+(r); \
 
165
         reg_t _t = ((reg_t)(b))+(r); \
165
166
         if ((a) < _t) { \
166
167
            d = (D_BASE-_t)+(a); r = 1; \
167
168
         } \
180
181
     } while(0)
181
182
 
182
183
#define DDIV(a0,a1,b,q) do { \
183
 
        reg_t _t = (a0)*D_BASE+(a1); \
 
184
        reg_t _t = ((reg_t)(a0))*D_BASE+(a1); \
184
185
        q = _t / (b); \
185
186
     } while(0)
186
187
 
187
188
#define DDIV2(a0,a1,b0,b1,q) do { \
188
 
        reg_t _t = (a0)*D_BASE+(a1); \
189
 
        q = _t / ((b0)*D_BASE+(b1)); \
 
189
        reg_t _t = ((reg_t)(a0))*D_BASE+(a1); \
 
190
        q = _t / (((reg_t)(b0))*D_BASE+(b1)); \
190
191
     } while(0)
191
192
 
192
193
#define DREM(a0,a1,b,r) do { \
193
 
        reg_t _t = (a0)*D_BASE+(a1); \
 
194
        reg_t _t = ((reg_t)(a0))*D_BASE+(a1); \
194
195
        r = _t % (b); \
195
196
     } while(0)
196
197
 
197
 
#define BIG_UINT_HEAP_SIZE (BIG_NEED_SIZE(2))
198
 
 
199
198
int big_decimal_estimate(Eterm);
 
199
#if 0   /* XXX: unused */
200
200
char* big_to_decimal(Eterm, char*, int);
201
 
Eterm big_to_list(Eterm, Eterm**);
 
201
#endif
 
202
Eterm erts_big_to_list(Eterm, Eterm**);
 
203
char *erts_big_to_string(Eterm x, char *buf, Uint buf_sz);
202
204
 
203
205
Eterm big_plus(Eterm, Eterm, Eterm*);
204
206
Eterm big_minus(Eterm, Eterm, Eterm*);
222
224
int big_to_double(Eterm x, double* resp);
223
225
Eterm small_to_big(Sint, Eterm*);
224
226
Eterm uint_to_big(Uint, Eterm*);
225
 
Eterm make_small_or_big(Uint, Process*);
 
227
Eterm erts_make_integer(Uint, Process *);
226
228
 
227
229
dsize_t big_bytes(Eterm);
 
230
#if 0   /* XXX: unused */
228
231
int bytes_eq_big(byte*, dsize_t, int, Eterm);
 
232
#endif
229
233
Eterm bytes_to_big(byte*, dsize_t, int, Eterm*);
230
234
byte* big_to_bytes(Eterm, byte*);
231
235
 
232
 
int big_fits_in_sint32(Eterm b);
233
 
int big_fits_in_uint32(Eterm b);
 
236
int term_to_Uint(Eterm, Uint*);
 
237
int term_to_Sint(Eterm, Sint*);
 
238
 
234
239
Uint32 big_to_uint32(Eterm b);
235
 
Sint32 big_to_sint32(Eterm b);
 
240
int term_equals_2pow32(Eterm);
236
241
 
237
242
#endif
238
243