summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2003-12-16 18:09:44 +0000
committerDamien Doligez <damien.doligez-inria.fr>2003-12-16 18:09:44 +0000
commitaa46693dc5810998b2668c31a8649c31f0f2e49c (patch)
treee9548200a8d76ee9d3d1dbe0a776aa5b32d01f4c
parenta90b6e9d1279612493dec0a50185bcdc8392807c (diff)
depollution (PR#1914, PR#1956)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6023 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--asmrun/stack.h6
-rw-r--r--asmrun/startup.c2
-rwxr-xr-xboot/ocamlcbin945598 -> 945938 bytes
-rwxr-xr-xboot/ocamllexbin144741 -> 144881 bytes
-rw-r--r--bytecomp/bytegen.ml8
-rw-r--r--bytecomp/matching.ml2
-rw-r--r--bytecomp/translcore.ml15
-rw-r--r--byterun/compare.c4
-rw-r--r--byterun/compatibility.h39
-rw-r--r--byterun/extern.c2
-rw-r--r--byterun/floats.c2
-rw-r--r--byterun/hash.c2
-rw-r--r--byterun/ints.c6
-rw-r--r--byterun/mlvalues.h2
-rw-r--r--byterun/startup.c4
-rw-r--r--byterun/str.c51
-rw-r--r--byterun/sys.c34
-rw-r--r--byterun/sys.h2
-rw-r--r--camlp4/etc/pr_r.ml2
-rw-r--r--otherlibs/unix/unix.ml2
-rw-r--r--stdlib/char.ml4
-rw-r--r--stdlib/filename.ml2
-rw-r--r--stdlib/pervasives.ml4
-rw-r--r--stdlib/random.ml2
-rw-r--r--stdlib/stdLabels.mli8
-rw-r--r--stdlib/string.ml8
-rw-r--r--stdlib/string.mli6
-rw-r--r--stdlib/stringLabels.mli6
-rw-r--r--stdlib/sys.ml22
-rw-r--r--stdlib/sys.mli18
30 files changed, 148 insertions, 117 deletions
diff --git a/asmrun/stack.h b/asmrun/stack.h
index 265b42d26..dd7069099 100644
--- a/asmrun/stack.h
+++ b/asmrun/stack.h
@@ -15,8 +15,8 @@
/* Machine-dependent interface with the asm code */
-#ifndef _stack_
-#define _stack_
+#ifndef CAML_STACK_H
+#define CAML_STACK_H
/* Macros to access the stack frame */
#ifdef TARGET_alpha
@@ -102,4 +102,4 @@ extern long caml_globals_inited;
extern long * caml_frametable[];
-#endif /* _stack_ */
+#endif /* CAML_STACK_H */
diff --git a/asmrun/startup.c b/asmrun/startup.c
index b3ae46d3c..24bd6e4f2 100644
--- a/asmrun/startup.c
+++ b/asmrun/startup.c
@@ -142,7 +142,7 @@ void caml_main(char **argv)
if (executable_name(proc_self_exe, sizeof(proc_self_exe)) == 0)
exe_name = proc_self_exe;
#endif
- sys_init(exe_name, argv);
+ caml_sys_init(exe_name, argv);
if (sigsetjmp(caml_termination_jmpbuf.buf, 0)) {
if (caml_termination_hook != NULL) caml_termination_hook(NULL);
return;
diff --git a/boot/ocamlc b/boot/ocamlc
index fd4e9f7f1..44efea801 100755
--- a/boot/ocamlc
+++ b/boot/ocamlc
Binary files differ
diff --git a/boot/ocamllex b/boot/ocamllex
index a77d1c946..2eae79605 100755
--- a/boot/ocamllex
+++ b/boot/ocamllex
Binary files differ
diff --git a/bytecomp/bytegen.ml b/bytecomp/bytegen.ml
index 18651b3dd..c22b8b58f 100644
--- a/bytecomp/bytegen.ml
+++ b/bytecomp/bytegen.ml
@@ -304,9 +304,9 @@ let comp_primitive p args =
| Pfloatcomp Cgt -> Kccall("gt_float", 2)
| Pfloatcomp Cle -> Kccall("le_float", 2)
| Pfloatcomp Cge -> Kccall("ge_float", 2)
- | Pstringlength -> Kccall("ml_string_length", 1)
- | Pstringrefs -> Kccall("string_get", 2)
- | Pstringsets -> Kccall("string_set", 3)
+ | Pstringlength -> Kccall("caml_ml_string_length", 1)
+ | Pstringrefs -> Kccall("caml_string_get", 2)
+ | Pstringsets -> Kccall("caml_string_set", 3)
| Pstringrefu -> Kgetstringchar
| Pstringsetu -> Ksetstringchar
| Parraylength kind -> Kvectlength
@@ -324,7 +324,7 @@ let comp_primitive p args =
| Parraysetu _ -> Ksetvectitem
| Pisint -> Kisint
| Pisout -> Kisout
- | Pbittest -> Kccall("bitvect_test", 2)
+ | Pbittest -> Kccall("caml_bitvect_test", 2)
| Pbintofint bi -> comp_bint_primitive bi "of_int" args
| Pintofbint bi -> comp_bint_primitive bi "to_int" args
| Pcvtbint(Pint32, Pnativeint) -> Kccall("nativeint_of_int32", 1)
diff --git a/bytecomp/matching.ml b/bytecomp/matching.ml
index 577c29050..5f5d3156a 100644
--- a/bytecomp/matching.ml
+++ b/bytecomp/matching.ml
@@ -1456,7 +1456,7 @@ let make_offset x arg = if x=0 then arg else Lprim(Poffsetint(x), [arg])
let prim_string_notequal =
- Pccall{prim_name = "string_notequal";
+ Pccall{prim_name = "caml_string_notequal";
prim_arity = 2; prim_alloc = false;
prim_native_name = ""; prim_native_float = false}
diff --git a/bytecomp/translcore.ml b/bytecomp/translcore.ml
index 49f4bd8ae..53e122f60 100644
--- a/bytecomp/translcore.ml
+++ b/bytecomp/translcore.ml
@@ -48,7 +48,8 @@ let comparisons_table = create_hashtable 11 [
prim_native_name = ""; prim_native_float = false},
Pintcomp Ceq,
Pfloatcomp Ceq,
- Pccall{prim_name = "string_equal"; prim_arity = 2; prim_alloc = false;
+ Pccall{prim_name = "caml_string_equal"; prim_arity = 2;
+ prim_alloc = false;
prim_native_name = ""; prim_native_float = false},
Pbintcomp(Pnativeint, Ceq),
Pbintcomp(Pint32, Ceq),
@@ -58,7 +59,7 @@ let comparisons_table = create_hashtable 11 [
prim_native_name = ""; prim_native_float = false},
Pintcomp Cneq,
Pfloatcomp Cneq,
- Pccall{prim_name = "string_notequal"; prim_arity = 2;
+ Pccall{prim_name = "caml_string_notequal"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
Pbintcomp(Pnativeint, Cneq),
@@ -69,7 +70,7 @@ let comparisons_table = create_hashtable 11 [
prim_native_name = ""; prim_native_float = false},
Pintcomp Clt,
Pfloatcomp Clt,
- Pccall{prim_name = "string_lessthan"; prim_arity = 2;
+ Pccall{prim_name = "caml_string_lessthan"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
Pbintcomp(Pnativeint, Clt),
@@ -80,7 +81,7 @@ let comparisons_table = create_hashtable 11 [
prim_native_name = ""; prim_native_float = false},
Pintcomp Cgt,
Pfloatcomp Cgt,
- Pccall{prim_name = "string_greaterthan"; prim_arity = 2;
+ Pccall{prim_name = "caml_string_greaterthan"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
Pbintcomp(Pnativeint, Cgt),
@@ -91,7 +92,7 @@ let comparisons_table = create_hashtable 11 [
prim_native_name = ""; prim_native_float = false},
Pintcomp Cle,
Pfloatcomp Cle,
- Pccall{prim_name = "string_lessequal"; prim_arity = 2;
+ Pccall{prim_name = "caml_string_lessequal"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
Pbintcomp(Pnativeint, Cle),
@@ -102,7 +103,7 @@ let comparisons_table = create_hashtable 11 [
prim_native_name = ""; prim_native_float = false},
Pintcomp Cge,
Pfloatcomp Cge,
- Pccall{prim_name = "string_greaterequal"; prim_arity = 2;
+ Pccall{prim_name = "caml_string_greaterequal"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
Pbintcomp(Pnativeint, Cge),
@@ -117,7 +118,7 @@ let comparisons_table = create_hashtable 11 [
Pccall{prim_name = "float_compare"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
- Pccall{prim_name = "string_compare"; prim_arity = 2;
+ Pccall{prim_name = "caml_string_compare"; prim_arity = 2;
prim_alloc = false; prim_native_name = "";
prim_native_float = false},
Pccall{prim_name = "nativeint_compare"; prim_arity = 2;
diff --git a/byterun/compare.c b/byterun/compare.c
index 220682316..bf5b6e4dd 100644
--- a/byterun/compare.c
+++ b/byterun/compare.c
@@ -137,8 +137,8 @@ static long compare_val(value v1, value v2, int total)
mlsize_t len1, len2, len;
unsigned char * p1, * p2;
if (v1 == v2) break;
- len1 = string_length(v1);
- len2 = string_length(v2);
+ len1 = caml_string_length(v1);
+ len2 = caml_string_length(v2);
for (len = (len1 <= len2 ? len1 : len2),
p1 = (unsigned char *) String_val(v1),
p2 = (unsigned char *) String_val(v2);
diff --git a/byterun/compatibility.h b/byterun/compatibility.h
index de5f987c1..df520fedb 100644
--- a/byterun/compatibility.h
+++ b/byterun/compatibility.h
@@ -30,7 +30,7 @@
/* **** debugger.c */
/* **** dynlink.c */
/* **** extern.c */
-/* **** fail.c */
+/* **** fail.c check asmrun */
/* **** finalise.c */
/* **** fix_code.c */
/* **** floats.c */
@@ -57,17 +57,46 @@
/* **** parsing.c */
/* **** prims.c */
/* **** printexc.c */
-/* **** roots.c */
+/* **** roots.c check asmrun */
/* **** rotatecursor.c */
-/* **** signals.c */
+/* **** signals.c check asmrun */
/* **** stacks.c */
-/* **** startup.c */
+/* **** startup.c check asmrun */
/* **** str.c */
+#define string_length caml_string_length
+/* ml_string_length -> caml_ml_string_length */
+/* create_string -> caml_create_string */
+/* string_get -> caml_string_get */
+/* string_set -> caml_string_set */
+/* string_equal -> caml_string_equal */
+/* string_notequal -> caml_string_notequal */
+/* string_compare -> caml_string_compare */
+/* string_lessthan -> caml_string_lessthan */
+/* string_lessequal -> caml_string_lessequal */
+/* string_greaterthan -> caml_string_greaterthan */
+/* string_greaterequal -> caml_string_greaterequal */
+/* blit_string -> caml_blit_string */
+/* fill_string -> caml_fill_string */
+/* is_printable -> caml_is_printable */
+/* bitvect_test -> caml_bitvect_test */
/* **** sys.c */
-/* sys_open -> caml_sys_open */
#define sys_error caml_sys_error
#define sys_exit caml_sys_exit
+/* sys_open -> caml_sys_open */
+/* sys_close -> caml_sys_close */
+/* sys_file_exists -> caml_sys_file_exists */
+/* sys_remove -> caml_sys_remove */
+/* sys_chdir -> caml_sys_chdir */
+/* sys_getcwd -> caml_sys_getcwd */
+/* sys_getenv -> caml_sys_getenv */
+/* sys_get_argv -> caml_sys_get_argv */
+/* g sys_init -> caml_sys_init */
+/* sys_system_command -> caml_sys_system_command */
+/* sys_time -> caml_sys_time */
+/* sys_random_seed -> caml_sys_random_seed */
+/* sys_get_config -> caml_sys_get_config */
+/* sys_read_directory -> caml_sys_read_directory */
/* **** terminfo.c */
/* **** unix.c */
diff --git a/byterun/extern.c b/byterun/extern.c
index 4d534b2eb..d9beb235d 100644
--- a/byterun/extern.c
+++ b/byterun/extern.c
@@ -294,7 +294,7 @@ static void extern_rec(value v)
/* Output the contents of the object */
switch(tag) {
case String_tag: {
- mlsize_t len = string_length(v);
+ mlsize_t len = caml_string_length(v);
if (len < 0x20) {
Write(PREFIX_SMALL_STRING + len);
} else if (len < 0x100) {
diff --git a/byterun/floats.c b/byterun/floats.c
index 5aa6efbc0..32e0c296e 100644
--- a/byterun/floats.c
+++ b/byterun/floats.c
@@ -113,7 +113,7 @@ CAMLprim value float_of_string(value vs)
mlsize_t len;
double d;
- len = string_length(vs);
+ len = caml_string_length(vs);
buf = len < sizeof(parse_buffer) ? parse_buffer : stat_alloc(len + 1);
src = String_val(vs);
dst = buf;
diff --git a/byterun/hash.c b/byterun/hash.c
index 4741d690d..a6e3970fd 100644
--- a/byterun/hash.c
+++ b/byterun/hash.c
@@ -67,7 +67,7 @@ static void hash_aux(value obj)
switch (tag) {
case String_tag:
hash_univ_count--;
- i = string_length(obj);
+ i = caml_string_length(obj);
for (p = &Byte_u(obj, 0); i > 0; i--, p++)
Combine_small(*p);
break;
diff --git a/byterun/ints.c b/byterun/ints.c
index 7cad6bbdf..6e4de92fe 100644
--- a/byterun/ints.c
+++ b/byterun/ints.c
@@ -79,7 +79,7 @@ static long parse_long(value s, int nbits)
/* Detect overflow in addition (base * res) + d */
if (res < (unsigned long) d) failwith("int_of_string");
}
- if (p != String_val(s) + string_length(s)) failwith("int_of_string");
+ if (p != String_val(s) + caml_string_length(s)) failwith("int_of_string");
if (base == 10) {
/* Signed representation expected, allow -2^(nbits-1) to 2^(nbits - 1) */
if (res > 1UL << (nbits - 1))
@@ -139,7 +139,7 @@ static char * parse_format(value fmt,
/* Copy Caml format fmt to format_string,
adding the suffix before the last letter of the format */
- len = string_length(fmt);
+ len = caml_string_length(fmt);
len_suffix = strlen(suffix);
if (len + len_suffix + 1 >= FORMAT_BUFFER_SIZE)
invalid_argument("format_int: format too long");
@@ -523,7 +523,7 @@ CAMLprim value int64_of_string(value s)
/* Detect overflow in addition (base * res) + d */
if (I64_ult(res, I64_of_int32(d))) failwith("int_of_string");
}
- if (p != String_val(s) + string_length(s)) failwith("int_of_string");
+ if (p != String_val(s) + caml_string_length(s)) failwith("int_of_string");
if (base == 10 && I64_ult(max_int64, res)) failwith("int_of_string");
if (sign < 0) res = I64_neg(res);
return copy_int64(res);
diff --git a/byterun/mlvalues.h b/byterun/mlvalues.h
index 2fca33f16..a3bbad312 100644
--- a/byterun/mlvalues.h
+++ b/byterun/mlvalues.h
@@ -215,7 +215,7 @@ CAMLextern value hash_variant(char * tag);
/* Strings. */
#define String_tag 252
#define String_val(x) ((char *) Bp_val(x))
-CAMLextern mlsize_t string_length (value); /* size in bytes */
+CAMLextern mlsize_t caml_string_length (value); /* size in bytes */
/* Floating-point numbers. */
#define Double_tag 253
diff --git a/byterun/startup.c b/byterun/startup.c
index 83e4afbdf..166951d18 100644
--- a/byterun/startup.c
+++ b/byterun/startup.c
@@ -393,7 +393,7 @@ CAMLexport void caml_main(char **argv)
oldify_mopup ();
/* Initialize system libraries */
init_exceptions();
- sys_init(exe_name, argv + pos);
+ caml_sys_init(exe_name, argv + pos);
#ifdef _WIN32
/* Start a thread to handle signals */
if (getenv("CAMLSIGPIPE"))
@@ -448,7 +448,7 @@ CAMLexport void caml_startup_code(code_t code, asize_t code_size,
oldify_mopup ();
/* Run the code */
init_exceptions();
- sys_init("", argv);
+ caml_sys_init("", argv);
res = interprete(start_code, code_size);
if (Is_exception_result(res))
fatal_uncaught_exception(Extract_exception(res));
diff --git a/byterun/str.c b/byterun/str.c
index e5588fdcf..347e5bcb9 100644
--- a/byterun/str.c
+++ b/byterun/str.c
@@ -25,7 +25,7 @@
#include <locale.h>
#endif
-CAMLexport mlsize_t string_length(value s)
+CAMLexport mlsize_t caml_string_length(value s)
{
mlsize_t temp;
temp = Bosize_val(s) - 1;
@@ -33,7 +33,7 @@ CAMLexport mlsize_t string_length(value s)
return temp - Byte (s, temp);
}
-CAMLprim value ml_string_length(value s)
+CAMLprim value caml_ml_string_length(value s)
{
mlsize_t temp;
temp = Bosize_val(s) - 1;
@@ -41,29 +41,29 @@ CAMLprim value ml_string_length(value s)
return Val_long(temp - Byte (s, temp));
}
-CAMLprim value create_string(value len)
+CAMLprim value caml_create_string(value len)
{
mlsize_t size = Long_val(len);
if (size > Bsize_wsize (Max_wosize) - 1) invalid_argument("String.create");
return alloc_string(size);
}
-CAMLprim value string_get(value str, value index)
+CAMLprim value caml_string_get(value str, value index)
{
long idx = Long_val(index);
- if (idx < 0 || idx >= string_length(str)) array_bound_error();
+ if (idx < 0 || idx >= caml_string_length(str)) array_bound_error();
return Val_int(Byte_u(str, idx));
}
-CAMLprim value string_set(value str, value index, value newval)
+CAMLprim value caml_string_set(value str, value index, value newval)
{
long idx = Long_val(index);
- if (idx < 0 || idx >= string_length(str)) array_bound_error();
+ if (idx < 0 || idx >= caml_string_length(str)) array_bound_error();
Byte_u(str, idx) = Int_val(newval);
return Val_unit;
}
-CAMLprim value string_equal(value s1, value s2)
+CAMLprim value caml_string_equal(value s1, value s2)
{
mlsize_t sz1 = Wosize_val(s1);
mlsize_t sz2 = Wosize_val(s2);
@@ -74,18 +74,18 @@ CAMLprim value string_equal(value s1, value s2)
return Val_true;
}
-CAMLprim value string_notequal(value s1, value s2)
+CAMLprim value caml_string_notequal(value s1, value s2)
{
- return Val_not(string_equal(s1, s2));
+ return Val_not(caml_string_equal(s1, s2));
}
-CAMLprim value string_compare(value s1, value s2)
+CAMLprim value caml_string_compare(value s1, value s2)
{
mlsize_t len1, len2, len;
int res;
- len1 = string_length(s1);
- len2 = string_length(s2);
+ len1 = caml_string_length(s1);
+ len2 = caml_string_length(s2);
res = memcmp(String_val(s1), String_val(s2), len1 <= len2 ? len1 : len2);
if (res < 0) return Val_int(-1);
if (res > 0) return Val_int(1);
@@ -94,39 +94,40 @@ CAMLprim value string_compare(value s1, value s2)
return Val_int(0);
}
-CAMLprim value string_lessthan(value s1, value s2)
+CAMLprim value caml_string_lessthan(value s1, value s2)
{
- return string_compare(s1, s2) < Val_int(0) ? Val_true : Val_false;
+ return caml_string_compare(s1, s2) < Val_int(0) ? Val_true : Val_false;
}
-CAMLprim value string_lessequal(value s1, value s2)
+CAMLprim value caml_string_lessequal(value s1, value s2)
{
- return string_compare(s1, s2) <= Val_int(0) ? Val_true : Val_false;
+ return caml_string_compare(s1, s2) <= Val_int(0) ? Val_true : Val_false;
}
-CAMLprim value string_greaterthan(value s1, value s2)
+CAMLprim value caml_string_greaterthan(value s1, value s2)
{
- return string_compare(s1, s2) > Val_int(0) ? Val_true : Val_false;
+ return caml_string_compare(s1, s2) > Val_int(0) ? Val_true : Val_false;
}
-CAMLprim value string_greaterequal(value s1, value s2)
+CAMLprim value caml_string_greaterequal(value s1, value s2)
{
- return string_compare(s1, s2) >= Val_int(0) ? Val_true : Val_false;
+ return caml_string_compare(s1, s2) >= Val_int(0) ? Val_true : Val_false;
}
-CAMLprim value blit_string(value s1, value ofs1, value s2, value ofs2, value n)
+CAMLprim value caml_blit_string(value s1, value ofs1, value s2, value ofs2,
+ value n)
{
memmove(&Byte(s2, Long_val(ofs2)), &Byte(s1, Long_val(ofs1)), Int_val(n));
return Val_unit;
}
-CAMLprim value fill_string(value s, value offset, value len, value init)
+CAMLprim value caml_fill_string(value s, value offset, value len, value init)
{
memset(&Byte(s, Long_val(offset)), Int_val(init), Long_val(len));
return Val_unit;
}
-CAMLprim value is_printable(value chr)
+CAMLprim value caml_is_printable(value chr)
{
int c;
@@ -141,7 +142,7 @@ CAMLprim value is_printable(value chr)
return Val_bool(isprint(c));
}
-CAMLprim value bitvect_test(value bv, value n)
+CAMLprim value caml_bitvect_test(value bv, value n)
{
int pos = Int_val(n);
return Val_int(Byte_u(bv, pos >> 3) & (1 << (pos & 7)));
diff --git a/byterun/sys.c b/byterun/sys.c
index 561b07a78..ae4cb3b87 100644
--- a/byterun/sys.c
+++ b/byterun/sys.c
@@ -106,7 +106,7 @@ CAMLexport void caml_sys_error(value arg)
str = copy_string(err);
} else {
int err_len = strlen(err);
- int arg_len = string_length(arg);
+ int arg_len = caml_string_length(arg);
str = alloc_string(arg_len + 2 + err_len);
memmove(&Byte(str, 0), String_val(arg), arg_len);
memmove(&Byte(str, arg_len), ": ", 2);
@@ -154,7 +154,7 @@ CAMLprim value caml_sys_open(value path, value flags, value perm)
int fd;
char * p;
- p = stat_alloc(string_length(path) + 1);
+ p = stat_alloc(caml_string_length(path) + 1);
strcpy(p, String_val(path));
/* open on a named FIFO can block (PR#1533) */
enter_blocking_section();
@@ -172,13 +172,13 @@ CAMLprim value caml_sys_open(value path, value flags, value perm)
CAMLreturn(Val_long(fd));
}
-CAMLprim value sys_close(value fd)
+CAMLprim value caml_sys_close(value fd)
{
close(Int_val(fd));
return Val_unit;
}
-CAMLprim value sys_file_exists(value name)
+CAMLprim value caml_sys_file_exists(value name)
{
#if macintosh
int f;
@@ -192,7 +192,7 @@ CAMLprim value sys_file_exists(value name)
#endif
}
-CAMLprim value sys_remove(value name)
+CAMLprim value caml_sys_remove(value name)
{
int ret;
ret = unlink(String_val(name));
@@ -200,20 +200,20 @@ CAMLprim value sys_remove(value name)
return Val_unit;
}
-CAMLprim value sys_rename(value oldname, value newname)
+CAMLprim value caml_sys_rename(value oldname, value newname)
{
if (rename(String_val(oldname), String_val(newname)) != 0)
caml_sys_error(oldname);
return Val_unit;
}
-CAMLprim value sys_chdir(value dirname)
+CAMLprim value caml_sys_chdir(value dirname)
{
if (chdir(String_val(dirname)) != 0) caml_sys_error(dirname);
return Val_unit;
}
-CAMLprim value sys_getcwd(value unit)
+CAMLprim value caml_sys_getcwd(value unit)
{
char buff[4096];
#ifdef HAS_GETCWD
@@ -224,7 +224,7 @@ CAMLprim value sys_getcwd(value unit)
return copy_string(buff);
}
-CAMLprim value sys_getenv(value var)
+CAMLprim value caml_sys_getenv(value var)
{
char * res;
@@ -236,7 +236,7 @@ CAMLprim value sys_getenv(value var)
char * caml_exe_name;
static char ** caml_main_argv;
-CAMLprim value sys_get_argv(value unit)
+CAMLprim value caml_sys_get_argv(value unit)
{
CAMLparam0 (); /* unit is unused */
CAMLlocal3 (exe_name, argv, res);
@@ -248,7 +248,7 @@ CAMLprim value sys_get_argv(value unit)
CAMLreturn(res);
}
-void sys_init(char * exe_name, char **argv)
+void caml_sys_init(char * exe_name, char **argv)
{
caml_exe_name = exe_name;
caml_main_argv = argv;
@@ -265,14 +265,14 @@ void sys_init(char * exe_name, char **argv)
#endif
#endif
-CAMLprim value sys_system_command(value command)
+CAMLprim value caml_sys_system_command(value command)
{
CAMLparam1 (command);
int status, retcode;
char *buf;
unsigned long len;
- len = string_length (command);
+ len = caml_string_length (command);
buf = stat_alloc (len + 1);
memmove (buf, String_val (command), len + 1);
enter_blocking_section ();
@@ -287,7 +287,7 @@ CAMLprim value sys_system_command(value command)
CAMLreturn (Val_int(retcode));
}
-CAMLprim value sys_time(value unit)
+CAMLprim value caml_sys_time(value unit)
{
#ifdef HAS_TIMES
#ifndef CLK_TCK
@@ -306,7 +306,7 @@ CAMLprim value sys_time(value unit)
#endif
}
-CAMLprim value sys_random_seed (value unit)
+CAMLprim value caml_sys_random_seed (value unit)
{
long seed;
#ifdef HAS_GETTIMEOFDAY
@@ -322,7 +322,7 @@ CAMLprim value sys_random_seed (value unit)
return Val_long(seed);
}
-CAMLprim value sys_get_config(value unit)
+CAMLprim value caml_sys_get_config(value unit)
{
CAMLparam0 (); /* unit is unused */
CAMLlocal2 (result, ostype);
@@ -334,7 +334,7 @@ CAMLprim value sys_get_config(value unit)
CAMLreturn (result);
}
-CAMLprim value sys_read_directory(value path)
+CAMLprim value caml_sys_read_directory(value path)
{
CAMLparam1(path);
CAMLlocal1(result);
diff --git a/byterun/sys.h b/byterun/sys.h
index 86daa7b7b..ef2354275 100644
--- a/byterun/sys.h
+++ b/byterun/sys.h
@@ -21,7 +21,7 @@
#define NO_ARG Val_int(0)
CAMLextern void caml_sys_error (value);
-extern void sys_init (char * exe_name, char ** argv);
+extern void caml_sys_init (char * exe_name, char ** argv);
CAMLextern value caml_sys_exit (value);
extern char * caml_exe_name;
diff --git a/camlp4/etc/pr_r.ml b/camlp4/etc/pr_r.ml
index eb14e7376..bedff1936 100644
--- a/camlp4/etc/pr_r.ml
+++ b/camlp4/etc/pr_r.ml
@@ -28,7 +28,7 @@ value gen_where = ref True;
value old_sequences = ref False;
value expand_declare = ref False;
-external is_printable : char -> bool = "is_printable";
+external is_printable : char -> bool = "caml_is_printable";
value char_escaped =
fun
diff --git a/otherlibs/unix/unix.ml b/otherlibs/unix/unix.ml
index daa24e61e..f476d8287 100644
--- a/otherlibs/unix/unix.ml
+++ b/otherlibs/unix/unix.ml
@@ -109,7 +109,7 @@ let handle_unix_error f arg =
exit 2
external environment : unit -> string array = "unix_environment"
-external getenv: string -> string = "sys_getenv"
+external getenv: string -> string = "caml_sys_getenv"
external putenv: string -> string -> unit = "unix_putenv"
type process_status =
diff --git a/stdlib/char.ml b/stdlib/char.ml
index 012317e0e..a316dab12 100644
--- a/stdlib/char.ml
+++ b/stdlib/char.ml
@@ -21,9 +21,9 @@ external unsafe_chr: int -> char = "%identity"
let chr n =
if n < 0 or n > 255 then invalid_arg "Char.chr" else unsafe_chr n
-external is_printable: char -> bool = "is_printable"
+external is_printable: char -> bool = "caml_is_printable"
-external string_create: int -> string = "create_string"
+external string_create: int -> string = "caml_create_string"
external string_unsafe_get : string -> int -> char = "%string_unsafe_get"
external string_unsafe_set : string -> int -> char -> unit
= "%string_unsafe_set"
diff --git a/stdlib/filename.ml b/stdlib/filename.ml
index 96f5aafa0..15f65e0dd 100644
--- a/stdlib/filename.ml
+++ b/stdlib/filename.ml
@@ -213,7 +213,7 @@ let chop_extension name =
invalid_arg "Filename.chop_extension"
external open_desc: string -> open_flag list -> int -> int = "caml_sys_open"
-external close_desc: int -> unit = "sys_close"
+external close_desc: int -> unit = "caml_sys_close"
let prng = Random.State.make_self_init ();;
diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml
index 1aa3c439a..b31da0259 100644
--- a/stdlib/pervasives.ml
+++ b/stdlib/pervasives.ml
@@ -137,9 +137,9 @@ external classify_float: float -> fpclass = "classify_float"
(* String operations -- more in module String *)
external string_length : string -> int = "%string_length"
-external string_create: int -> string = "create_string"
+external string_create: int -> string = "caml_create_string"
external string_blit : string -> int -> string -> int -> int -> unit
- = "blit_string" "noalloc"
+ = "caml_blit_string" "noalloc"
let (^) s1 s2 =
let l1 = string_length s1 and l2 = string_length s2 in
diff --git a/stdlib/random.ml b/stdlib/random.ml
index 9374cb6c6..bdf238fd4 100644
--- a/stdlib/random.ml
+++ b/stdlib/random.ml
@@ -20,7 +20,7 @@
It is seeded by a MD5-based PRNG.
*)
-external random_seed: unit -> int = "sys_random_seed";;
+external random_seed: unit -> int = "caml_sys_random_seed";;
module State = struct
diff --git a/stdlib/stdLabels.mli b/stdlib/stdLabels.mli
index 08ec70f5a..509eccb62 100644
--- a/stdlib/stdLabels.mli
+++ b/stdlib/stdLabels.mli
@@ -104,7 +104,7 @@ module String :
external length : string -> int = "%string_length"
external get : string -> int -> char = "%string_safe_get"
external set : string -> int -> char -> unit = "%string_safe_set"
- external create : int -> string = "create_string"
+ external create : int -> string = "caml_create_string"
val make : int -> char -> string
val copy : string -> string
val sub : string -> pos:int -> len:int -> string
@@ -130,7 +130,7 @@ module String :
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
external unsafe_blit :
src:string -> src_pos:int -> dst:string -> dst_pos:int -> len:int ->
- unit = "blit_string" "noalloc"
- external unsafe_fill :
- string -> pos:int -> len:int -> char -> unit = "fill_string" "noalloc"
+ unit = "caml_blit_string" "noalloc"
+ external unsafe_fill : string -> pos:int -> len:int -> char -> unit
+ = "caml_fill_string" "noalloc"
end
diff --git a/stdlib/string.ml b/stdlib/string.ml
index 6f2495c7e..00b4b3d83 100644
--- a/stdlib/string.ml
+++ b/stdlib/string.ml
@@ -18,13 +18,13 @@
external length : string -> int = "%string_length"
external get : string -> int -> char = "%string_safe_get"
external set : string -> int -> char -> unit = "%string_safe_set"
-external create : int -> string = "create_string"
+external create : int -> string = "caml_create_string"
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
external unsafe_blit : string -> int -> string -> int -> int -> unit
- = "blit_string" "noalloc"
+ = "caml_blit_string" "noalloc"
external unsafe_fill : string -> int -> int -> char -> unit
- = "fill_string" "noalloc"
+ = "caml_fill_string" "noalloc"
let make n c =
let s = create n in
@@ -78,7 +78,7 @@ let concat sep l =
tl;
r
-external is_printable: char -> bool = "is_printable"
+external is_printable: char -> bool = "caml_is_printable"
external char_code: char -> int = "%identity"
external char_chr: int -> char = "%identity"
diff --git a/stdlib/string.mli b/stdlib/string.mli
index 3bdc12783..4e8aea4f4 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -35,7 +35,7 @@ external set : string -> int -> char -> unit = "%string_safe_set"
Raise [Invalid_argument "index out of bounds"]
if [n] is outside the range 0 to [(String.length s - 1)]. *)
-external create : int -> string = "create_string"
+external create : int -> string = "caml_create_string"
(** [String.create n] returns a fresh string of length [n].
The string initially contains arbitrary characters.
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_string_length].
@@ -157,6 +157,6 @@ val compare: t -> t -> int
external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
external unsafe_blit :
- string -> int -> string -> int -> int -> unit = "blit_string" "noalloc"
+ string -> int -> string -> int -> int -> unit = "caml_blit_string" "noalloc"
external unsafe_fill :
- string -> int -> int -> char -> unit = "fill_string" "noalloc"
+ string -> int -> int -> char -> unit = "caml_fill_string" "noalloc"
diff --git a/stdlib/stringLabels.mli b/stdlib/stringLabels.mli
index 884690e46..b1f957751 100644
--- a/stdlib/stringLabels.mli
+++ b/stdlib/stringLabels.mli
@@ -33,7 +33,7 @@ external set : string -> int -> char -> unit = "%string_safe_set"
0 to [(String.length s - 1)].
You can also write [s.[n] <- c] instead of [String.set s n c]. *)
-external create : int -> string = "create_string"
+external create : int -> string = "caml_create_string"
(** [String.create n] returns a fresh string of length [n].
The string initially contains arbitrary characters.
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_string_length].
@@ -149,6 +149,6 @@ external unsafe_get : string -> int -> char = "%string_unsafe_get"
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
external unsafe_blit :
src:string -> src_pos:int -> dst:string -> dst_pos:int -> len:int ->
- unit = "blit_string" "noalloc"
+ unit = "caml_blit_string" "noalloc"
external unsafe_fill :
- string -> pos:int -> len:int -> char -> unit = "fill_string" "noalloc"
+ string -> pos:int -> len:int -> char -> unit = "caml_fill_string" "noalloc"
diff --git a/stdlib/sys.ml b/stdlib/sys.ml
index c011554d0..cb53c8258 100644
--- a/stdlib/sys.ml
+++ b/stdlib/sys.ml
@@ -15,23 +15,23 @@
(* System interface *)
-external get_config: unit -> string * int = "sys_get_config"
-external get_argv: unit -> string * string array = "sys_get_argv"
+external get_config: unit -> string * int = "caml_sys_get_config"
+external get_argv: unit -> string * string array = "caml_sys_get_argv"
let (executable_name, argv) = get_argv()
let (os_type, word_size) = get_config()
let max_array_length = (1 lsl (word_size - 10)) - 1;;
let max_string_length = word_size / 8 * max_array_length - 1;;
-external file_exists: string -> bool = "sys_file_exists"
-external remove: string -> unit = "sys_remove"
-external rename : string -> string -> unit = "sys_rename"
-external getenv: string -> string = "sys_getenv"
-external command: string -> int = "sys_system_command"
-external time: unit -> float = "sys_time"
-external chdir: string -> unit = "sys_chdir"
-external getcwd: unit -> string = "sys_getcwd"
-external readdir : string -> string array = "sys_read_directory"
+external file_exists: string -> bool = "caml_sys_file_exists"
+external remove: string -> unit = "caml_sys_remove"
+external rename : string -> string -> unit = "caml_sys_rename"
+external getenv: string -> string = "caml_sys_getenv"
+external command: string -> int = "caml_sys_system_command"
+external time: unit -> float = "caml_sys_time"
+external chdir: string -> unit = "caml_sys_chdir"
+external getcwd: unit -> string = "caml_sys_getcwd"
+external readdir : string -> string array = "caml_sys_read_directory"
let interactive = ref false
diff --git a/stdlib/sys.mli b/stdlib/sys.mli
index 551e958a6..e1b871b08 100644
--- a/stdlib/sys.mli
+++ b/stdlib/sys.mli
@@ -24,34 +24,34 @@ val argv : string array
val executable_name : string
(** The name of the file containing the executable currently running. *)
-external file_exists : string -> bool = "sys_file_exists"
+external file_exists : string -> bool = "caml_sys_file_exists"
(** Test if a file with the given name exists. *)
-external remove : string -> unit = "sys_remove"
+external remove : string -> unit = "caml_sys_remove"
(** Remove the given file name from the file system. *)
-external rename : string -> string -> unit = "sys_rename"
+external rename : string -> string -> unit = "caml_sys_rename"
(** Rename a file. The first argument is the old name and the
second is the new name. *)
-external getenv : string -> string = "sys_getenv"
+external getenv : string -> string = "caml_sys_getenv"
(** Return the value associated to a variable in the process
environment. Raise [Not_found] if the variable is unbound. *)
-external command : string -> int = "sys_system_command"
+external command : string -> int = "caml_sys_system_command"
(** Execute the given shell command and return its exit code. *)
-external time : unit -> float = "sys_time"
+external time : unit -> float = "caml_sys_time"
(** Return the processor time, in seconds, used by the program
since the beginning of execution. *)
-external chdir : string -> unit = "sys_chdir"
+external chdir : string -> unit = "caml_sys_chdir"
(** Change the current working directory of the process. *)
-external getcwd : unit -> string = "sys_getcwd"
+external getcwd : unit -> string = "caml_sys_getcwd"
(** Return the current working directory of the process. *)
-external readdir : string -> string array = "sys_read_directory"
+external readdir : string -> string array = "caml_sys_read_directory"
(** Return the names of all files present in the given directory.
Names denoting the current directory and the parent directory
(["."] and [".."] in Unix) are not returned. Each string in the