1995-08-09 08:06:35 -07:00
|
|
|
/***********************************************************************/
|
|
|
|
/* */
|
1996-04-30 07:53:58 -07:00
|
|
|
/* Objective Caml */
|
1995-08-09 08:06:35 -07:00
|
|
|
/* */
|
|
|
|
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
|
|
|
|
/* */
|
1996-04-30 07:53:58 -07:00
|
|
|
/* Copyright 1996 Institut National de Recherche en Informatique et */
|
1999-11-17 10:59:06 -08:00
|
|
|
/* en Automatique. All rights reserved. This file is distributed */
|
2001-12-07 05:41:02 -08:00
|
|
|
/* under the terms of the GNU Library General Public License, with */
|
|
|
|
/* the special exception on linking described in file ../LICENSE. */
|
1995-08-09 08:06:35 -07:00
|
|
|
/* */
|
|
|
|
/***********************************************************************/
|
|
|
|
|
|
|
|
/* $Id$ */
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
#include <stdio.h>
|
1996-05-28 05:41:37 -07:00
|
|
|
#include <string.h>
|
1995-05-04 03:15:53 -07:00
|
|
|
#include "alloc.h"
|
2000-02-11 04:03:31 -08:00
|
|
|
#include "custom.h"
|
1995-05-04 03:15:53 -07:00
|
|
|
#include "fail.h"
|
2000-02-11 04:03:31 -08:00
|
|
|
#include "intext.h"
|
1995-05-04 03:15:53 -07:00
|
|
|
#include "memory.h"
|
1995-07-13 02:02:41 -07:00
|
|
|
#include "misc.h"
|
1995-05-04 03:15:53 -07:00
|
|
|
#include "mlvalues.h"
|
|
|
|
|
2000-02-11 04:03:31 -08:00
|
|
|
static char * parse_sign_and_base(char * p,
|
|
|
|
/*out*/ int * base,
|
|
|
|
/*out*/ int * sign)
|
1995-05-04 03:15:53 -07:00
|
|
|
{
|
2000-02-11 04:03:31 -08:00
|
|
|
*sign = 1;
|
1995-05-04 03:15:53 -07:00
|
|
|
if (*p == '-') {
|
2000-02-11 04:03:31 -08:00
|
|
|
*sign = -1;
|
1995-05-04 03:15:53 -07:00
|
|
|
p++;
|
|
|
|
}
|
2000-02-11 04:03:31 -08:00
|
|
|
*base = 10;
|
1995-05-04 03:15:53 -07:00
|
|
|
if (*p == '0') {
|
|
|
|
switch (p[1]) {
|
|
|
|
case 'x': case 'X':
|
2000-02-11 04:03:31 -08:00
|
|
|
*base = 16; p += 2; break;
|
1995-05-04 03:15:53 -07:00
|
|
|
case 'o': case 'O':
|
2000-02-11 04:03:31 -08:00
|
|
|
*base = 8; p += 2; break;
|
2002-10-11 13:18:00 -07:00
|
|
|
case 'b': case 'B':
|
2000-02-11 04:03:31 -08:00
|
|
|
*base = 2; p += 2; break;
|
1995-05-04 03:15:53 -07:00
|
|
|
}
|
|
|
|
}
|
2000-02-11 04:03:31 -08:00
|
|
|
return p;
|
|
|
|
}
|
|
|
|
|
2002-02-04 08:44:55 -08:00
|
|
|
static int parse_digit(char c)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
if (c >= '0' && c <= '9')
|
|
|
|
return c - '0';
|
|
|
|
else if (c >= 'A' && c <= 'F')
|
|
|
|
return c - 'A' + 10;
|
|
|
|
else if (c >= 'a' && c <= 'f')
|
|
|
|
return c - 'a' + 10;
|
|
|
|
else
|
|
|
|
return -1;
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static intnat parse_intnat(value s, int nbits)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2003-06-23 04:27:05 -07:00
|
|
|
char * p;
|
2005-09-22 07:21:50 -07:00
|
|
|
uintnat res, threshold;
|
2000-02-11 04:03:31 -08:00
|
|
|
int sign, base, d;
|
|
|
|
|
2003-06-23 04:27:05 -07:00
|
|
|
p = parse_sign_and_base(String_val(s), &base, &sign);
|
2005-09-22 07:21:50 -07:00
|
|
|
threshold = ((uintnat) -1) / base;
|
2002-02-04 08:44:55 -08:00
|
|
|
d = parse_digit(*p);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (d < 0 || d >= base) caml_failwith("int_of_string");
|
2000-03-07 01:08:17 -08:00
|
|
|
for (p++, res = d; /*nothing*/; p++) {
|
2002-02-04 08:44:55 -08:00
|
|
|
char c = *p;
|
|
|
|
if (c == '_') continue;
|
|
|
|
d = parse_digit(c);
|
2000-08-08 05:26:50 -07:00
|
|
|
if (d < 0 || d >= base) break;
|
2003-11-21 07:58:10 -08:00
|
|
|
/* Detect overflow in multiplication base * res */
|
2004-01-01 08:42:43 -08:00
|
|
|
if (res > threshold) caml_failwith("int_of_string");
|
1995-05-04 03:15:53 -07:00
|
|
|
res = base * res + d;
|
2003-11-21 07:58:10 -08:00
|
|
|
/* Detect overflow in addition (base * res) + d */
|
2005-09-22 07:21:50 -07:00
|
|
|
if (res < (uintnat) d) caml_failwith("int_of_string");
|
2004-01-01 08:42:43 -08:00
|
|
|
}
|
|
|
|
if (p != String_val(s) + caml_string_length(s)){
|
|
|
|
caml_failwith("int_of_string");
|
1995-05-04 03:15:53 -07:00
|
|
|
}
|
2003-11-21 07:58:10 -08:00
|
|
|
if (base == 10) {
|
|
|
|
/* Signed representation expected, allow -2^(nbits-1) to 2^(nbits - 1) */
|
2006-05-04 05:41:26 -07:00
|
|
|
if (res > (uintnat)1 << (nbits - 1))
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_failwith("int_of_string");
|
2003-11-21 07:58:10 -08:00
|
|
|
} else {
|
|
|
|
/* Unsigned representation expected, allow 0 to 2^nbits - 1
|
|
|
|
and tolerate -(2^nbits - 1) to 0 */
|
2006-05-04 05:41:26 -07:00
|
|
|
if (nbits < sizeof(uintnat) * 8 && res >= (uintnat)1 << nbits)
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_failwith("int_of_string");
|
2003-11-21 07:58:10 -08:00
|
|
|
}
|
2005-09-22 07:21:50 -07:00
|
|
|
return sign < 0 ? -((intnat) res) : (intnat) res;
|
1995-05-04 03:15:53 -07:00
|
|
|
}
|
|
|
|
|
2002-05-25 01:32:53 -07:00
|
|
|
#ifdef NONSTANDARD_DIV_MOD
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat caml_safe_div(intnat p, intnat q)
|
2002-05-25 01:32:53 -07:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
uintnat ap = p >= 0 ? p : -p;
|
|
|
|
uintnat aq = q >= 0 ? q : -q;
|
|
|
|
uintnat ar = ap / aq;
|
2002-05-25 01:32:53 -07:00
|
|
|
return (p ^ q) >= 0 ? ar : -ar;
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat caml_safe_mod(intnat p, intnat q)
|
2002-05-25 01:32:53 -07:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
uintnat ap = p >= 0 ? p : -p;
|
|
|
|
uintnat aq = q >= 0 ? q : -q;
|
|
|
|
uintnat ar = ap % aq;
|
2002-05-25 01:32:53 -07:00
|
|
|
return p >= 0 ? ar : -ar;
|
|
|
|
}
|
|
|
|
#endif
|
|
|
|
|
|
|
|
/* Tagged integers */
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int_compare(value v1, value v2)
|
2003-04-01 00:46:39 -08:00
|
|
|
{
|
|
|
|
int res = (v1 > v2) - (v1 < v2);
|
|
|
|
return Val_int(res);
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int_of_string(value s)
|
1995-05-04 03:15:53 -07:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
return Val_long(parse_intnat(s, 8 * sizeof(value) - 1));
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
|
|
|
#define FORMAT_BUFFER_SIZE 32
|
|
|
|
|
|
|
|
static char * parse_format(value fmt,
|
|
|
|
char * suffix,
|
|
|
|
char format_string[],
|
2003-03-31 00:41:58 -08:00
|
|
|
char default_format_buffer[],
|
|
|
|
char *conv)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2003-03-31 00:41:58 -08:00
|
|
|
int prec;
|
1995-05-04 03:15:53 -07:00
|
|
|
char * p;
|
2003-03-31 00:41:58 -08:00
|
|
|
char lastletter;
|
2000-02-11 04:03:31 -08:00
|
|
|
mlsize_t len, len_suffix;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2000-02-11 04:03:31 -08:00
|
|
|
/* Copy Caml format fmt to format_string,
|
|
|
|
adding the suffix before the last letter of the format */
|
2003-12-16 10:09:44 -08:00
|
|
|
len = caml_string_length(fmt);
|
2000-02-11 04:03:31 -08:00
|
|
|
len_suffix = strlen(suffix);
|
|
|
|
if (len + len_suffix + 1 >= FORMAT_BUFFER_SIZE)
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_invalid_argument("format_int: format too long");
|
2000-10-12 11:05:42 -07:00
|
|
|
memmove(format_string, String_val(fmt), len);
|
2000-02-11 04:03:31 -08:00
|
|
|
p = format_string + len - 1;
|
|
|
|
lastletter = *p;
|
2001-10-28 06:19:13 -08:00
|
|
|
/* Compress two-letter formats, ignoring the [lnL] annotation */
|
|
|
|
if (p[-1] == 'l' || p[-1] == 'n' || p[-1] == 'L') p--;
|
2000-10-12 11:05:42 -07:00
|
|
|
memmove(p, suffix, len_suffix); p += len_suffix;
|
2000-02-11 04:03:31 -08:00
|
|
|
*p++ = lastletter;
|
|
|
|
*p = 0;
|
|
|
|
/* Determine space needed for result and allocate it dynamically if needed */
|
2001-10-28 06:19:13 -08:00
|
|
|
prec = 22 + 5; /* 22 digits for 64-bit number in octal + 5 extra */
|
1995-05-04 03:15:53 -07:00
|
|
|
for (p = String_val(fmt); *p != 0; p++) {
|
|
|
|
if (*p >= '0' && *p <= '9') {
|
|
|
|
prec = atoi(p) + 5;
|
|
|
|
break;
|
|
|
|
}
|
|
|
|
}
|
2003-03-31 00:41:58 -08:00
|
|
|
*conv = lastletter;
|
2000-02-11 04:03:31 -08:00
|
|
|
if (prec < FORMAT_BUFFER_SIZE)
|
|
|
|
return default_format_buffer;
|
|
|
|
else
|
2003-12-31 06:20:40 -08:00
|
|
|
return caml_stat_alloc(prec + 1);
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_format_int(value fmt, value arg)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2001-02-05 00:51:56 -08:00
|
|
|
char format_string[FORMAT_BUFFER_SIZE];
|
|
|
|
char default_format_buffer[FORMAT_BUFFER_SIZE];
|
2000-02-11 04:03:31 -08:00
|
|
|
char * buffer;
|
2003-03-31 00:41:58 -08:00
|
|
|
char conv;
|
2000-02-11 04:03:31 -08:00
|
|
|
value res;
|
|
|
|
|
2003-03-31 00:41:58 -08:00
|
|
|
buffer = parse_format(fmt, "l", format_string, default_format_buffer, &conv);
|
|
|
|
switch (conv) {
|
|
|
|
case 'u': case 'x': case 'X': case 'o':
|
|
|
|
sprintf(buffer, format_string, Unsigned_long_val(arg));
|
|
|
|
break;
|
|
|
|
default:
|
|
|
|
sprintf(buffer, format_string, Long_val(arg));
|
|
|
|
break;
|
|
|
|
}
|
2003-12-29 14:15:02 -08:00
|
|
|
res = caml_copy_string(buffer);
|
2003-12-31 06:20:40 -08:00
|
|
|
if (buffer != default_format_buffer) caml_stat_free(buffer);
|
2000-02-11 04:03:31 -08:00
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
|
|
|
/* 32-bit integers */
|
|
|
|
|
2003-04-01 00:46:39 -08:00
|
|
|
static int int32_cmp(value v1, value v2)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
int32 i1 = Int32_val(v1);
|
|
|
|
int32 i2 = Int32_val(v2);
|
2003-04-01 00:46:39 -08:00
|
|
|
return (i1 > i2) - (i1 < i2);
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static intnat int32_hash(value v)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
return Int32_val(v);
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static void int32_serialize(value v, uintnat * wsize_32,
|
|
|
|
uintnat * wsize_64)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_serialize_int_4(Int32_val(v));
|
2000-02-11 04:03:31 -08:00
|
|
|
*wsize_32 = *wsize_64 = 4;
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static uintnat int32_deserialize(void * dst)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
*((int32 *) dst) = caml_deserialize_sint_4();
|
2000-02-11 04:03:31 -08:00
|
|
|
return 4;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLexport struct custom_operations caml_int32_ops = {
|
2000-02-11 04:03:31 -08:00
|
|
|
"_i",
|
|
|
|
custom_finalize_default,
|
2003-04-01 00:46:39 -08:00
|
|
|
int32_cmp,
|
2000-02-11 04:03:31 -08:00
|
|
|
int32_hash,
|
|
|
|
int32_serialize,
|
|
|
|
int32_deserialize
|
|
|
|
};
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLexport value caml_copy_int32(int32 i)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
value res = caml_alloc_custom(&caml_int32_ops, 4, 0, 1);
|
2000-02-11 04:03:31 -08:00
|
|
|
Int32_val(res) = i;
|
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_neg(value v)
|
|
|
|
{ return caml_copy_int32(- Int32_val(v)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_add(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) + Int32_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_sub(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) - Int32_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_mul(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) * Int32_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_div(value v1, value v2)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
int32 divisor = Int32_val(v2);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (divisor == 0) caml_raise_zero_divide();
|
2002-05-25 01:32:53 -07:00
|
|
|
#ifdef NONSTANDARD_DIV_MOD
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int32(caml_safe_div(Int32_val(v1), divisor));
|
2002-05-25 01:32:53 -07:00
|
|
|
#else
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int32(Int32_val(v1) / divisor);
|
2002-05-25 01:32:53 -07:00
|
|
|
#endif
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_mod(value v1, value v2)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
int32 divisor = Int32_val(v2);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (divisor == 0) caml_raise_zero_divide();
|
2002-05-25 01:32:53 -07:00
|
|
|
#ifdef NONSTANDARD_DIV_MOD
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int32(caml_safe_mod(Int32_val(v1), divisor));
|
2002-05-25 01:32:53 -07:00
|
|
|
#else
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int32(Int32_val(v1) % divisor);
|
2002-05-25 01:32:53 -07:00
|
|
|
#endif
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_and(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) & Int32_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_or(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) | Int32_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_xor(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) ^ Int32_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_shift_left(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) << Int_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_shift_right(value v1, value v2)
|
|
|
|
{ return caml_copy_int32(Int32_val(v1) >> Int_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_shift_right_unsigned(value v1, value v2)
|
|
|
|
{ return caml_copy_int32((uint32)Int32_val(v1) >> Int_val(v2)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_of_int(value v)
|
|
|
|
{ return caml_copy_int32(Long_val(v)); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_to_int(value v)
|
2000-02-11 04:03:31 -08:00
|
|
|
{ return Val_long(Int32_val(v)); }
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_of_float(value v)
|
|
|
|
{ return caml_copy_int32((int32)(Double_val(v))); }
|
2000-04-18 07:41:13 -07:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_to_float(value v)
|
2004-01-02 11:23:29 -08:00
|
|
|
{ return caml_copy_double((double)(Int32_val(v))); }
|
2000-04-18 07:41:13 -07:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_compare(value v1, value v2)
|
2003-04-01 00:46:39 -08:00
|
|
|
{
|
|
|
|
int32 i1 = Int32_val(v1);
|
|
|
|
int32 i2 = Int32_val(v2);
|
|
|
|
int res = (i1 > i2) - (i1 < i2);
|
|
|
|
return Val_int(res);
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_format(value fmt, value arg)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2001-02-05 00:51:56 -08:00
|
|
|
char format_string[FORMAT_BUFFER_SIZE];
|
|
|
|
char default_format_buffer[FORMAT_BUFFER_SIZE];
|
2000-02-11 04:03:31 -08:00
|
|
|
char * buffer;
|
2003-03-31 00:41:58 -08:00
|
|
|
char conv;
|
2000-02-11 04:03:31 -08:00
|
|
|
value res;
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
buffer = parse_format(fmt, ARCH_INT32_PRINTF_FORMAT,
|
|
|
|
format_string, default_format_buffer, &conv);
|
|
|
|
sprintf(buffer, format_string, Int32_val(arg));
|
2003-12-29 14:15:02 -08:00
|
|
|
res = caml_copy_string(buffer);
|
2003-12-31 06:20:40 -08:00
|
|
|
if (buffer != default_format_buffer) caml_stat_free(buffer);
|
2000-02-11 04:03:31 -08:00
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_of_string(value s)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
return caml_copy_int32(parse_intnat(s, 32));
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_bits_of_float(value vd)
|
2003-12-20 08:24:35 -08:00
|
|
|
{
|
|
|
|
union { float d; int32 i; } u;
|
|
|
|
u.d = Double_val(vd);
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int32(u.i);
|
2003-12-20 08:24:35 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int32_float_of_bits(value vi)
|
2003-12-20 08:24:35 -08:00
|
|
|
{
|
|
|
|
union { float d; int32 i; } u;
|
|
|
|
u.i = Int32_val(vi);
|
2004-01-02 11:23:29 -08:00
|
|
|
return caml_copy_double(u.d);
|
2003-12-20 08:24:35 -08:00
|
|
|
}
|
|
|
|
|
2000-02-11 04:03:31 -08:00
|
|
|
/* 64-bit integers */
|
|
|
|
|
2000-02-11 07:47:09 -08:00
|
|
|
#ifdef ARCH_INT64_TYPE
|
2002-05-25 01:32:53 -07:00
|
|
|
#include "int64_native.h"
|
|
|
|
#else
|
|
|
|
#include "int64_emul.h"
|
|
|
|
#endif
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2000-03-10 09:36:31 -08:00
|
|
|
#ifdef ARCH_ALIGN_INT64
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLexport int64 caml_Int64_val(value v)
|
2000-03-10 09:36:31 -08:00
|
|
|
{
|
|
|
|
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];
|
|
|
|
return buffer.j;
|
|
|
|
}
|
|
|
|
|
|
|
|
#endif
|
|
|
|
|
2003-04-01 00:46:39 -08:00
|
|
|
static int int64_cmp(value v1, value v2)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
int64 i1 = Int64_val(v1);
|
|
|
|
int64 i2 = Int64_val(v2);
|
2002-05-25 01:32:53 -07:00
|
|
|
return I64_compare(i1, i2);
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static intnat int64_hash(value v)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
return I64_to_intnat(Int64_val(v));
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static void int64_serialize(value v, uintnat * wsize_32,
|
|
|
|
uintnat * wsize_64)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_serialize_int_8(Int64_val(v));
|
2000-11-30 09:13:41 -08:00
|
|
|
*wsize_32 = *wsize_64 = 8;
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static uintnat int64_deserialize(void * dst)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2001-09-24 05:39:26 -07:00
|
|
|
#ifndef ARCH_ALIGN_INT64
|
2004-01-01 08:42:43 -08:00
|
|
|
*((int64 *) dst) = caml_deserialize_sint_8();
|
2001-09-24 05:39:26 -07:00
|
|
|
#else
|
|
|
|
union { int32 i[2]; int64 j; } buffer;
|
2004-01-01 08:42:43 -08:00
|
|
|
buffer.j = caml_deserialize_sint_8();
|
2001-09-24 05:39:26 -07:00
|
|
|
((int32 *) dst)[0] = buffer.i[0];
|
|
|
|
((int32 *) dst)[1] = buffer.i[1];
|
|
|
|
#endif
|
2000-02-11 04:03:31 -08:00
|
|
|
return 8;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLexport struct custom_operations caml_int64_ops = {
|
2000-02-11 07:09:27 -08:00
|
|
|
"_j",
|
2000-02-11 04:03:31 -08:00
|
|
|
custom_finalize_default,
|
2003-04-01 00:46:39 -08:00
|
|
|
int64_cmp,
|
2000-02-11 04:03:31 -08:00
|
|
|
int64_hash,
|
|
|
|
int64_serialize,
|
|
|
|
int64_deserialize
|
|
|
|
};
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLexport value caml_copy_int64(int64 i)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
value res = caml_alloc_custom(&caml_int64_ops, 8, 0, 1);
|
2000-03-10 09:54:18 -08:00
|
|
|
#ifndef ARCH_ALIGN_INT64
|
2000-02-11 04:03:31 -08:00
|
|
|
Int64_val(res) = i;
|
2000-03-10 09:54:18 -08:00
|
|
|
#else
|
|
|
|
union { int32 i[2]; int64 j; } buffer;
|
|
|
|
buffer.j = i;
|
|
|
|
((int32 *) Data_custom_val(res))[0] = buffer.i[0];
|
|
|
|
((int32 *) Data_custom_val(res))[1] = buffer.i[1];
|
|
|
|
#endif
|
2000-02-11 04:03:31 -08:00
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_neg(value v)
|
|
|
|
{ return caml_copy_int64(I64_neg(Int64_val(v))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_add(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_add(Int64_val(v1), Int64_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_sub(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_sub(Int64_val(v1), Int64_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_mul(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_mul(Int64_val(v1), Int64_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_div(value v1, value v2)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
int64 divisor = Int64_val(v2);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (I64_is_zero(divisor)) caml_raise_zero_divide();
|
|
|
|
return caml_copy_int64(I64_div(Int64_val(v1), divisor));
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_mod(value v1, value v2)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
int64 divisor = Int64_val(v2);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (I64_is_zero(divisor)) caml_raise_zero_divide();
|
|
|
|
return caml_copy_int64(I64_mod(Int64_val(v1), divisor));
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_and(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_and(Int64_val(v1), Int64_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_or(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_or(Int64_val(v1), Int64_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_xor(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_xor(Int64_val(v1), Int64_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_shift_left(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_lsl(Int64_val(v1), Int_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_shift_right(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_asr(Int64_val(v1), Int_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_shift_right_unsigned(value v1, value v2)
|
|
|
|
{ return caml_copy_int64(I64_lsr(Int64_val(v1), Int_val(v2))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_of_int(value v)
|
2005-09-22 07:21:50 -07:00
|
|
|
{ return caml_copy_int64(I64_of_intnat(Long_val(v))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_to_int(value v)
|
2005-09-22 07:21:50 -07:00
|
|
|
{ return Val_long(I64_to_intnat(Int64_val(v))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_of_float(value v)
|
|
|
|
{ return caml_copy_int64(I64_of_double(Double_val(v))); }
|
2000-04-18 07:41:13 -07:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_to_float(value v)
|
2003-03-20 07:07:44 -08:00
|
|
|
{
|
|
|
|
int64 i = Int64_val(v);
|
2004-01-02 11:23:29 -08:00
|
|
|
return caml_copy_double(I64_to_double(i));
|
2003-03-20 07:07:44 -08:00
|
|
|
}
|
2000-04-18 07:41:13 -07:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_of_int32(value v)
|
|
|
|
{ return caml_copy_int64(I64_of_int32(Int32_val(v))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_to_int32(value v)
|
|
|
|
{ return caml_copy_int32(I64_to_int32(Int64_val(v))); }
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_of_nativeint(value v)
|
2005-09-22 07:21:50 -07:00
|
|
|
{ return caml_copy_int64(I64_of_intnat(Nativeint_val(v))); }
|
2000-03-05 11:17:54 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_to_nativeint(value v)
|
2005-09-22 07:21:50 -07:00
|
|
|
{ return caml_copy_nativeint(I64_to_intnat(Int64_val(v))); }
|
2000-03-05 11:17:54 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_compare(value v1, value v2)
|
2003-04-01 00:46:39 -08:00
|
|
|
{
|
|
|
|
int64 i1 = Int64_val(v1);
|
|
|
|
int64 i2 = Int64_val(v2);
|
|
|
|
return Val_int(I64_compare(i1, i2));
|
|
|
|
}
|
|
|
|
|
2000-04-05 11:30:22 -07:00
|
|
|
#ifdef ARCH_INT64_PRINTF_FORMAT
|
2002-05-25 01:32:53 -07:00
|
|
|
#define I64_format(buf,fmt,x) sprintf(buf,fmt,x)
|
|
|
|
#else
|
|
|
|
#include "int64_format.h"
|
|
|
|
#define ARCH_INT64_PRINTF_FORMAT ""
|
|
|
|
#endif
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_format(value fmt, value arg)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
2001-02-05 00:51:56 -08:00
|
|
|
char format_string[FORMAT_BUFFER_SIZE];
|
|
|
|
char default_format_buffer[FORMAT_BUFFER_SIZE];
|
2000-02-11 04:03:31 -08:00
|
|
|
char * buffer;
|
2003-03-31 00:41:58 -08:00
|
|
|
char conv;
|
2000-02-11 04:03:31 -08:00
|
|
|
value res;
|
|
|
|
|
2000-02-11 07:47:09 -08:00
|
|
|
buffer = parse_format(fmt, ARCH_INT64_PRINTF_FORMAT,
|
2003-03-31 00:41:58 -08:00
|
|
|
format_string, default_format_buffer, &conv);
|
2002-05-25 01:32:53 -07:00
|
|
|
I64_format(buffer, format_string, Int64_val(arg));
|
2003-12-29 14:15:02 -08:00
|
|
|
res = caml_copy_string(buffer);
|
2003-12-31 06:20:40 -08:00
|
|
|
if (buffer != default_format_buffer) caml_stat_free(buffer);
|
1995-05-04 03:15:53 -07:00
|
|
|
return res;
|
|
|
|
}
|
2000-02-11 04:03:31 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_of_string(value s)
|
2000-02-11 04:03:31 -08:00
|
|
|
{
|
|
|
|
char * p;
|
2003-11-21 07:58:10 -08:00
|
|
|
uint64 max_uint64 = I64_literal(0xFFFFFFFF, 0xFFFFFFFF);
|
|
|
|
uint64 max_int64 = I64_literal(0x80000000, 0x00000000);
|
|
|
|
uint64 res, threshold;
|
2000-02-11 04:03:31 -08:00
|
|
|
int sign, base, d;
|
|
|
|
|
|
|
|
p = parse_sign_and_base(String_val(s), &base, &sign);
|
2003-11-21 07:58:10 -08:00
|
|
|
I64_udivmod(max_uint64, I64_of_int32(base), &threshold, &res);
|
2002-02-04 08:44:55 -08:00
|
|
|
d = parse_digit(*p);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (d < 0 || d >= base) caml_failwith("int_of_string");
|
2002-05-25 01:32:53 -07:00
|
|
|
res = I64_of_int32(d);
|
|
|
|
for (p++; /*nothing*/; p++) {
|
2002-02-04 08:44:55 -08:00
|
|
|
char c = *p;
|
|
|
|
if (c == '_') continue;
|
|
|
|
d = parse_digit(c);
|
2000-08-08 05:26:50 -07:00
|
|
|
if (d < 0 || d >= base) break;
|
2003-11-21 07:58:10 -08:00
|
|
|
/* Detect overflow in multiplication base * res */
|
2004-01-01 08:42:43 -08:00
|
|
|
if (I64_ult(threshold, res)) caml_failwith("int_of_string");
|
2002-05-25 01:32:53 -07:00
|
|
|
res = I64_add(I64_mul(I64_of_int32(base), res), I64_of_int32(d));
|
2003-11-21 07:58:10 -08:00
|
|
|
/* Detect overflow in addition (base * res) + d */
|
2004-01-01 08:42:43 -08:00
|
|
|
if (I64_ult(res, I64_of_int32(d))) caml_failwith("int_of_string");
|
|
|
|
}
|
|
|
|
if (p != String_val(s) + caml_string_length(s)){
|
|
|
|
caml_failwith("int_of_string");
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
2004-01-01 08:42:43 -08:00
|
|
|
if (base == 10 && I64_ult(max_int64, res)) caml_failwith("int_of_string");
|
2002-05-25 01:32:53 -07:00
|
|
|
if (sign < 0) res = I64_neg(res);
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int64(res);
|
2000-02-11 04:03:31 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_bits_of_float(value vd)
|
2001-02-05 00:51:56 -08:00
|
|
|
{
|
|
|
|
union { double d; int64 i; } u;
|
|
|
|
u.d = Double_val(vd);
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_int64(u.i);
|
2001-02-05 00:51:56 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_int64_float_of_bits(value vi)
|
2001-02-05 00:51:56 -08:00
|
|
|
{
|
|
|
|
union { double d; int64 i; } u;
|
|
|
|
u.i = Int64_val(vi);
|
2004-01-02 11:23:29 -08:00
|
|
|
return caml_copy_double(u.d);
|
2001-02-05 00:51:56 -08:00
|
|
|
}
|
|
|
|
|
2000-02-11 07:09:27 -08:00
|
|
|
/* Native integers */
|
|
|
|
|
2003-04-01 00:46:39 -08:00
|
|
|
static int nativeint_cmp(value v1, value v2)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat i1 = Nativeint_val(v1);
|
|
|
|
intnat i2 = Nativeint_val(v2);
|
2003-04-01 00:46:39 -08:00
|
|
|
return (i1 > i2) - (i1 < i2);
|
2000-02-11 07:09:27 -08:00
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static intnat nativeint_hash(value v)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
|
|
|
return Nativeint_val(v);
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static void nativeint_serialize(value v, uintnat * wsize_32,
|
|
|
|
uintnat * wsize_64)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat l = Nativeint_val(v);
|
2000-02-11 07:09:27 -08:00
|
|
|
#ifdef ARCH_SIXTYFOUR
|
|
|
|
if (l <= 0x7FFFFFFFL && l >= -0x80000000L) {
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_serialize_int_1(1);
|
|
|
|
caml_serialize_int_4((int32) l);
|
2000-02-11 07:09:27 -08:00
|
|
|
} else {
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_serialize_int_1(2);
|
|
|
|
caml_serialize_int_8(l);
|
2000-02-11 07:09:27 -08:00
|
|
|
}
|
|
|
|
#else
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_serialize_int_1(1);
|
|
|
|
caml_serialize_int_4(l);
|
2000-02-11 07:09:27 -08:00
|
|
|
#endif
|
|
|
|
*wsize_32 = 4;
|
|
|
|
*wsize_64 = 8;
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static uintnat nativeint_deserialize(void * dst)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
switch (caml_deserialize_uint_1()) {
|
2000-02-11 07:09:27 -08:00
|
|
|
case 1:
|
2004-01-01 08:42:43 -08:00
|
|
|
*((long *) dst) = caml_deserialize_sint_4();
|
2000-02-11 07:09:27 -08:00
|
|
|
break;
|
|
|
|
case 2:
|
|
|
|
#ifdef ARCH_SIXTYFOUR
|
2004-01-01 08:42:43 -08:00
|
|
|
*((long *) dst) = caml_deserialize_sint_8();
|
2000-02-11 07:09:27 -08:00
|
|
|
#else
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_deserialize_error("input_value: native integer value too large");
|
2000-02-11 07:09:27 -08:00
|
|
|
#endif
|
|
|
|
break;
|
|
|
|
default:
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_deserialize_error("input_value: ill-formed native integer");
|
2000-02-11 07:09:27 -08:00
|
|
|
}
|
|
|
|
return sizeof(long);
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLexport struct custom_operations caml_nativeint_ops = {
|
2000-02-11 07:09:27 -08:00
|
|
|
"_n",
|
|
|
|
custom_finalize_default,
|
2003-04-01 00:46:39 -08:00
|
|
|
nativeint_cmp,
|
2000-02-11 07:09:27 -08:00
|
|
|
nativeint_hash,
|
|
|
|
nativeint_serialize,
|
|
|
|
nativeint_deserialize
|
|
|
|
};
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
CAMLexport value caml_copy_nativeint(intnat i)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
value res = caml_alloc_custom(&caml_nativeint_ops, sizeof(intnat), 0, 1);
|
2000-02-11 07:09:27 -08:00
|
|
|
Nativeint_val(res) = i;
|
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_neg(value v)
|
|
|
|
{ return caml_copy_nativeint(- Nativeint_val(v)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_add(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) + Nativeint_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_sub(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) - Nativeint_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_mul(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) * Nativeint_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_div(value v1, value v2)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat divisor = Nativeint_val(v2);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (divisor == 0) caml_raise_zero_divide();
|
2002-05-25 01:32:53 -07:00
|
|
|
#ifdef NONSTANDARD_DIV_MOD
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_nativeint(caml_safe_div(Nativeint_val(v1), divisor));
|
2002-05-25 01:32:53 -07:00
|
|
|
#else
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_nativeint(Nativeint_val(v1) / divisor);
|
2002-05-25 01:32:53 -07:00
|
|
|
#endif
|
2000-02-11 07:09:27 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_mod(value v1, value v2)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat divisor = Nativeint_val(v2);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (divisor == 0) caml_raise_zero_divide();
|
2002-05-25 01:32:53 -07:00
|
|
|
#ifdef NONSTANDARD_DIV_MOD
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_nativeint(caml_safe_mod(Nativeint_val(v1), divisor));
|
2002-05-25 01:32:53 -07:00
|
|
|
#else
|
2004-01-01 08:42:43 -08:00
|
|
|
return caml_copy_nativeint(Nativeint_val(v1) % divisor);
|
2002-05-25 01:32:53 -07:00
|
|
|
#endif
|
2000-02-11 07:09:27 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_and(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) & Nativeint_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_or(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) | Nativeint_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_xor(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) ^ Nativeint_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_shift_left(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) << Int_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_shift_right(value v1, value v2)
|
|
|
|
{ return caml_copy_nativeint(Nativeint_val(v1) >> Int_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_shift_right_unsigned(value v1, value v2)
|
2005-09-22 07:21:50 -07:00
|
|
|
{ return caml_copy_nativeint((uintnat)Nativeint_val(v1) >> Int_val(v2)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_of_int(value v)
|
|
|
|
{ return caml_copy_nativeint(Long_val(v)); }
|
2000-02-11 07:09:27 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_to_int(value v)
|
2000-02-11 07:09:27 -08:00
|
|
|
{ return Val_long(Nativeint_val(v)); }
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_of_float(value v)
|
2005-09-22 07:21:50 -07:00
|
|
|
{ return caml_copy_nativeint((intnat)(Double_val(v))); }
|
2000-04-18 07:41:13 -07:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_to_float(value v)
|
2004-01-02 11:23:29 -08:00
|
|
|
{ return caml_copy_double((double)(Nativeint_val(v))); }
|
2000-04-18 07:41:13 -07:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_of_int32(value v)
|
|
|
|
{ return caml_copy_nativeint(Int32_val(v)); }
|
2000-03-05 11:17:54 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_to_int32(value v)
|
|
|
|
{ return caml_copy_int32(Nativeint_val(v)); }
|
2000-03-05 11:17:54 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_compare(value v1, value v2)
|
2003-04-01 00:46:39 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat i1 = Nativeint_val(v1);
|
|
|
|
intnat i2 = Nativeint_val(v2);
|
2003-04-01 00:46:39 -08:00
|
|
|
int res = (i1 > i2) - (i1 < i2);
|
|
|
|
return Val_int(res);
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_format(value fmt, value arg)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2001-02-05 00:51:56 -08:00
|
|
|
char format_string[FORMAT_BUFFER_SIZE];
|
|
|
|
char default_format_buffer[FORMAT_BUFFER_SIZE];
|
2000-02-11 07:09:27 -08:00
|
|
|
char * buffer;
|
2003-03-31 00:41:58 -08:00
|
|
|
char conv;
|
2000-02-11 07:09:27 -08:00
|
|
|
value res;
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
buffer = parse_format(fmt, ARCH_INTNAT_PRINTF_FORMAT,
|
|
|
|
format_string, default_format_buffer, &conv);
|
2000-02-11 07:09:27 -08:00
|
|
|
sprintf(buffer, format_string, (long) Nativeint_val(arg));
|
2003-12-29 14:15:02 -08:00
|
|
|
res = caml_copy_string(buffer);
|
2003-12-31 06:20:40 -08:00
|
|
|
if (buffer != default_format_buffer) caml_stat_free(buffer);
|
2000-02-11 07:09:27 -08:00
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
CAMLprim value caml_nativeint_of_string(value s)
|
2000-02-11 07:09:27 -08:00
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
return caml_copy_nativeint(parse_intnat(s, 8 * sizeof(value)));
|
2000-02-11 07:09:27 -08:00
|
|
|
}
|