summaryrefslogtreecommitdiffstats
path: root/otherlibs/bigarray
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/bigarray')
-rw-r--r--otherlibs/bigarray/.depend30
-rw-r--r--otherlibs/bigarray/bigarray.mli2
-rw-r--r--otherlibs/bigarray/bigarray_stubs.c106
-rw-r--r--otherlibs/bigarray/mmap_unix.c4
4 files changed, 62 insertions, 80 deletions
diff --git a/otherlibs/bigarray/.depend b/otherlibs/bigarray/.depend
index 4df63a3e3..889328a33 100644
--- a/otherlibs/bigarray/.depend
+++ b/otherlibs/bigarray/.depend
@@ -1,21 +1,21 @@
bigarray_stubs.o: bigarray_stubs.c ../../byterun/alloc.h \
- ../../byterun/misc.h ../../byterun/config.h ../../byterun/../config/m.h \
- ../../byterun/../config/s.h ../../byterun/mlvalues.h bigarray.h \
- ../../byterun/config.h ../../byterun/mlvalues.h ../../byterun/custom.h \
- ../../byterun/fail.h ../../byterun/intext.h ../../byterun/io.h \
- ../../byterun/hash.h ../../byterun/memory.h ../../byterun/gc.h \
- ../../byterun/major_gc.h ../../byterun/freelist.h \
- ../../byterun/minor_gc.h ../../byterun/int64_native.h
+ ../../byterun/misc.h ../../byterun/config.h ../../byterun/../config/m.h \
+ ../../byterun/../config/s.h ../../byterun/mlvalues.h bigarray.h \
+ ../../byterun/config.h ../../byterun/mlvalues.h ../../byterun/custom.h \
+ ../../byterun/fail.h ../../byterun/intext.h ../../byterun/io.h \
+ ../../byterun/hash.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h
mmap_unix.o: mmap_unix.c bigarray.h ../../byterun/config.h \
- ../../byterun/../config/m.h ../../byterun/../config/s.h \
- ../../byterun/mlvalues.h ../../byterun/config.h ../../byterun/misc.h \
- ../../byterun/custom.h ../../byterun/mlvalues.h ../../byterun/fail.h \
- ../../byterun/io.h ../../byterun/sys.h ../../byterun/signals.h
+ ../../byterun/../config/m.h ../../byterun/../config/s.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../byterun/misc.h \
+ ../../byterun/custom.h ../../byterun/mlvalues.h ../../byterun/fail.h \
+ ../../byterun/io.h ../../byterun/sys.h ../../byterun/signals.h
mmap_win32.o: mmap_win32.c bigarray.h ../../byterun/config.h \
- ../../byterun/../config/m.h ../../byterun/../config/s.h \
- ../../byterun/mlvalues.h ../../byterun/config.h ../../byterun/misc.h \
- ../../byterun/alloc.h ../../byterun/mlvalues.h ../../byterun/custom.h \
- ../../byterun/fail.h ../../byterun/sys.h ../unix/unixsupport.h
+ ../../byterun/../config/m.h ../../byterun/../config/s.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/mlvalues.h ../../byterun/custom.h \
+ ../../byterun/fail.h ../../byterun/sys.h ../unix/unixsupport.h
bigarray.cmi :
bigarray.cmo : bigarray.cmi
bigarray.cmx : bigarray.cmi
diff --git a/otherlibs/bigarray/bigarray.mli b/otherlibs/bigarray/bigarray.mli
index 058c25904..b3016a717 100644
--- a/otherlibs/bigarray/bigarray.mli
+++ b/otherlibs/bigarray/bigarray.mli
@@ -108,7 +108,7 @@ type ('a, 'b) kind =
let zero : type a b. (a, b) kind -> a = function
| Float32 -> 0.0 | Complex32 -> Complex.zero
| Float64 -> 0.0 | Complex64 -> Complex.zero
- | Int8_signed -> 0 | Int8_unsigned -> 0
+ | Int8_signed -> 0 | Int8_unsigned -> 0
| Int16_signed -> 0 | Int16_unsigned -> 0
| Int32 -> 0l | Int64 -> 0L
| Int -> 0 | Nativeint -> 0n
diff --git a/otherlibs/bigarray/bigarray_stubs.c b/otherlibs/bigarray/bigarray_stubs.c
index b8c768afa..f2ccb92ba 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:
@@ -293,7 +293,7 @@ value caml_ba_get_N(value vb, value * vind, int nind)
{ double * p = ((double *) b->data) + offset * 2;
return copy_two_doubles(p[0], p[1]); }
case CAML_BA_CHAR:
- return Val_int(((char *) b->data)[offset]);
+ return Val_int(((unsigned char *) b->data)[offset]);
}
}
@@ -386,16 +386,9 @@ CAMLprim value caml_ba_uint8_get32(value vb, value vind)
return caml_copy_int32(res);
}
-#ifdef ARCH_INT64_TYPE
-#include "int64_native.h"
-#else
-#include "int64_emul.h"
-#endif
-
CAMLprim value caml_ba_uint8_get64(value vb, value vind)
{
- uint32 reshi;
- uint32 reslo;
+ 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);
@@ -409,13 +402,17 @@ 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
- reshi = b1 << 24 | b2 << 16 | b3 << 8 | b4;
- reslo = b5 << 24 | b6 << 16 | b7 << 8 | 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
- reshi = b8 << 24 | b7 << 16 | b6 << 8 | b5;
- reslo = b4 << 24 | b3 << 16 | b2 << 8 | 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(I64_literal(reshi,reslo));
+ return caml_copy_int64(res);
}
/* Generic write to a big array */
@@ -450,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:
@@ -579,31 +576,29 @@ CAMLprim value caml_ba_uint8_set32(value vb, value vind, value newval)
CAMLprim value caml_ba_uint8_set64(value vb, value vind, value newval)
{
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
- uint32 lo,hi;
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);
- I64_split(val,hi,lo);
#ifdef ARCH_BIG_ENDIAN
- b1 = 0xFF & hi >> 24;
- b2 = 0xFF & hi >> 16;
- b3 = 0xFF & hi >> 8;
- b4 = 0xFF & hi;
- b5 = 0xFF & lo >> 24;
- b6 = 0xFF & lo >> 16;
- b7 = 0xFF & lo >> 8;
- b8 = 0xFF & lo;
+ b1 = 0xFF & val >> 56;
+ b2 = 0xFF & val >> 48;
+ b3 = 0xFF & val >> 40;
+ b4 = 0xFF & val >> 32;
+ b5 = 0xFF & val >> 24;
+ b6 = 0xFF & val >> 16;
+ b7 = 0xFF & val >> 8;
+ b8 = 0xFF & val;
#else
- b8 = 0xFF & hi >> 24;
- b7 = 0xFF & hi >> 16;
- b6 = 0xFF & hi >> 8;
- b5 = 0xFF & hi;
- b4 = 0xFF & lo >> 24;
- b3 = 0xFF & lo >> 16;
- b2 = 0xFF & lo >> 8;
- b1 = 0xFF & lo;
+ b8 = 0xFF & val >> 56;
+ b7 = 0xFF & val >> 48;
+ b6 = 0xFF & val >> 40;
+ b5 = 0xFF & val >> 32;
+ b4 = 0xFF & val >> 24;
+ b3 = 0xFF & val >> 16;
+ b2 = 0xFF & val >> 8;
+ b1 = 0xFF & val;
#endif
((unsigned char*) b->data)[idx] = b1;
((unsigned char*) b->data)[idx+1] = b2;
@@ -755,7 +750,7 @@ static int caml_ba_compare(value v1, value v2)
case CAML_BA_FLOAT64:
DO_FLOAT_COMPARISON(double);
case CAML_BA_CHAR:
- DO_INTEGER_COMPARISON(char);
+ DO_INTEGER_COMPARISON(uint8);
case CAML_BA_SINT8:
DO_INTEGER_COMPARISON(int8);
case CAML_BA_UINT8:
@@ -765,22 +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:
-#ifdef ARCH_INT64_TYPE
- DO_INTEGER_COMPARISON(int64);
-#else
- { int64 * p1 = b1->data; int64 * p2 = b2->data;
- for (n = 0; n < num_elts; n++) {
- int64 e1 = *p1++; int64 e2 = *p2++;
- if ((int32)e1.h > (int32)e2.h) return 1;
- if ((int32)e1.h < (int32)e2.h) return -1;
- if (e1.l > e2.l) return 1;
- if (e1.l < e2.l) return -1;
- }
- return 0;
- }
-#endif
+ DO_INTEGER_COMPARISON(int64_t);
case CAML_BA_CAML_INT:
case CAML_BA_NATIVE_INT:
DO_INTEGER_COMPARISON(intnat);
@@ -798,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;
@@ -838,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;
@@ -853,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;
@@ -896,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);
@@ -1187,7 +1169,7 @@ CAMLprim value caml_ba_fill(value vb, value vinit)
case CAML_BA_SINT8:
case CAML_BA_UINT8: {
int init = Int_val(vinit);
- char * p;
+ unsigned char * p;
for (p = b->data; num_elts > 0; p++, num_elts--) *p = init;
break;
}
@@ -1199,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/bigarray/mmap_unix.c b/otherlibs/bigarray/mmap_unix.c
index 8a93a06b1..cdcfe3ce3 100644
--- a/otherlibs/bigarray/mmap_unix.c
+++ b/otherlibs/bigarray/mmap_unix.c
@@ -153,7 +153,7 @@ CAMLprim value caml_ba_map_file(value vfd, value vkind, value vlayout,
}
}
/* Determine offset so that the mapping starts at the given file pos */
- page = getpagesize();
+ page = sysconf(_SC_PAGESIZE);
delta = (uintnat) startpos % page;
/* Do the mmap */
shared = Bool_val(vshared) ? MAP_SHARED : MAP_PRIVATE;
@@ -189,7 +189,7 @@ CAMLprim value caml_ba_map_file_bytecode(value * argv, int argn)
void caml_ba_unmap_file(void * addr, uintnat len)
{
#if defined(HAS_MMAP)
- uintnat page = getpagesize();
+ uintnat page = sysconf(_SC_PAGESIZE);
uintnat delta = (uintnat) addr % page;
if (len == 0) return; /* PR#5463 */
addr = (void *)((uintnat)addr - delta);