Nettoyages pour modele IL32LLP64
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7394 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
5d7edf5d8c
commit
b89cda5f86
|
@ -83,7 +83,7 @@ static struct compare_item * compare_resize_stack(struct compare_item * sp)
|
|||
#define LESS -1
|
||||
#define EQUAL 0
|
||||
#define GREATER 1
|
||||
#define UNORDERED (1L << (8 * sizeof(value) - 1))
|
||||
#define UNORDERED ((intnat)1 << (8 * sizeof(value) - 1))
|
||||
|
||||
/* The return value of compare_val is as follows:
|
||||
> 0 v1 is greater than v2
|
||||
|
|
|
@ -299,7 +299,7 @@ static void extern_rec(value v)
|
|||
} else if (n >= -(1 << 15) && n < (1 << 15)) {
|
||||
writecode16(CODE_INT16, n);
|
||||
#ifdef ARCH_SIXTYFOUR
|
||||
} else if (n < -(1L << 31) || n >= (1L << 31)) {
|
||||
} else if (n < -((intnat)1 << 31) || n >= ((intnat)1 << 31)) {
|
||||
writecode64(CODE_INT64, n);
|
||||
#endif
|
||||
} else
|
||||
|
@ -417,7 +417,7 @@ static void extern_rec(value v)
|
|||
if (tag < 16 && sz < 8) {
|
||||
Write(PREFIX_SMALL_BLOCK + tag + (sz << 4));
|
||||
#ifdef ARCH_SIXTYFOUR
|
||||
} else if (hd >= (1UL << 32)) {
|
||||
} else if (hd >= ((uintnat)1 << 32)) {
|
||||
writecode64(CODE_BLOCK64, Whitehd_hd (hd));
|
||||
#endif
|
||||
} else {
|
||||
|
@ -478,8 +478,8 @@ static intnat extern_value(value v, value flags)
|
|||
/* Write the sizes */
|
||||
res_len = extern_output_length();
|
||||
#ifdef ARCH_SIXTYFOUR
|
||||
if (res_len >= (1L << 32) ||
|
||||
size_32 >= (1L << 32) || size_64 >= (1L << 32)) {
|
||||
if (res_len >= ((intnat)1 << 32) ||
|
||||
size_32 >= ((intnat)1 << 32) || size_64 >= ((intnat)1 << 32)) {
|
||||
/* The object is so big its size cannot be written in the header.
|
||||
Besides, some of the array lengths or string lengths or shared offsets
|
||||
it contains may have overflowed the 32 bits used to write them. */
|
||||
|
|
|
@ -84,12 +84,12 @@ static intnat parse_intnat(value s, int nbits)
|
|||
}
|
||||
if (base == 10) {
|
||||
/* Signed representation expected, allow -2^(nbits-1) to 2^(nbits - 1) */
|
||||
if (res > 1UL << (nbits - 1))
|
||||
if (res > (uintnat)1 << (nbits - 1))
|
||||
caml_failwith("int_of_string");
|
||||
} else {
|
||||
/* Unsigned representation expected, allow 0 to 2^nbits - 1
|
||||
and tolerate -(2^nbits - 1) to 0 */
|
||||
if (nbits < sizeof(uintnat) * 8 && res >= 1UL << nbits)
|
||||
if (nbits < sizeof(uintnat) * 8 && res >= (uintnat)1 << nbits)
|
||||
caml_failwith("int_of_string");
|
||||
}
|
||||
return sign < 0 ? -((intnat) res) : (intnat) res;
|
||||
|
|
|
@ -68,8 +68,8 @@ typedef uintnat mark_t;
|
|||
/* Example: Val_long as in "Val from long" or "Val of long". */
|
||||
#define Val_long(x) (((intnat)(x) << 1) + 1)
|
||||
#define Long_val(x) ((x) >> 1)
|
||||
#define Max_long ((1L << (8 * sizeof(value) - 2)) - 1)
|
||||
#define Min_long (-(1L << (8 * sizeof(value) - 2)))
|
||||
#define Max_long (((intnat)1 << (8 * sizeof(value) - 2)) - 1)
|
||||
#define Min_long (-((intnat)1 << (8 * sizeof(value) - 2)))
|
||||
#define Val_int(x) Val_long(x)
|
||||
#define Int_val(x) ((int) Long_val(x))
|
||||
#define Unsigned_long_val(x) ((uintnat)(x) >> 1)
|
||||
|
@ -109,7 +109,7 @@ bits 63 10 9 8 7 0
|
|||
|
||||
#define Num_tags (1 << 8)
|
||||
#ifdef ARCH_SIXTYFOUR
|
||||
#define Max_wosize ((1L << 54) - 1)
|
||||
#define Max_wosize (((intnat)1 << 54) - 1)
|
||||
#else
|
||||
#define Max_wosize ((1 << 22) - 1)
|
||||
#endif
|
||||
|
|
Loading…
Reference in New Issue