ocaml/0013-PR-6517-use-ISO-C99-ty...

1964 lines
66 KiB
Diff

From 4072cbf56bba989f87783f285952d7227ba5898d Mon Sep 17 00:00:00 2001
From: Xavier Leroy <xavier.leroy@inria.fr>
Date: Wed, 27 Aug 2014 09:58:33 +0000
Subject: [PATCH 13/18] PR#6517: use ISO C99 types {,u}int{32,64}_t in
preference to our homegrown types {,u}int{32,64}.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15131 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
----------------------------------------------------------------------
For Fedora:
This commit was cherry picked from upstream
commit b868c05ec91a7ee193010a421de768a3b1a80952 (SVN 15131).
See also:
http://caml.inria.fr/mantis/view.php?id=6517
---
asmrun/backtrace.c | 6 +-
byterun/alloc.h | 4 +-
byterun/backtrace.c | 2 +-
byterun/config.h | 35 +++++++----
byterun/debugger.h | 28 ++++-----
byterun/exec.h | 4 +-
byterun/extern.c | 4 +-
byterun/fix_code.c | 8 +--
byterun/floats.c | 6 +-
byterun/globroots.c | 4 +-
byterun/hash.c | 44 +++++++-------
byterun/hash.h | 12 ++--
byterun/int64_emul.h | 114 ++++++++++++++++++------------------
byterun/int64_format.h | 4 +-
byterun/int64_native.h | 20 +++----
byterun/intern.c | 20 +++----
byterun/interp.c | 2 +-
byterun/intext.h | 12 ++--
byterun/ints.c | 112 +++++++++++++++++------------------
byterun/io.c | 6 +-
byterun/io.h | 6 +-
byterun/md5.c | 26 ++++----
byterun/md5.h | 6 +-
byterun/mlvalues.h | 12 ++--
byterun/startup.c | 10 ++--
byterun/startup.h | 4 +-
byterun/str.c | 20 +++----
config/auto-aux/int64align.c | 14 ++---
config/s-nt.h | 3 +
configure | 25 ++------
otherlibs/bigarray/bigarray_stubs.c | 48 +++++++--------
otherlibs/num/nat_stubs.c | 14 ++---
otherlibs/unix/addrofstr.c | 2 +-
stdlib/header.c | 2 +-
34 files changed, 319 insertions(+), 320 deletions(-)
diff --git a/asmrun/backtrace.c b/asmrun/backtrace.c
index 05e0d6b..5eb8600 100644
--- a/asmrun/backtrace.c
+++ b/asmrun/backtrace.c
@@ -217,7 +217,7 @@ static void extract_location_info(frame_descr * d,
/*out*/ struct loc_info * li)
{
uintnat infoptr;
- uint32 info1, info2;
+ uint32_t info1, info2;
/* If no debugging information available, print nothing.
When everything is compiled with -g, this corresponds to
@@ -232,8 +232,8 @@ static void extract_location_info(frame_descr * d,
sizeof(char *) + sizeof(short) + sizeof(short) +
sizeof(short) * d->num_live + sizeof(frame_descr *) - 1)
& -sizeof(frame_descr *);
- info1 = ((uint32 *)infoptr)[0];
- info2 = ((uint32 *)infoptr)[1];
+ info1 = ((uint32_t *)infoptr)[0];
+ info2 = ((uint32_t *)infoptr)[1];
/* Format of the two info words:
llllllllllllllllllll aaaaaaaa bbbbbbbbbb nnnnnnnnnnnnnnnnnnnnnnnn kk
44 36 26 2 0
diff --git a/byterun/alloc.h b/byterun/alloc.h
index f00a7ef..2a640eb 100644
--- a/byterun/alloc.h
+++ b/byterun/alloc.h
@@ -32,8 +32,8 @@ CAMLextern value caml_alloc_string (mlsize_t); /* size in bytes */
CAMLextern value caml_copy_string (char const *);
CAMLextern value caml_copy_string_array (char const **);
CAMLextern value caml_copy_double (double);
-CAMLextern value caml_copy_int32 (int32); /* defined in [ints.c] */
-CAMLextern value caml_copy_int64 (int64); /* defined in [ints.c] */
+CAMLextern value caml_copy_int32 (int32_t); /* defined in [ints.c] */
+CAMLextern value caml_copy_int64 (int64_t); /* defined in [ints.c] */
CAMLextern value caml_copy_nativeint (intnat); /* defined in [ints.c] */
CAMLextern value caml_alloc_array (value (*funct) (char const *),
char const ** array);
diff --git a/byterun/backtrace.c b/byterun/backtrace.c
index 76e3ddf..6ed56c8 100644
--- a/byterun/backtrace.c
+++ b/byterun/backtrace.c
@@ -229,7 +229,7 @@ static void read_debug_info(void)
int fd;
struct exec_trailer trail;
struct channel * chan;
- uint32 num_events, orig, i;
+ uint32_t num_events, orig, i;
intnat j;
value evl, l, ev_start;
diff --git a/byterun/config.h b/byterun/config.h
index f775988..6c86d16 100644
--- a/byterun/config.h
+++ b/byterun/config.h
@@ -25,24 +25,30 @@
#include "compatibility.h"
#endif
-/* Types for 32-bit integers, 64-bit integers,
+#ifdef HAS_STDINT_H
+#include <stdint.h>
+#endif
+
+/* Types for 32-bit integers, 64-bit integers, and
native integers (as wide as a pointer type) */
+#ifndef ARCH_INT32_TYPE
#if SIZEOF_INT == 4
-typedef int int32;
-typedef unsigned int uint32;
+#define ARCH_INT32_TYPE int
+#define ARCH_UINT32_TYPE unsigned int
#define ARCH_INT32_PRINTF_FORMAT ""
#elif SIZEOF_LONG == 4
-typedef long int32;
-typedef unsigned long uint32;
+#define ARCH_INT32_TYPE long
+#define ARCH_UINT32_TYPE unsigned long
#define ARCH_INT32_PRINTF_FORMAT "l"
#elif SIZEOF_SHORT == 4
-typedef short int32;
-typedef unsigned short uint32;
+#define ARCH_INT32_TYPE short
+#define ARCH_UINT32_TYPE unsigned short
#define ARCH_INT32_PRINTF_FORMAT ""
#else
#error "No 32-bit integer type available"
#endif
+#endif
#ifndef ARCH_INT64_TYPE
#if SIZEOF_LONGLONG == 8
@@ -58,8 +64,13 @@ typedef unsigned short uint32;
#endif
#endif
-typedef ARCH_INT64_TYPE int64;
-typedef ARCH_UINT64_TYPE uint64;
+#ifndef HAS_STDINT_H
+/* Not a C99 compiler, typically MSVC. Define the C99 types we use. */
+typedef ARCH_INT32_TYPE int32_t;
+typedef ARCH_UINT32_TYPE uint32_t;
+typedef ARCH_INT64_TYPE int64_t;
+typedef ARCH_UINT64_TYPE uint64_t;
+#endif
#if SIZEOF_PTR == SIZEOF_LONG
/* Standard models: ILP32 or I32LP64 */
@@ -72,9 +83,9 @@ typedef int intnat;
typedef unsigned int uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT ""
#elif SIZEOF_PTR == 8
-/* Win64 model: IL32LLP64 */
-typedef int64 intnat;
-typedef uint64 uintnat;
+/* Win64 model: IL32P64 */
+typedef int64_t intnat;
+typedef uint64_t uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT ARCH_INT64_PRINTF_FORMAT
#else
#error "No integer type available to represent pointers"
diff --git a/byterun/debugger.h b/byterun/debugger.h
index b5079eb..e68ef75 100644
--- a/byterun/debugger.h
+++ b/byterun/debugger.h
@@ -37,17 +37,17 @@ void caml_debugger_cleanup_fork (void);
/* Requests from the debugger to the runtime system */
enum debugger_request {
- REQ_SET_EVENT = 'e', /* uint32 pos */
+ REQ_SET_EVENT = 'e', /* uint32_t pos */
/* Set an event on the instruction at position pos */
- REQ_SET_BREAKPOINT = 'B', /* uint32 pos, (char k) */
+ REQ_SET_BREAKPOINT = 'B', /* uint32_t pos, (char k) */
/* Set a breakpoint at position pos */
/* In profiling mode, the breakpoint kind is set to k */
- REQ_RESET_INSTR = 'i', /* uint32 pos */
+ REQ_RESET_INSTR = 'i', /* uint32_t pos */
/* Clear an event or breapoint at position pos, restores initial instr. */
REQ_CHECKPOINT = 'c', /* no args */
/* Checkpoint the runtime system by forking a child process.
Reply is pid of child process or -1 if checkpoint failed. */
- REQ_GO = 'g', /* uint32 n */
+ REQ_GO = 'g', /* uint32_t n */
/* Run the program for n events.
Reply is one of debugger_reply described below. */
REQ_STOP = 's', /* no args */
@@ -59,38 +59,38 @@ enum debugger_request {
Reply is stack offset and current pc. */
REQ_GET_FRAME = 'f', /* no args */
/* Return current frame location (stack offset + current pc). */
- REQ_SET_FRAME = 'S', /* uint32 stack_offset */
+ REQ_SET_FRAME = 'S', /* uint32_t stack_offset */
/* Set current frame to given stack offset. No reply. */
- REQ_UP_FRAME = 'U', /* uint32 n */
+ REQ_UP_FRAME = 'U', /* uint32_t n */
/* Move one frame up. Argument n is size of current frame (in words).
Reply is stack offset and current pc, or -1 if top of stack reached. */
- REQ_SET_TRAP_BARRIER = 'b', /* uint32 offset */
+ REQ_SET_TRAP_BARRIER = 'b', /* uint32_t offset */
/* Set the trap barrier at the given offset. */
- REQ_GET_LOCAL = 'L', /* uint32 slot_number */
+ REQ_GET_LOCAL = 'L', /* uint32_t slot_number */
/* Return the local variable at the given slot in the current frame.
Reply is one value. */
- REQ_GET_ENVIRONMENT = 'E', /* uint32 slot_number */
+ REQ_GET_ENVIRONMENT = 'E', /* uint32_t slot_number */
/* Return the local variable at the given slot in the heap environment
of the current frame. Reply is one value. */
- REQ_GET_GLOBAL = 'G', /* uint32 global_number */
+ REQ_GET_GLOBAL = 'G', /* uint32_t global_number */
/* Return the specified global variable. Reply is one value. */
REQ_GET_ACCU = 'A', /* no args */
/* Return the current contents of the accumulator. Reply is one value. */
REQ_GET_HEADER = 'H', /* mlvalue v */
/* As REQ_GET_OBJ, but sends only the header. */
- REQ_GET_FIELD = 'F', /* mlvalue v, uint32 fieldnum */
+ REQ_GET_FIELD = 'F', /* mlvalue v, uint32_t fieldnum */
/* As REQ_GET_OBJ, but sends only one field. */
REQ_MARSHAL_OBJ = 'M', /* mlvalue v */
/* Send a copy of the data structure rooted at v, using the same
format as [caml_output_value]. */
REQ_GET_CLOSURE_CODE = 'C', /* mlvalue v */
/* Send the code address of the given closure.
- Reply is one uint32. */
- REQ_SET_FORK_MODE = 'K' /* uint32 m */
+ Reply is one uint32_t. */
+ REQ_SET_FORK_MODE = 'K' /* uint32_t m */
/* Set whether to follow the child (m=0) or the parent on fork. */
};
-/* Replies to a REQ_GO request. All replies are followed by three uint32:
+/* Replies to a REQ_GO request. All replies are followed by three uint32_t:
- the value of the event counter
- the position of the stack
- the current pc. */
diff --git a/byterun/exec.h b/byterun/exec.h
index a58bcf8..7e084ac 100644
--- a/byterun/exec.h
+++ b/byterun/exec.h
@@ -39,13 +39,13 @@
struct section_descriptor {
char name[4]; /* Section name */
- uint32 len; /* Length of data in bytes */
+ uint32_t len; /* Length of data in bytes */
};
/* Structure of the trailer. */
struct exec_trailer {
- uint32 num_sections; /* Number of sections */
+ uint32_t num_sections; /* Number of sections */
char magic[12]; /* The magic number */
struct section_descriptor * section; /* Not part of file */
};
diff --git a/byterun/extern.c b/byterun/extern.c
index 33fa89a..e67d7a3 100644
--- a/byterun/extern.c
+++ b/byterun/extern.c
@@ -720,7 +720,7 @@ CAMLexport void caml_serialize_int_2(int i)
extern_ptr += 2;
}
-CAMLexport void caml_serialize_int_4(int32 i)
+CAMLexport void caml_serialize_int_4(int32_t i)
{
if (extern_ptr + 4 > extern_limit) grow_extern_output(4);
extern_ptr[0] = i >> 24;
@@ -730,7 +730,7 @@ CAMLexport void caml_serialize_int_4(int32 i)
extern_ptr += 4;
}
-CAMLexport void caml_serialize_int_8(int64 i)
+CAMLexport void caml_serialize_int_8(int64_t i)
{
caml_serialize_block_8(&i, 1);
}
diff --git a/byterun/fix_code.c b/byterun/fix_code.c
index 3380dc9..4fa0275 100644
--- a/byterun/fix_code.c
+++ b/byterun/fix_code.c
@@ -134,12 +134,12 @@ void caml_thread_code (code_t code, asize_t len)
}
*p++ = (opcode_t)(caml_instr_table[instr] - caml_instr_base);
if (instr == SWITCH) {
- uint32 sizes = *p++;
- uint32 const_size = sizes & 0xFFFF;
- uint32 block_size = sizes >> 16;
+ uint32_t sizes = *p++;
+ uint32_t const_size = sizes & 0xFFFF;
+ uint32_t block_size = sizes >> 16;
p += const_size + block_size;
} else if (instr == CLOSUREREC) {
- uint32 nfuncs = *p++;
+ uint32_t nfuncs = *p++;
p++; /* skip nvars */
p += nfuncs;
} else {
diff --git a/byterun/floats.c b/byterun/floats.c
index 7ff6d89..d8fdd05 100644
--- a/byterun/floats.c
+++ b/byterun/floats.c
@@ -378,9 +378,9 @@ CAMLprim value caml_log1p_float(value f)
union double_as_two_int32 {
double d;
#if defined(ARCH_BIG_ENDIAN) || (defined(__arm__) && !defined(__ARM_EABI__))
- struct { uint32 h; uint32 l; } i;
+ struct { uint32_t h; uint32_t l; } i;
#else
- struct { uint32 l; uint32 h; } i;
+ struct { uint32_t l; uint32_t h; } i;
#endif
};
@@ -467,7 +467,7 @@ CAMLprim value caml_classify_float(value vd)
}
#else
union double_as_two_int32 u;
- uint32 h, l;
+ uint32_t h, l;
u.d = Double_val(vd);
h = u.i.h; l = u.i.l;
diff --git a/byterun/globroots.c b/byterun/globroots.c
index ded393e..d9111ee 100644
--- a/byterun/globroots.c
+++ b/byterun/globroots.c
@@ -43,11 +43,11 @@ struct global_root_list {
(i.e. 2 * (NUM_LEVELS - 1)). Moreover, the congruential PRNG
is faster and guaranteed to be deterministic (to reproduce bugs). */
-static uint32 random_seed = 0;
+static uint32_t random_seed = 0;
static int random_level(void)
{
- uint32 r;
+ uint32_t r;
int level = 0;
/* Linear congruence with modulus = 2^32, multiplier = 69069
diff --git a/byterun/hash.c b/byterun/hash.c
index f896426..12912d3 100644
--- a/byterun/hash.c
+++ b/byterun/hash.c
@@ -41,7 +41,7 @@
h *= 0xc2b2ae35; \
h ^= h >> 16;
-CAMLexport uint32 caml_hash_mix_uint32(uint32 h, uint32 d)
+CAMLexport uint32_t caml_hash_mix_uint32(uint32_t h, uint32_t d)
{
MIX(h, d);
return h;
@@ -49,17 +49,17 @@ CAMLexport uint32 caml_hash_mix_uint32(uint32 h, uint32 d)
/* Mix a platform-native integer. */
-CAMLexport uint32 caml_hash_mix_intnat(uint32 h, intnat d)
+CAMLexport uint32_t caml_hash_mix_intnat(uint32_t h, intnat d)
{
- uint32 n;
+ uint32_t n;
#ifdef ARCH_SIXTYFOUR
/* Mix the low 32 bits and the high 32 bits, in a way that preserves
- 32/64 compatibility: we want n = (uint32) d
+ 32/64 compatibility: we want n = (uint32_t) d
if d is in the range [-2^31, 2^31-1]. */
n = (d >> 32) ^ (d >> 63) ^ d;
/* If 0 <= d < 2^31: d >> 32 = 0 d >> 63 = 0
If -2^31 <= d < 0: d >> 32 = -1 d >> 63 = -1
- In both cases, n = (uint32) d. */
+ In both cases, n = (uint32_t) d. */
#else
n = d;
#endif
@@ -69,9 +69,9 @@ CAMLexport uint32 caml_hash_mix_intnat(uint32 h, intnat d)
/* Mix a 64-bit integer. */
-CAMLexport uint32 caml_hash_mix_int64(uint32 h, int64 d)
+CAMLexport uint32_t caml_hash_mix_int64(uint32_t h, int64_t d)
{
- uint32 hi = (uint32) (d >> 32), lo = (uint32) d;
+ uint32_t hi = (uint32_t) (d >> 32), lo = (uint32_t) d;
MIX(h, lo);
MIX(h, hi);
return h;
@@ -82,17 +82,17 @@ CAMLexport uint32 caml_hash_mix_int64(uint32 h, int64 d)
Treats all NaNs identically.
*/
-CAMLexport uint32 caml_hash_mix_double(uint32 hash, double d)
+CAMLexport uint32_t caml_hash_mix_double(uint32_t hash, double d)
{
union {
double d;
#if defined(ARCH_BIG_ENDIAN) || (defined(__arm__) && !defined(__ARM_EABI__))
- struct { uint32 h; uint32 l; } i;
+ struct { uint32_t h; uint32_t l; } i;
#else
- struct { uint32 l; uint32 h; } i;
+ struct { uint32_t l; uint32_t h; } i;
#endif
} u;
- uint32 h, l;
+ uint32_t h, l;
/* Convert to two 32-bit halves */
u.d = d;
h = u.i.h; l = u.i.l;
@@ -115,14 +115,14 @@ CAMLexport uint32 caml_hash_mix_double(uint32 hash, double d)
Treats all NaNs identically.
*/
-CAMLexport uint32 caml_hash_mix_float(uint32 hash, float d)
+CAMLexport uint32_t caml_hash_mix_float(uint32_t hash, float d)
{
union {
float f;
- uint32 i;
+ uint32_t i;
} u;
- uint32 n;
- /* Convert to int32 */
+ uint32_t n;
+ /* Convert to int32_t */
u.f = d; n = u.i;
/* Normalize NaNs */
if ((n & 0x7F800000) == 0x7F800000 && (n & 0x007FFFFF) != 0) {
@@ -138,11 +138,11 @@ CAMLexport uint32 caml_hash_mix_float(uint32 hash, float d)
/* Mix an OCaml string */
-CAMLexport uint32 caml_hash_mix_string(uint32 h, value s)
+CAMLexport uint32_t caml_hash_mix_string(uint32_t h, value s)
{
mlsize_t len = caml_string_length(s);
mlsize_t i;
- uint32 w;
+ uint32_t w;
/* Mix by 32-bit blocks (little-endian) */
for (i = 0; i + 4 <= len; i += 4) {
@@ -152,7 +152,7 @@ CAMLexport uint32 caml_hash_mix_string(uint32 h, value s)
| (Byte_u(s, i+2) << 16)
| (Byte_u(s, i+3) << 24);
#else
- w = *((uint32 *) &Byte_u(s, i));
+ w = *((uint32_t *) &Byte_u(s, i));
#endif
MIX(h, w);
}
@@ -166,7 +166,7 @@ CAMLexport uint32 caml_hash_mix_string(uint32 h, value s)
default: /*skip*/; /* len & 3 == 0, no extra bytes, do nothing */
}
/* Finally, mix in the length. Ignore the upper 32 bits, generally 0. */
- h ^= (uint32) len;
+ h ^= (uint32_t) len;
return h;
}
@@ -184,7 +184,7 @@ CAMLprim value caml_hash(value count, value limit, value seed, value obj)
intnat wr; /* One past position of last value in queue */
intnat sz; /* Max number of values to put in queue */
intnat num; /* Max number of meaningful values to see */
- uint32 h; /* Rolling hash */
+ uint32_t h; /* Rolling hash */
value v;
mlsize_t i, len;
@@ -245,7 +245,7 @@ CAMLprim value caml_hash(value count, value limit, value seed, value obj)
/* If no hashing function provided, do nothing. */
/* Only use low 32 bits of custom hash, for 32/64 compatibility */
if (Custom_ops_val(v)->hash != NULL) {
- uint32 n = (uint32) Custom_ops_val(v)->hash(v);
+ uint32_t n = (uint32_t) Custom_ops_val(v)->hash(v);
h = caml_hash_mix_uint32(h, n);
num--;
}
@@ -408,5 +408,5 @@ CAMLexport value caml_hash_variant(char const * tag)
#endif
/* Force sign extension of bit 31 for compatibility between 32 and 64-bit
platforms */
- return (int32) accu;
+ return (int32_t) accu;
}
diff --git a/byterun/hash.h b/byterun/hash.h
index 436a8bb..6561397 100644
--- a/byterun/hash.h
+++ b/byterun/hash.h
@@ -18,12 +18,12 @@
#include "mlvalues.h"
-CAMLextern uint32 caml_hash_mix_uint32(uint32 h, uint32 d);
-CAMLextern uint32 caml_hash_mix_intnat(uint32 h, intnat d);
-CAMLextern uint32 caml_hash_mix_int64(uint32 h, int64 d);
-CAMLextern uint32 caml_hash_mix_double(uint32 h, double d);
-CAMLextern uint32 caml_hash_mix_float(uint32 h, float d);
-CAMLextern uint32 caml_hash_mix_string(uint32 h, value s);
+CAMLextern uint32_t caml_hash_mix_uint32(uint32_t h, uint32_t d);
+CAMLextern uint32_t caml_hash_mix_intnat(uint32_t h, intnat d);
+CAMLextern uint32_t caml_hash_mix_int64(uint32_t h, int64_t d);
+CAMLextern uint32_t caml_hash_mix_double(uint32_t h, double d);
+CAMLextern uint32_t caml_hash_mix_float(uint32_t h, float d);
+CAMLextern uint32_t caml_hash_mix_string(uint32_t h, value s);
#endif
diff --git a/byterun/int64_emul.h b/byterun/int64_emul.h
index ba7904a..2554df1 100644
--- a/byterun/int64_emul.h
+++ b/byterun/int64_emul.h
@@ -28,7 +28,7 @@
#define I64_split(x,hi,lo) (hi = (x).h, lo = (x).l)
/* Unsigned comparison */
-static int I64_ucompare(uint64 x, uint64 y)
+static int I64_ucompare(uint64_t x, uint64_t y)
{
if (x.h > y.h) return 1;
if (x.h < y.h) return -1;
@@ -40,19 +40,19 @@ static int I64_ucompare(uint64 x, uint64 y)
#define I64_ult(x, y) (I64_ucompare(x, y) < 0)
/* Signed comparison */
-static int I64_compare(int64 x, int64 y)
+static int I64_compare(int64_t x, int64_t y)
{
- if ((int32)x.h > (int32)y.h) return 1;
- if ((int32)x.h < (int32)y.h) return -1;
+ if ((int32_t)x.h > (int32_t)y.h) return 1;
+ if ((int32_t)x.h < (int32_t)y.h) return -1;
if (x.l > y.l) return 1;
if (x.l < y.l) return -1;
return 0;
}
/* Negation */
-static int64 I64_neg(int64 x)
+static int64_t I64_neg(int64_t x)
{
- int64 res;
+ int64_t res;
res.l = -x.l;
res.h = ~x.h;
if (res.l == 0) res.h++;
@@ -60,9 +60,9 @@ static int64 I64_neg(int64 x)
}
/* Addition */
-static int64 I64_add(int64 x, int64 y)
+static int64_t I64_add(int64_t x, int64_t y)
{
- int64 res;
+ int64_t res;
res.l = x.l + y.l;
res.h = x.h + y.h;
if (res.l < x.l) res.h++;
@@ -70,9 +70,9 @@ static int64 I64_add(int64 x, int64 y)
}
/* Subtraction */
-static int64 I64_sub(int64 x, int64 y)
+static int64_t I64_sub(int64_t x, int64_t y)
{
- int64 res;
+ int64_t res;
res.l = x.l - y.l;
res.h = x.h - y.h;
if (x.l < y.l) res.h--;
@@ -80,13 +80,13 @@ static int64 I64_sub(int64 x, int64 y)
}
/* Multiplication */
-static int64 I64_mul(int64 x, int64 y)
+static int64_t I64_mul(int64_t x, int64_t y)
{
- int64 res;
- uint32 prod00 = (x.l & 0xFFFF) * (y.l & 0xFFFF);
- uint32 prod10 = (x.l >> 16) * (y.l & 0xFFFF);
- uint32 prod01 = (x.l & 0xFFFF) * (y.l >> 16);
- uint32 prod11 = (x.l >> 16) * (y.l >> 16);
+ int64_t res;
+ uint32_t prod00 = (x.l & 0xFFFF) * (y.l & 0xFFFF);
+ uint32_t prod10 = (x.l >> 16) * (y.l & 0xFFFF);
+ uint32_t prod01 = (x.l & 0xFFFF) * (y.l >> 16);
+ uint32_t prod11 = (x.l >> 16) * (y.l >> 16);
res.l = prod00;
res.h = prod11 + (prod01 >> 16) + (prod10 >> 16);
prod01 = prod01 << 16; res.l += prod01; if (res.l < prod01) res.h++;
@@ -96,39 +96,39 @@ static int64 I64_mul(int64 x, int64 y)
}
#define I64_is_zero(x) (((x).l | (x).h) == 0)
-#define I64_is_negative(x) ((int32) (x).h < 0)
+#define I64_is_negative(x) ((int32_t) (x).h < 0)
#define I64_is_min_int(x) ((x).l == 0 && (x).h == 0x80000000U)
#define I64_is_minus_one(x) (((x).l & (x).h) == 0xFFFFFFFFU)
/* Bitwise operations */
-static int64 I64_and(int64 x, int64 y)
+static int64_t I64_and(int64_t x, int64_t y)
{
- int64 res;
+ int64_t res;
res.l = x.l & y.l;
res.h = x.h & y.h;
return res;
}
-static int64 I64_or(int64 x, int64 y)
+static int64_t I64_or(int64_t x, int64_t y)
{
- int64 res;
+ int64_t res;
res.l = x.l | y.l;
res.h = x.h | y.h;
return res;
}
-static int64 I64_xor(int64 x, int64 y)
+static int64_t I64_xor(int64_t x, int64_t y)
{
- int64 res;
+ int64_t res;
res.l = x.l ^ y.l;
res.h = x.h ^ y.h;
return res;
}
/* Shifts */
-static int64 I64_lsl(int64 x, int s)
+static int64_t I64_lsl(int64_t x, int s)
{
- int64 res;
+ int64_t res;
s = s & 63;
if (s == 0) return x;
if (s < 32) {
@@ -141,9 +141,9 @@ static int64 I64_lsl(int64 x, int s)
return res;
}
-static int64 I64_lsr(int64 x, int s)
+static int64_t I64_lsr(int64_t x, int s)
{
- int64 res;
+ int64_t res;
s = s & 63;
if (s == 0) return x;
if (s < 32) {
@@ -156,17 +156,17 @@ static int64 I64_lsr(int64 x, int s)
return res;
}
-static int64 I64_asr(int64 x, int s)
+static int64_t I64_asr(int64_t x, int s)
{
- int64 res;
+ int64_t res;
s = s & 63;
if (s == 0) return x;
if (s < 32) {
res.l = (x.l >> s) | (x.h << (32 - s));
- res.h = (int32) x.h >> s;
+ res.h = (int32_t) x.h >> s;
} else {
- res.l = (int32) x.h >> (s - 32);
- res.h = (int32) x.h >> 31;
+ res.l = (int32_t) x.h >> (s - 32);
+ res.h = (int32_t) x.h >> 31;
}
return res;
}
@@ -176,15 +176,15 @@ static int64 I64_asr(int64 x, int s)
#define I64_SHL1(x) x.h = (x.h << 1) | (x.l >> 31); x.l <<= 1
#define I64_SHR1(x) x.l = (x.l >> 1) | (x.h << 31); x.h >>= 1
-static void I64_udivmod(uint64 modulus, uint64 divisor,
- uint64 * quo, uint64 * mod)
+static void I64_udivmod(uint64_t modulus, uint64_t divisor,
+ uint64_t * quo, uint64_t * mod)
{
- int64 quotient, mask;
+ int64_t quotient, mask;
int cmp;
quotient.h = 0; quotient.l = 0;
mask.h = 0; mask.l = 1;
- while ((int32) divisor.h >= 0) {
+ while ((int32_t) divisor.h >= 0) {
cmp = I64_ucompare(divisor, modulus);
I64_SHL1(divisor);
I64_SHL1(mask);
@@ -202,27 +202,27 @@ static void I64_udivmod(uint64 modulus, uint64 divisor,
*mod = modulus;
}
-static int64 I64_div(int64 x, int64 y)
+static int64_t I64_div(int64_t x, int64_t y)
{
- int64 q, r;
- int32 sign;
+ int64_t q, r;
+ int32_t sign;
sign = x.h ^ y.h;
- if ((int32) x.h < 0) x = I64_neg(x);
- if ((int32) y.h < 0) y = I64_neg(y);
+ if ((int32_t) x.h < 0) x = I64_neg(x);
+ if ((int32_t) y.h < 0) y = I64_neg(y);
I64_udivmod(x, y, &q, &r);
if (sign < 0) q = I64_neg(q);
return q;
}
-static int64 I64_mod(int64 x, int64 y)
+static int64_t I64_mod(int64_t x, int64_t y)
{
- int64 q, r;
- int32 sign;
+ int64_t q, r;
+ int32_t sign;
sign = x.h;
- if ((int32) x.h < 0) x = I64_neg(x);
- if ((int32) y.h < 0) y = I64_neg(y);
+ if ((int32_t) x.h < 0) x = I64_neg(x);
+ if ((int32_t) y.h < 0) y = I64_neg(y);
I64_udivmod(x, y, &q, &r);
if (sign < 0) r = I64_neg(r);
return r;
@@ -230,49 +230,49 @@ static int64 I64_mod(int64 x, int64 y)
/* Coercions */
-static int64 I64_of_int32(int32 x)
+static int64_t I64_of_int32(int32_t x)
{
- int64 res;
+ int64_t res;
res.l = x;
res.h = x >> 31;
return res;
}
-#define I64_to_int32(x) ((int32) (x).l)
+#define I64_to_int32(x) ((int32_t) (x).l)
/* Note: we assume sizeof(intnat) = 4 here, which is true otherwise
autoconfiguration would have selected native 64-bit integers */
#define I64_of_intnat I64_of_int32
#define I64_to_intnat I64_to_int32
-static double I64_to_double(int64 x)
+static double I64_to_double(int64_t x)
{
double res;
- int32 sign = x.h;
+ int32_t sign = x.h;
if (sign < 0) x = I64_neg(x);
res = ldexp((double) x.h, 32) + x.l;
if (sign < 0) res = -res;
return res;
}
-static int64 I64_of_double(double f)
+static int64_t I64_of_double(double f)
{
- int64 res;
+ int64_t res;
double frac, integ;
int neg;
neg = (f < 0);
f = fabs(f);
frac = modf(ldexp(f, -32), &integ);
- res.h = (uint32) integ;
- res.l = (uint32) ldexp(frac, 32);
+ res.h = (uint32_t) integ;
+ res.l = (uint32_t) ldexp(frac, 32);
if (neg) res = I64_neg(res);
return res;
}
-static int64 I64_bswap(int64 x)
+static int64_t I64_bswap(int64_t x)
{
- int64 res;
+ int64_t res;
res.h = (((x.l & 0x000000FF) << 24) |
((x.l & 0x0000FF00) << 8) |
((x.l & 0x00FF0000) >> 8) |
diff --git a/byterun/int64_format.h b/byterun/int64_format.h
index b0de527..aa8f1ab 100644
--- a/byterun/int64_format.h
+++ b/byterun/int64_format.h
@@ -17,7 +17,7 @@
#ifndef CAML_INT64_FORMAT_H
#define CAML_INT64_FORMAT_H
-static void I64_format(char * buffer, char * fmt, int64 x)
+static void I64_format(char * buffer, char * fmt, int64_t x)
{
static char conv_lower[] = "0123456789abcdef";
static char conv_upper[] = "0123456789ABCDEF";
@@ -26,7 +26,7 @@ static void I64_format(char * buffer, char * fmt, int64 x)
int base, width, sign, i, rawlen;
char * cvtbl;
char * p, * r;
- int64 wbase, digit;
+ int64_t wbase, digit;
/* Parsing of format */
justify = '+';
diff --git a/byterun/int64_native.h b/byterun/int64_native.h
index e9ffe67..b6716ad 100644
--- a/byterun/int64_native.h
+++ b/byterun/int64_native.h
@@ -18,36 +18,36 @@
#ifndef CAML_INT64_NATIVE_H
#define CAML_INT64_NATIVE_H
-#define I64_literal(hi,lo) ((int64)(hi) << 32 | (lo))
-#define I64_split(x,hi,lo) (hi = (uint32)((x)>>32), lo = (uint32)(x))
+#define I64_literal(hi,lo) ((int64_t)(hi) << 32 | (lo))
+#define I64_split(x,hi,lo) (hi = (uint32_t)((x)>>32), lo = (uint32_t)(x))
#define I64_compare(x,y) (((x) > (y)) - ((x) < (y)))
-#define I64_ult(x,y) ((uint64)(x) < (uint64)(y))
+#define I64_ult(x,y) ((uint64_t)(x) < (uint64_t)(y))
#define I64_neg(x) (-(x))
#define I64_add(x,y) ((x) + (y))
#define I64_sub(x,y) ((x) - (y))
#define I64_mul(x,y) ((x) * (y))
#define I64_is_zero(x) ((x) == 0)
#define I64_is_negative(x) ((x) < 0)
-#define I64_is_min_int(x) ((x) == ((int64)1 << 63))
+#define I64_is_min_int(x) ((x) == ((int64_t)1 << 63))
#define I64_is_minus_one(x) ((x) == -1)
#define I64_div(x,y) ((x) / (y))
#define I64_mod(x,y) ((x) % (y))
#define I64_udivmod(x,y,quo,rem) \
- (*(rem) = (uint64)(x) % (uint64)(y), \
- *(quo) = (uint64)(x) / (uint64)(y))
+ (*(rem) = (uint64_t)(x) % (uint64_t)(y), \
+ *(quo) = (uint64_t)(x) / (uint64_t)(y))
#define I64_and(x,y) ((x) & (y))
#define I64_or(x,y) ((x) | (y))
#define I64_xor(x,y) ((x) ^ (y))
#define I64_lsl(x,y) ((x) << (y))
#define I64_asr(x,y) ((x) >> (y))
-#define I64_lsr(x,y) ((uint64)(x) >> (y))
+#define I64_lsr(x,y) ((uint64_t)(x) >> (y))
#define I64_to_intnat(x) ((intnat) (x))
#define I64_of_intnat(x) ((intnat) (x))
-#define I64_to_int32(x) ((int32) (x))
-#define I64_of_int32(x) ((int64) (x))
+#define I64_to_int32(x) ((int32_t) (x))
+#define I64_of_int32(x) ((int64_t) (x))
#define I64_to_double(x) ((double)(x))
-#define I64_of_double(x) ((int64)(x))
+#define I64_of_double(x) ((int64_t)(x))
#define I64_bswap(x) ((((x) & 0x00000000000000FFULL) << 56) | \
(((x) & 0x000000000000FF00ULL) << 40) | \
diff --git a/byterun/intern.c b/byterun/intern.c
index e0fcc5d..638ff72 100644
--- a/byterun/intern.c
+++ b/byterun/intern.c
@@ -553,7 +553,7 @@ static void intern_add_to_heap(mlsize_t whsize)
value caml_input_val(struct channel *chan)
{
- uint32 magic;
+ uint32_t magic;
mlsize_t block_len, num_objects, whsize;
char * block;
value res;
@@ -663,7 +663,7 @@ static value input_val_from_block(void)
CAMLexport value caml_input_value_from_malloc(char * data, intnat ofs)
{
- uint32 magic;
+ uint32_t magic;
value obj;
intern_input = (unsigned char *) data;
@@ -681,7 +681,7 @@ CAMLexport value caml_input_value_from_malloc(char * data, intnat ofs)
CAMLexport value caml_input_value_from_block(char * data, intnat len)
{
- uint32 magic;
+ uint32_t magic;
mlsize_t block_len;
value obj;
@@ -700,7 +700,7 @@ CAMLexport value caml_input_value_from_block(char * data, intnat len)
CAMLprim value caml_marshal_data_size(value buff, value ofs)
{
- uint32 magic;
+ uint32_t magic;
mlsize_t block_len;
intern_src = &Byte_u(buff, Long_val(ofs));
@@ -771,26 +771,26 @@ CAMLexport int caml_deserialize_sint_2(void)
return read16s();
}
-CAMLexport uint32 caml_deserialize_uint_4(void)
+CAMLexport uint32_t caml_deserialize_uint_4(void)
{
return read32u();
}
-CAMLexport int32 caml_deserialize_sint_4(void)
+CAMLexport int32_t caml_deserialize_sint_4(void)
{
return read32s();
}
-CAMLexport uint64 caml_deserialize_uint_8(void)
+CAMLexport uint64_t caml_deserialize_uint_8(void)
{
- uint64 i;
+ uint64_t i;
caml_deserialize_block_8(&i, 1);
return i;
}
-CAMLexport int64 caml_deserialize_sint_8(void)
+CAMLexport int64_t caml_deserialize_sint_8(void)
{
- int64 i;
+ int64_t i;
caml_deserialize_block_8(&i, 1);
return i;
}
diff --git a/byterun/interp.c b/byterun/interp.c
index 9b682ba..e22b28b 100644
--- a/byterun/interp.c
+++ b/byterun/interp.c
@@ -793,7 +793,7 @@ value caml_interprete(code_t prog, asize_t prog_size)
if (accu == Val_false) pc += *pc; else pc++;
Next;
Instruct(SWITCH): {
- uint32 sizes = *pc++;
+ uint32_t sizes = *pc++;
if (Is_block(accu)) {
intnat index = Tag_val(accu);
Assert ((uintnat) index < (sizes >> 16));
diff --git a/byterun/intext.h b/byterun/intext.h
index f7aa655..2c108a4 100644
--- a/byterun/intext.h
+++ b/byterun/intext.h
@@ -119,8 +119,8 @@ CAMLextern value caml_input_value_from_block(char * data, intnat len);
CAMLextern void caml_serialize_int_1(int i);
CAMLextern void caml_serialize_int_2(int i);
-CAMLextern void caml_serialize_int_4(int32 i);
-CAMLextern void caml_serialize_int_8(int64 i);
+CAMLextern void caml_serialize_int_4(int32_t i);
+CAMLextern void caml_serialize_int_8(int64_t i);
CAMLextern void caml_serialize_float_4(float f);
CAMLextern void caml_serialize_float_8(double f);
CAMLextern void caml_serialize_block_1(void * data, intnat len);
@@ -133,10 +133,10 @@ CAMLextern int caml_deserialize_uint_1(void);
CAMLextern int caml_deserialize_sint_1(void);
CAMLextern int caml_deserialize_uint_2(void);
CAMLextern int caml_deserialize_sint_2(void);
-CAMLextern uint32 caml_deserialize_uint_4(void);
-CAMLextern int32 caml_deserialize_sint_4(void);
-CAMLextern uint64 caml_deserialize_uint_8(void);
-CAMLextern int64 caml_deserialize_sint_8(void);
+CAMLextern uint32_t caml_deserialize_uint_4(void);
+CAMLextern int32_t caml_deserialize_sint_4(void);
+CAMLextern uint64_t caml_deserialize_uint_8(void);
+CAMLextern int64_t caml_deserialize_sint_8(void);
CAMLextern float caml_deserialize_float_4(void);
CAMLextern double caml_deserialize_float_8(void);
CAMLextern void caml_deserialize_block_1(void * data, intnat len);
diff --git a/byterun/ints.c b/byterun/ints.c
index d762c76..056e82a 100644
--- a/byterun/ints.c
+++ b/byterun/ints.c
@@ -172,8 +172,8 @@ CAMLprim value caml_format_int(value fmt, value arg)
static int int32_cmp(value v1, value v2)
{
- int32 i1 = Int32_val(v1);
- int32 i2 = Int32_val(v2);
+ int32_t i1 = Int32_val(v1);
+ int32_t i2 = Int32_val(v2);
return (i1 > i2) - (i1 < i2);
}
@@ -191,7 +191,7 @@ static void int32_serialize(value v, uintnat * wsize_32,
static uintnat int32_deserialize(void * dst)
{
- *((int32 *) dst) = caml_deserialize_sint_4();
+ *((int32_t *) dst) = caml_deserialize_sint_4();
return 4;
}
@@ -205,7 +205,7 @@ CAMLexport struct custom_operations caml_int32_ops = {
custom_compare_ext_default
};
-CAMLexport value caml_copy_int32(int32 i)
+CAMLexport value caml_copy_int32(int32_t i)
{
value res = caml_alloc_custom(&caml_int32_ops, 4, 0, 1);
Int32_val(res) = i;
@@ -226,8 +226,8 @@ CAMLprim value caml_int32_mul(value v1, value v2)
CAMLprim value caml_int32_div(value v1, value v2)
{
- int32 dividend = Int32_val(v1);
- int32 divisor = Int32_val(v2);
+ int32_t dividend = Int32_val(v1);
+ int32_t divisor = Int32_val(v2);
if (divisor == 0) caml_raise_zero_divide();
/* PR#4740: on some processors, division crashes on overflow.
Implement the same behavior as for type "int". */
@@ -237,8 +237,8 @@ CAMLprim value caml_int32_div(value v1, value v2)
CAMLprim value caml_int32_mod(value v1, value v2)
{
- int32 dividend = Int32_val(v1);
- int32 divisor = Int32_val(v2);
+ int32_t dividend = Int32_val(v1);
+ int32_t divisor = Int32_val(v2);
if (divisor == 0) caml_raise_zero_divide();
/* PR#4740: on some processors, modulus crashes if division overflows.
Implement the same behavior as for type "int". */
@@ -262,9 +262,9 @@ CAMLprim value caml_int32_shift_right(value v1, value v2)
{ return caml_copy_int32(Int32_val(v1) >> Int_val(v2)); }
CAMLprim value caml_int32_shift_right_unsigned(value v1, value v2)
-{ return caml_copy_int32((uint32)Int32_val(v1) >> Int_val(v2)); }
+{ return caml_copy_int32((uint32_t)Int32_val(v1) >> Int_val(v2)); }
-static int32 caml_swap32(int32 x)
+static int32_t caml_swap32(int32_t x)
{
return (((x & 0x000000FF) << 24) |
((x & 0x0000FF00) << 8) |
@@ -285,15 +285,15 @@ CAMLprim value caml_int32_to_int(value v)
{ return Val_long(Int32_val(v)); }
CAMLprim value caml_int32_of_float(value v)
-{ return caml_copy_int32((int32)(Double_val(v))); }
+{ return caml_copy_int32((int32_t)(Double_val(v))); }
CAMLprim value caml_int32_to_float(value v)
{ return caml_copy_double((double)(Int32_val(v))); }
CAMLprim value caml_int32_compare(value v1, value v2)
{
- int32 i1 = Int32_val(v1);
- int32 i2 = Int32_val(v2);
+ int32_t i1 = Int32_val(v1);
+ int32_t i2 = Int32_val(v2);
int res = (i1 > i2) - (i1 < i2);
return Val_int(res);
}
@@ -313,14 +313,14 @@ CAMLprim value caml_int32_of_string(value s)
CAMLprim value caml_int32_bits_of_float(value vd)
{
- union { float d; int32 i; } u;
+ union { float d; int32_t i; } u;
u.d = Double_val(vd);
return caml_copy_int32(u.i);
}
CAMLprim value caml_int32_float_of_bits(value vi)
{
- union { float d; int32 i; } u;
+ union { float d; int32_t i; } u;
u.i = Int32_val(vi);
return caml_copy_double(u.d);
}
@@ -329,11 +329,11 @@ CAMLprim value caml_int32_float_of_bits(value vi)
#ifdef ARCH_ALIGN_INT64
-CAMLexport int64 caml_Int64_val(value v)
+CAMLexport int64_t caml_Int64_val(value v)
{
- union { int32 i[2]; int64 j; } buffer;
- buffer.i[0] = ((int32 *) Data_custom_val(v))[0];
- buffer.i[1] = ((int32 *) Data_custom_val(v))[1];
+ union { int32_t i[2]; int64_t j; } buffer;
+ buffer.i[0] = ((int32_t *) Data_custom_val(v))[0];
+ buffer.i[1] = ((int32_t *) Data_custom_val(v))[1];
return buffer.j;
}
@@ -341,15 +341,15 @@ CAMLexport int64 caml_Int64_val(value v)
static int int64_cmp(value v1, value v2)
{
- int64 i1 = Int64_val(v1);
- int64 i2 = Int64_val(v2);
+ int64_t i1 = Int64_val(v1);
+ int64_t i2 = Int64_val(v2);
return (i1 > i2) - (i1 < i2);
}
static intnat int64_hash(value v)
{
- int64 x = Int64_val(v);
- uint32 lo = (uint32) x, hi = (uint32) (x >> 32);
+ int64_t x = Int64_val(v);
+ uint32_t lo = (uint32_t) x, hi = (uint32_t) (x >> 32);
return hi ^ lo;
}
@@ -363,12 +363,12 @@ static void int64_serialize(value v, uintnat * wsize_32,
static uintnat int64_deserialize(void * dst)
{
#ifndef ARCH_ALIGN_INT64
- *((int64 *) dst) = caml_deserialize_sint_8();
+ *((int64_t *) dst) = caml_deserialize_sint_8();
#else
- union { int32 i[2]; int64 j; } buffer;
+ union { int32_t i[2]; int64_t j; } buffer;
buffer.j = caml_deserialize_sint_8();
- ((int32 *) dst)[0] = buffer.i[0];
- ((int32 *) dst)[1] = buffer.i[1];
+ ((int32_t *) dst)[0] = buffer.i[0];
+ ((int32_t *) dst)[1] = buffer.i[1];
#endif
return 8;
}
@@ -383,16 +383,16 @@ CAMLexport struct custom_operations caml_int64_ops = {
custom_compare_ext_default
};
-CAMLexport value caml_copy_int64(int64 i)
+CAMLexport value caml_copy_int64(int64_t i)
{
value res = caml_alloc_custom(&caml_int64_ops, 8, 0, 1);
#ifndef ARCH_ALIGN_INT64
Int64_val(res) = i;
#else
- union { int32 i[2]; int64 j; } buffer;
+ union { int32_t i[2]; int64_t j; } buffer;
buffer.j = i;
- ((int32 *) Data_custom_val(res))[0] = buffer.i[0];
- ((int32 *) Data_custom_val(res))[1] = buffer.i[1];
+ ((int32_t *) Data_custom_val(res))[0] = buffer.i[0];
+ ((int32_t *) Data_custom_val(res))[1] = buffer.i[1];
#endif
return res;
}
@@ -413,23 +413,23 @@ CAMLprim value caml_int64_mul(value v1, value v2)
CAMLprim value caml_int64_div(value v1, value v2)
{
- int64 dividend = Int64_val(v1);
- int64 divisor = Int64_val(v2);
+ int64_t dividend = Int64_val(v1);
+ int64_t divisor = Int64_val(v2);
if (divisor == 0) caml_raise_zero_divide();
/* PR#4740: on some processors, division crashes on overflow.
Implement the same behavior as for type "int". */
- if (dividend == ((int64)1 << 63) && divisor == -1) return v1;
+ if (dividend == ((int64_t)1 << 63) && divisor == -1) return v1;
return caml_copy_int64(Int64_val(v1) / divisor);
}
CAMLprim value caml_int64_mod(value v1, value v2)
{
- int64 dividend = Int64_val(v1);
- int64 divisor = Int64_val(v2);
+ int64_t dividend = Int64_val(v1);
+ int64_t divisor = Int64_val(v2);
if (divisor == 0) caml_raise_zero_divide();
/* PR#4740: on some processors, division crashes on overflow.
Implement the same behavior as for type "int". */
- if (dividend == ((int64)1 << 63) && divisor == -1) return caml_copy_int64(0);
+ if (dividend == ((int64_t)1 << 63) && divisor == -1) return caml_copy_int64(0);
return caml_copy_int64(Int64_val(v1) % divisor);
}
@@ -449,7 +449,7 @@ CAMLprim value caml_int64_shift_right(value v1, value v2)
{ return caml_copy_int64(Int64_val(v1) >> Int_val(v2)); }
CAMLprim value caml_int64_shift_right_unsigned(value v1, value v2)
-{ return caml_copy_int64((uint64) (Int64_val(v1)) >> Int_val(v2)); }
+{ return caml_copy_int64((uint64_t) (Int64_val(v1)) >> Int_val(v2)); }
#ifdef ARCH_SIXTYFOUR
static value caml_swap64(value x)
@@ -470,7 +470,7 @@ value caml_int64_direct_bswap(value v)
CAMLprim value caml_int64_bswap(value v)
{
- int64 x = Int64_val(v);
+ int64_t x = Int64_val(v);
return caml_copy_int64
(((x & 0x00000000000000FFULL) << 56) |
((x & 0x000000000000FF00ULL) << 40) |
@@ -483,33 +483,33 @@ CAMLprim value caml_int64_bswap(value v)
}
CAMLprim value caml_int64_of_int(value v)
-{ return caml_copy_int64((int64) (Long_val(v))); }
+{ return caml_copy_int64((int64_t) (Long_val(v))); }
CAMLprim value caml_int64_to_int(value v)
{ return Val_long((intnat) (Int64_val(v))); }
CAMLprim value caml_int64_of_float(value v)
-{ return caml_copy_int64((int64) (Double_val(v))); }
+{ return caml_copy_int64((int64_t) (Double_val(v))); }
CAMLprim value caml_int64_to_float(value v)
{ return caml_copy_double((double) (Int64_val(v))); }
CAMLprim value caml_int64_of_int32(value v)
-{ return caml_copy_int64((int64) (Int32_val(v))); }
+{ return caml_copy_int64((int64_t) (Int32_val(v))); }
CAMLprim value caml_int64_to_int32(value v)
-{ return caml_copy_int32((int32) (Int64_val(v))); }
+{ return caml_copy_int32((int32_t) (Int64_val(v))); }
CAMLprim value caml_int64_of_nativeint(value v)
-{ return caml_copy_int64((int64) (Nativeint_val(v))); }
+{ return caml_copy_int64((int64_t) (Nativeint_val(v))); }
CAMLprim value caml_int64_to_nativeint(value v)
{ return caml_copy_nativeint((intnat) (Int64_val(v))); }
CAMLprim value caml_int64_compare(value v1, value v2)
{
- int64 i1 = Int64_val(v1);
- int64 i2 = Int64_val(v2);
+ int64_t i1 = Int64_val(v1);
+ int64_t i2 = Int64_val(v2);
return Val_int((i1 > i2) - (i1 < i2));
}
@@ -524,11 +524,11 @@ CAMLprim value caml_int64_format(value fmt, value arg)
CAMLprim value caml_int64_of_string(value s)
{
char * p;
- uint64 res, threshold;
+ uint64_t res, threshold;
int sign, base, d;
p = parse_sign_and_base(String_val(s), &base, &sign);
- threshold = ((uint64) -1) / base;
+ threshold = ((uint64_t) -1) / base;
d = parse_digit(*p);
if (d < 0 || d >= base) caml_failwith("int_of_string");
res = d;
@@ -541,7 +541,7 @@ CAMLprim value caml_int64_of_string(value s)
if (res > threshold) caml_failwith("int_of_string");
res = base * res + d;
/* Detect overflow in addition (base * res) + d */
- if (res < (uint64) d) caml_failwith("int_of_string");
+ if (res < (uint64_t) d) caml_failwith("int_of_string");
}
if (p != String_val(s) + caml_string_length(s)){
caml_failwith("int_of_string");
@@ -549,9 +549,9 @@ CAMLprim value caml_int64_of_string(value s)
if (base == 10) {
/* Signed representation expected, allow -2^63 to 2^63 - 1 only */
if (sign >= 0) {
- if (res >= (uint64)1 << 63) caml_failwith("int_of_string");
+ if (res >= (uint64_t)1 << 63) caml_failwith("int_of_string");
} else {
- if (res > (uint64)1 << 63) caml_failwith("int_of_string");
+ if (res > (uint64_t)1 << 63) caml_failwith("int_of_string");
}
}
if (sign < 0) res = - res;
@@ -560,20 +560,20 @@ CAMLprim value caml_int64_of_string(value s)
CAMLprim value caml_int64_bits_of_float(value vd)
{
- union { double d; int64 i; int32 h[2]; } u;
+ union { double d; int64_t i; int32_t h[2]; } u;
u.d = Double_val(vd);
#if defined(__arm__) && !defined(__ARM_EABI__)
- { int32 t = u.h[0]; u.h[0] = u.h[1]; u.h[1] = t; }
+ { int32_t t = u.h[0]; u.h[0] = u.h[1]; u.h[1] = t; }
#endif
return caml_copy_int64(u.i);
}
CAMLprim value caml_int64_float_of_bits(value vi)
{
- union { double d; int64 i; int32 h[2]; } u;
+ union { double d; int64_t i; int32_t h[2]; } u;
u.i = Int64_val(vi);
#if defined(__arm__) && !defined(__ARM_EABI__)
- { int32 t = u.h[0]; u.h[0] = u.h[1]; u.h[1] = t; }
+ { int32_t t = u.h[0]; u.h[0] = u.h[1]; u.h[1] = t; }
#endif
return caml_copy_double(u.d);
}
@@ -606,7 +606,7 @@ static void nativeint_serialize(value v, uintnat * wsize_32,
#ifdef ARCH_SIXTYFOUR
if (l >= -((intnat)1 << 31) && l < ((intnat)1 << 31)) {
caml_serialize_int_1(1);
- caml_serialize_int_4((int32) l);
+ caml_serialize_int_4((int32_t) l);
} else {
caml_serialize_int_1(2);
caml_serialize_int_8(l);
diff --git a/byterun/io.c b/byterun/io.c
index 5f04a96..bedc0f0 100644
--- a/byterun/io.c
+++ b/byterun/io.c
@@ -207,7 +207,7 @@ CAMLexport void caml_flush(struct channel *channel)
/* Output data */
-CAMLexport void caml_putword(struct channel *channel, uint32 w)
+CAMLexport void caml_putword(struct channel *channel, uint32_t w)
{
if (! caml_channel_binary_mode(channel))
caml_failwith("output_binary_int: not a binary channel");
@@ -303,10 +303,10 @@ CAMLexport unsigned char caml_refill(struct channel *channel)
return (unsigned char)(channel->buff[0]);
}
-CAMLexport uint32 caml_getword(struct channel *channel)
+CAMLexport uint32_t caml_getword(struct channel *channel)
{
int i;
- uint32 res;
+ uint32_t res;
if (! caml_channel_binary_mode(channel))
caml_failwith("input_binary_int: not a binary channel");
diff --git a/byterun/io.h b/byterun/io.h
index 64a8bf5..5a9c037 100644
--- a/byterun/io.h
+++ b/byterun/io.h
@@ -78,12 +78,12 @@ CAMLextern value caml_alloc_channel(struct channel *chan);
CAMLextern int caml_flush_partial (struct channel *);
CAMLextern void caml_flush (struct channel *);
-CAMLextern void caml_putword (struct channel *, uint32);
+CAMLextern void caml_putword (struct channel *, uint32_t);
CAMLextern int caml_putblock (struct channel *, char *, intnat);
CAMLextern void caml_really_putblock (struct channel *, char *, intnat);
CAMLextern unsigned char caml_refill (struct channel *);
-CAMLextern uint32 caml_getword (struct channel *);
+CAMLextern uint32_t caml_getword (struct channel *);
CAMLextern int caml_getblock (struct channel *, char *, intnat);
CAMLextern int caml_really_getblock (struct channel *, char *, intnat);
@@ -107,7 +107,7 @@ CAMLextern struct channel * caml_all_opened_channels;
#define Unlock_exn() \
if (caml_channel_mutex_unlock_exn != NULL) (*caml_channel_mutex_unlock_exn)()
-/* Conversion between file_offset and int64 */
+/* Conversion between file_offset and int64_t */
#define Val_file_offset(fofs) caml_copy_int64(fofs)
#define File_offset_val(v) ((file_offset) Int64_val(v))
diff --git a/byterun/md5.c b/byterun/md5.c
index 10ac76a..2dc90a2 100644
--- a/byterun/md5.c
+++ b/byterun/md5.c
@@ -97,11 +97,11 @@ CAMLexport void caml_md5_block(unsigned char digest[16],
#else
static void byteReverse(unsigned char * buf, unsigned longs)
{
- uint32 t;
+ uint32_t t;
do {
- t = (uint32) ((unsigned) buf[3] << 8 | buf[2]) << 16 |
+ t = (uint32_t) ((unsigned) buf[3] << 8 | buf[2]) << 16 |
((unsigned) buf[1] << 8 | buf[0]);
- *(uint32 *) buf = t;
+ *(uint32_t *) buf = t;
buf += 4;
} while (--longs);
}
@@ -129,12 +129,12 @@ CAMLexport void caml_MD5Init(struct MD5Context *ctx)
CAMLexport void caml_MD5Update(struct MD5Context *ctx, unsigned char *buf,
uintnat len)
{
- uint32 t;
+ uint32_t t;
/* Update bitcount */
t = ctx->bits[0];
- if ((ctx->bits[0] = t + ((uint32) len << 3)) < t)
+ if ((ctx->bits[0] = t + ((uint32_t) len << 3)) < t)
ctx->bits[1]++; /* Carry from low to high */
ctx->bits[1] += len >> 29;
@@ -152,7 +152,7 @@ CAMLexport void caml_MD5Update(struct MD5Context *ctx, unsigned char *buf,
}
memcpy(p, buf, t);
byteReverse(ctx->in, 16);
- caml_MD5Transform(ctx->buf, (uint32 *) ctx->in);
+ caml_MD5Transform(ctx->buf, (uint32_t *) ctx->in);
buf += t;
len -= t;
}
@@ -161,7 +161,7 @@ CAMLexport void caml_MD5Update(struct MD5Context *ctx, unsigned char *buf,
while (len >= 64) {
memcpy(ctx->in, buf, 64);
byteReverse(ctx->in, 16);
- caml_MD5Transform(ctx->buf, (uint32 *) ctx->in);
+ caml_MD5Transform(ctx->buf, (uint32_t *) ctx->in);
buf += 64;
len -= 64;
}
@@ -196,7 +196,7 @@ CAMLexport void caml_MD5Final(unsigned char *digest, struct MD5Context *ctx)
/* Two lots of padding: Pad the first block to 64 bytes */
memset(p, 0, count);
byteReverse(ctx->in, 16);
- caml_MD5Transform(ctx->buf, (uint32 *) ctx->in);
+ caml_MD5Transform(ctx->buf, (uint32_t *) ctx->in);
/* Now fill the next block with 56 bytes */
memset(ctx->in, 0, 56);
@@ -207,10 +207,10 @@ CAMLexport void caml_MD5Final(unsigned char *digest, struct MD5Context *ctx)
byteReverse(ctx->in, 14);
/* Append length in bits and transform */
- ((uint32 *) ctx->in)[14] = ctx->bits[0];
- ((uint32 *) ctx->in)[15] = ctx->bits[1];
+ ((uint32_t *) ctx->in)[14] = ctx->bits[0];
+ ((uint32_t *) ctx->in)[15] = ctx->bits[1];
- caml_MD5Transform(ctx->buf, (uint32 *) ctx->in);
+ caml_MD5Transform(ctx->buf, (uint32_t *) ctx->in);
byteReverse((unsigned char *) ctx->buf, 4);
memcpy(digest, ctx->buf, 16);
memset(ctx, 0, sizeof(*ctx)); /* In case it's sensitive */
@@ -233,9 +233,9 @@ CAMLexport void caml_MD5Final(unsigned char *digest, struct MD5Context *ctx)
* reflect the addition of 16 longwords of new data. caml_MD5Update blocks
* the data and converts bytes into longwords for this routine.
*/
-CAMLexport void caml_MD5Transform(uint32 *buf, uint32 *in)
+CAMLexport void caml_MD5Transform(uint32_t *buf, uint32_t *in)
{
- register uint32 a, b, c, d;
+ register uint32_t a, b, c, d;
a = buf[0];
b = buf[1];
diff --git a/byterun/md5.h b/byterun/md5.h
index d8aff09..f63667d 100644
--- a/byterun/md5.h
+++ b/byterun/md5.h
@@ -26,8 +26,8 @@ CAMLextern void caml_md5_block(unsigned char digest[16],
void * data, uintnat len);
struct MD5Context {
- uint32 buf[4];
- uint32 bits[2];
+ uint32_t buf[4];
+ uint32_t bits[2];
unsigned char in[64];
};
@@ -35,7 +35,7 @@ CAMLextern void caml_MD5Init (struct MD5Context *context);
CAMLextern void caml_MD5Update (struct MD5Context *context, unsigned char *buf,
uintnat len);
CAMLextern void caml_MD5Final (unsigned char *digest, struct MD5Context *ctx);
-CAMLextern void caml_MD5Transform (uint32 *buf, uint32 *in);
+CAMLextern void caml_MD5Transform (uint32_t *buf, uint32_t *in);
#endif /* CAML_MD5_H */
diff --git a/byterun/mlvalues.h b/byterun/mlvalues.h
index 268bcfe..a08948e 100644
--- a/byterun/mlvalues.h
+++ b/byterun/mlvalues.h
@@ -38,8 +38,8 @@ extern "C" {
bp: Pointer to the first byte of a block. (a char *)
op: Pointer to the first field of a block. (a value *)
hp: Pointer to the header of a block. (a char *)
- int32: Four bytes on all architectures.
- int64: Eight bytes on all architectures.
+ int32_t: Four bytes on all architectures.
+ int64_t: Eight bytes on all architectures.
Remark: A block size is always a multiple of the word size, and at least
one word plus the header.
@@ -161,7 +161,7 @@ bits 63 10 9 8 7 0
/* Fields are numbered from 0. */
#define Field(x, i) (((value *)(x)) [i]) /* Also an l-value. */
-typedef int32 opcode_t;
+typedef int32_t opcode_t;
typedef opcode_t * code_t;
/* NOTE: [Forward_tag] and [Infix_tag] must be just under
@@ -262,12 +262,12 @@ struct custom_operations; /* defined in [custom.h] */
/* Int32.t, Int64.t and Nativeint.t are represented as custom blocks. */
-#define Int32_val(v) (*((int32 *) Data_custom_val(v)))
+#define Int32_val(v) (*((int32_t *) Data_custom_val(v)))
#define Nativeint_val(v) (*((intnat *) Data_custom_val(v)))
#ifndef ARCH_ALIGN_INT64
-#define Int64_val(v) (*((int64 *) Data_custom_val(v)))
+#define Int64_val(v) (*((int64_t *) Data_custom_val(v)))
#else
-CAMLextern int64 caml_Int64_val(value v);
+CAMLextern int64_t caml_Int64_val(value v);
#define Int64_val(v) caml_Int64_val(v)
#endif
diff --git a/byterun/startup.c b/byterun/startup.c
index 3697220..ab926ef 100644
--- a/byterun/startup.c
+++ b/byterun/startup.c
@@ -79,7 +79,7 @@ static void init_atoms(void)
/* Read the trailer of a bytecode file */
-static void fixup_endianness_trailer(uint32 * p)
+static void fixup_endianness_trailer(uint32_t * p)
{
#ifndef ARCH_BIG_ENDIAN
Reverse_32(p, p);
@@ -153,7 +153,7 @@ void caml_read_section_descriptors(int fd, struct exec_trailer *trail)
Return the length of the section data in bytes, or -1 if no section
found with that name. */
-int32 caml_seek_optional_section(int fd, struct exec_trailer *trail, char *name)
+int32_t caml_seek_optional_section(int fd, struct exec_trailer *trail, char *name)
{
long ofs;
int i;
@@ -172,9 +172,9 @@ int32 caml_seek_optional_section(int fd, struct exec_trailer *trail, char *name)
/* Position fd at the beginning of the section having the given name.
Return the length of the section data in bytes. */
-int32 caml_seek_section(int fd, struct exec_trailer *trail, char *name)
+int32_t caml_seek_section(int fd, struct exec_trailer *trail, char *name)
{
- int32 len = caml_seek_optional_section(fd, trail, name);
+ int32_t len = caml_seek_optional_section(fd, trail, name);
if (len == -1)
caml_fatal_error_arg("Fatal_error: section `%s' is missing\n", name);
return len;
@@ -185,7 +185,7 @@ int32 caml_seek_section(int fd, struct exec_trailer *trail, char *name)
static char * read_section(int fd, struct exec_trailer *trail, char *name)
{
- int32 len;
+ int32_t len;
char * data;
len = caml_seek_optional_section(fd, trail, name);
diff --git a/byterun/startup.h b/byterun/startup.h
index 3dda64b..3268d88 100644
--- a/byterun/startup.h
+++ b/byterun/startup.h
@@ -30,9 +30,9 @@ enum { FILE_NOT_FOUND = -1, BAD_BYTECODE = -2 };
extern int caml_attempt_open(char **name, struct exec_trailer *trail,
int do_open_script);
extern void caml_read_section_descriptors(int fd, struct exec_trailer *trail);
-extern int32 caml_seek_optional_section(int fd, struct exec_trailer *trail,
+extern int32_t caml_seek_optional_section(int fd, struct exec_trailer *trail,
char *name);
-extern int32 caml_seek_section(int fd, struct exec_trailer *trail, char *name);
+extern int32_t caml_seek_section(int fd, struct exec_trailer *trail, char *name);
#endif /* CAML_STARTUP_H */
diff --git a/byterun/str.c b/byterun/str.c
index 6effa91..9c7baa1 100644
--- a/byterun/str.c
+++ b/byterun/str.c
@@ -101,7 +101,7 @@ CAMLprim value caml_string_get32(value str, value index)
CAMLprim value caml_string_get64(value str, value index)
{
- uint64 res;
+ uint64_t res;
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
intnat idx = Long_val(index);
if (idx < 0 || idx + 7 >= caml_string_length(str)) caml_array_bound_error();
@@ -114,15 +114,15 @@ CAMLprim value caml_string_get64(value str, value index)
b7 = Byte_u(str, idx + 6);
b8 = Byte_u(str, idx + 7);
#ifdef ARCH_BIG_ENDIAN
- res = (uint64) b1 << 56 | (uint64) b2 << 48
- | (uint64) b3 << 40 | (uint64) b4 << 32
- | (uint64) b5 << 24 | (uint64) b6 << 16
- | (uint64) b7 << 8 | (uint64) b8;
+ res = (uint64_t) b1 << 56 | (uint64_t) b2 << 48
+ | (uint64_t) b3 << 40 | (uint64_t) b4 << 32
+ | (uint64_t) b5 << 24 | (uint64_t) b6 << 16
+ | (uint64_t) b7 << 8 | (uint64_t) b8;
#else
- res = (uint64) b8 << 56 | (uint64) b7 << 48
- | (uint64) b6 << 40 | (uint64) b5 << 32
- | (uint64) b4 << 24 | (uint64) b3 << 16
- | (uint64) b2 << 8 | (uint64) b1;
+ res = (uint64_t) b8 << 56 | (uint64_t) b7 << 48
+ | (uint64_t) b6 << 40 | (uint64_t) b5 << 32
+ | (uint64_t) b4 << 24 | (uint64_t) b3 << 16
+ | (uint64_t) b2 << 8 | (uint64_t) b1;
#endif
return caml_copy_int64(res);
}
@@ -174,7 +174,7 @@ CAMLprim value caml_string_set32(value str, value index, value newval)
CAMLprim value caml_string_set64(value str, value index, value newval)
{
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
- int64 val;
+ int64_t val;
intnat idx = Long_val(index);
if (idx < 0 || idx + 7 >= caml_string_length(str)) caml_array_bound_error();
val = Int64_val(newval);
diff --git a/config/auto-aux/int64align.c b/config/auto-aux/int64align.c
index 5795e48..c143986 100644
--- a/config/auto-aux/int64align.c
+++ b/config/auto-aux/int64align.c
@@ -17,18 +17,18 @@
#include "m.h"
#if defined(ARCH_INT64_TYPE)
-typedef ARCH_INT64_TYPE int64;
+typedef ARCH_INT64_TYPE int64_t;
#elif SIZEOF_LONG == 8
-typedef long int64;
+typedef long int64_t;
#elif SIZEOF_LONGLONG == 8
-typedef long long int64;
+typedef long long int64_t;
#else
#error "No 64-bit integer type available"
#endif
-int64 foo;
+int64_t foo;
-void access_int64(int64 *p)
+void access_int64(int64_t *p)
{
foo = *p;
}
@@ -49,8 +49,8 @@ int main(void)
signal(SIGBUS, sig_handler);
#endif
if(setjmp(failure) == 0) {
- access_int64((int64 *) n);
- access_int64((int64 *) (n+1));
+ access_int64((int64_t *) n);
+ access_int64((int64_t *) (n+1));
res = 0;
} else {
res = 1;
diff --git a/config/s-nt.h b/config/s-nt.h
index e8aa878..ccf1bf4 100644
--- a/config/s-nt.h
+++ b/config/s-nt.h
@@ -15,6 +15,9 @@
#define OCAML_OS_TYPE "Win32"
+#ifdef __MINGW32__
+#define HAS_STDINT_H
+#endif
#undef BSD_SIGNALS
#define HAS_STRERROR
#define HAS_SOCKETS
diff --git a/configure b/configure
index c04272c..092d467 100755
--- a/configure
+++ b/configure
@@ -619,26 +619,6 @@ case "$target" in
esac
esac
-# Check semantics of division and modulus
-
-sh ./runtest divmod.c
-case $? in
- 0) inf "Native division and modulus have round-towards-zero semantics," \
- "will use them."
- echo "#undef NONSTANDARD_DIV_MOD" >> m.h;;
- 1) inf "Native division and modulus do not have round-towards-zero"
- "semantics, will use software emulation."
- echo "#define NONSTANDARD_DIV_MOD" >> m.h;;
- *) case $target in
- *-*-mingw*) inf "Native division and modulus have round-towards-zero" \
- "semantics, will use them."
- echo "#undef NONSTANDARD_DIV_MOD" >> m.h;;
- *) wrn "Something went wrong while checking native division and modulus"\
- "please report it at http://http://caml.inria.fr/mantis/"
- echo "#define NONSTANDARD_DIV_MOD" >> m.h;;
- esac;;
-esac
-
# Shared library support
shared_libraries_supported=false
@@ -1097,6 +1077,11 @@ if sh ./hasgot -i sys/types.h -i sys/socket.h -i netinet/in.h \
echo "#define HAS_IPV6" >> s.h
fi
+if sh ./hasgot -i stdint.h; then
+ inf "stdint.h found."
+ echo "#define HAS_STDINT_H" >> s.h
+fi
+
if sh ./hasgot -i unistd.h; then
inf "unistd.h found."
echo "#define HAS_UNISTD" >> s.h
diff --git a/otherlibs/bigarray/bigarray_stubs.c b/otherlibs/bigarray/bigarray_stubs.c
index 7e63cbf..f2ccb92 100644
--- a/otherlibs/bigarray/bigarray_stubs.c
+++ b/otherlibs/bigarray/bigarray_stubs.c
@@ -279,9 +279,9 @@ value caml_ba_get_N(value vb, value * vind, int nind)
case CAML_BA_UINT16:
return Val_int(((uint16 *) b->data)[offset]);
case CAML_BA_INT32:
- return caml_copy_int32(((int32 *) b->data)[offset]);
+ return caml_copy_int32(((int32_t *) b->data)[offset]);
case CAML_BA_INT64:
- return caml_copy_int64(((int64 *) b->data)[offset]);
+ return caml_copy_int64(((int64_t *) b->data)[offset]);
case CAML_BA_NATIVE_INT:
return caml_copy_nativeint(((intnat *) b->data)[offset]);
case CAML_BA_CAML_INT:
@@ -388,7 +388,7 @@ CAMLprim value caml_ba_uint8_get32(value vb, value vind)
CAMLprim value caml_ba_uint8_get64(value vb, value vind)
{
- uint64 res;
+ uint64_t res;
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
intnat idx = Long_val(vind);
struct caml_ba_array * b = Caml_ba_array_val(vb);
@@ -402,15 +402,15 @@ CAMLprim value caml_ba_uint8_get64(value vb, value vind)
b7 = ((unsigned char*) b->data)[idx+6];
b8 = ((unsigned char*) b->data)[idx+7];
#ifdef ARCH_BIG_ENDIAN
- res = (uint64) b1 << 56 | (uint64) b2 << 48
- | (uint64) b3 << 40 | (uint64) b4 << 32
- | (uint64) b5 << 24 | (uint64) b6 << 16
- | (uint64) b7 << 8 | (uint64) b8;
+ res = (uint64_t) b1 << 56 | (uint64_t) b2 << 48
+ | (uint64_t) b3 << 40 | (uint64_t) b4 << 32
+ | (uint64_t) b5 << 24 | (uint64_t) b6 << 16
+ | (uint64_t) b7 << 8 | (uint64_t) b8;
#else
- res = (uint64) b8 << 56 | (uint64) b7 << 48
- | (uint64) b6 << 40 | (uint64) b5 << 32
- | (uint64) b4 << 24 | (uint64) b3 << 16
- | (uint64) b2 << 8 | (uint64) b1;
+ res = (uint64_t) b8 << 56 | (uint64_t) b7 << 48
+ | (uint64_t) b6 << 40 | (uint64_t) b5 << 32
+ | (uint64_t) b4 << 24 | (uint64_t) b3 << 16
+ | (uint64_t) b2 << 8 | (uint64_t) b1;
#endif
return caml_copy_int64(res);
}
@@ -447,9 +447,9 @@ static value caml_ba_set_aux(value vb, value * vind, intnat nind, value newval)
case CAML_BA_UINT16:
((int16 *) b->data)[offset] = Int_val(newval); break;
case CAML_BA_INT32:
- ((int32 *) b->data)[offset] = Int32_val(newval); break;
+ ((int32_t *) b->data)[offset] = Int32_val(newval); break;
case CAML_BA_INT64:
- ((int64 *) b->data)[offset] = Int64_val(newval); break;
+ ((int64_t *) b->data)[offset] = Int64_val(newval); break;
case CAML_BA_NATIVE_INT:
((intnat *) b->data)[offset] = Nativeint_val(newval); break;
case CAML_BA_CAML_INT:
@@ -577,7 +577,7 @@ CAMLprim value caml_ba_uint8_set64(value vb, value vind, value newval)
{
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
intnat idx = Long_val(vind);
- int64 val;
+ int64_t val;
struct caml_ba_array * b = Caml_ba_array_val(vb);
if (idx < 0 || idx >= b->dim[0] - 7) caml_array_bound_error();
val = Int64_val(newval);
@@ -760,9 +760,9 @@ static int caml_ba_compare(value v1, value v2)
case CAML_BA_UINT16:
DO_INTEGER_COMPARISON(uint16);
case CAML_BA_INT32:
- DO_INTEGER_COMPARISON(int32);
+ DO_INTEGER_COMPARISON(int32_t);
case CAML_BA_INT64:
- DO_INTEGER_COMPARISON(int64);
+ DO_INTEGER_COMPARISON(int64_t);
case CAML_BA_CAML_INT:
case CAML_BA_NATIVE_INT:
DO_INTEGER_COMPARISON(intnat);
@@ -780,7 +780,7 @@ static intnat caml_ba_hash(value v)
{
struct caml_ba_array * b = Caml_ba_array_val(v);
intnat num_elts, n;
- uint32 h, w;
+ uint32_t h, w;
int i;
num_elts = 1;
@@ -820,7 +820,7 @@ static intnat caml_ba_hash(value v)
}
case CAML_BA_INT32:
{
- uint32 * p = b->data;
+ uint32_t * p = b->data;
if (num_elts > 64) num_elts = 64;
for (n = 0; n < num_elts; n++, p++) h = caml_hash_mix_uint32(h, *p);
break;
@@ -835,7 +835,7 @@ static intnat caml_ba_hash(value v)
}
case CAML_BA_INT64:
{
- int64 * p = b->data;
+ int64_t * p = b->data;
if (num_elts > 32) num_elts = 32;
for (n = 0; n < num_elts; n++, p++) h = caml_hash_mix_int64(h, *p);
break;
@@ -878,7 +878,7 @@ static void caml_ba_serialize_longarray(void * data,
} else {
caml_serialize_int_1(0);
for (n = 0, p = data; n < num_elts; n++, p++)
- caml_serialize_int_4((int32) *p);
+ caml_serialize_int_4((int32_t) *p);
}
#else
caml_serialize_int_1(0);
@@ -1181,14 +1181,14 @@ CAMLprim value caml_ba_fill(value vb, value vinit)
break;
}
case CAML_BA_INT32: {
- int32 init = Int32_val(vinit);
- int32 * p;
+ int32_t init = Int32_val(vinit);
+ int32_t * p;
for (p = b->data; num_elts > 0; p++, num_elts--) *p = init;
break;
}
case CAML_BA_INT64: {
- int64 init = Int64_val(vinit);
- int64 * p;
+ int64_t init = Int64_val(vinit);
+ int64_t * p;
for (p = b->data; num_elts > 0; p++, num_elts--) *p = init;
break;
}
diff --git a/otherlibs/num/nat_stubs.c b/otherlibs/num/nat_stubs.c
index 9a62759..d718a05 100644
--- a/otherlibs/num/nat_stubs.c
+++ b/otherlibs/num/nat_stubs.c
@@ -347,9 +347,9 @@ static void serialize_nat(value nat,
if (len >= ((mlsize_t)1 << 32))
failwith("output_value: nat too big");
#endif
- serialize_int_4((int32) len);
+ serialize_int_4((int32_t) len);
#if defined(ARCH_SIXTYFOUR) && defined(ARCH_BIG_ENDIAN)
- { int32 * p;
+ { int32_t * p;
mlsize_t i;
for (i = len, p = Data_custom_val(nat); i > 0; i -= 2, p += 2) {
serialize_int_4(p[1]); /* low 32 bits of 64-bit digit */
@@ -369,7 +369,7 @@ static uintnat deserialize_nat(void * dst)
len = deserialize_uint_4();
#if defined(ARCH_SIXTYFOUR) && defined(ARCH_BIG_ENDIAN)
- { uint32 * p;
+ { uint32_t * p;
mlsize_t i;
for (i = len, p = dst; i > 1; i -= 2, p += 2) {
p[1] = deserialize_uint_4(); /* low 32 bits of 64-bit digit */
@@ -385,7 +385,7 @@ static uintnat deserialize_nat(void * dst)
deserialize_block_4(dst, len);
#if defined(ARCH_SIXTYFOUR)
if (len & 1){
- ((uint32 *) dst)[len] = 0;
+ ((uint32_t *) dst)[len] = 0;
++ len;
}
#endif
@@ -396,7 +396,7 @@ static uintnat deserialize_nat(void * dst)
static intnat hash_nat(value v)
{
bngsize len, i;
- uint32 h;
+ uint32_t h;
len = bng_num_digits(&Digit_val(v,0), Wosize_val(v) - 1);
h = 0;
@@ -406,10 +406,10 @@ static intnat hash_nat(value v)
/* Mix the two 32-bit halves as if we were on a 32-bit platform,
namely low 32 bits first, then high 32 bits.
Also, ignore final 32 bits if they are zero. */
- h = caml_hash_mix_uint32(h, (uint32) d);
+ h = caml_hash_mix_uint32(h, (uint32_t) d);
d = d >> 32;
if (d == 0 && i + 1 == len) break;
- h = caml_hash_mix_uint32(h, (uint32) d);
+ h = caml_hash_mix_uint32(h, (uint32_t) d);
#else
h = caml_hash_mix_uint32(h, d);
#endif
diff --git a/otherlibs/unix/addrofstr.c b/otherlibs/unix/addrofstr.c
index e17841f..a2830ba 100644
--- a/otherlibs/unix/addrofstr.c
+++ b/otherlibs/unix/addrofstr.c
@@ -73,7 +73,7 @@ CAMLprim value unix_inet_addr_of_string(value s)
#else
struct in_addr address;
address.s_addr = inet_addr(String_val(s));
- if (address.s_addr == (uint32) -1) failwith("inet_addr_of_string");
+ if (address.s_addr == (uint32_t) -1) failwith("inet_addr_of_string");
return alloc_inet_addr(&address);
#endif
}
diff --git a/stdlib/header.c b/stdlib/header.c
index cb3d995..93cdfeb 100644
--- a/stdlib/header.c
+++ b/stdlib/header.c
@@ -133,7 +133,7 @@ static char * read_runtime_path(int fd)
char buffer[TRAILER_SIZE];
static char runtime_path[MAXPATHLEN];
int num_sections, i;
- uint32 path_size;
+ uint32_t path_size;
long ofs;
lseek(fd, (long) -TRAILER_SIZE, SEEK_END);
--
2.3.1