summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--otherlibs/bigarray/bigarray_stubs.c2
-rw-r--r--otherlibs/db/dbstubs.c6
-rw-r--r--otherlibs/dbm/cldbm.c6
-rw-r--r--otherlibs/labltk/support/cltkMisc.c2
-rw-r--r--otherlibs/str/strstubs.c2
-rw-r--r--otherlibs/systhreads/posix.c6
-rw-r--r--otherlibs/threads/scheduler.c1
-rw-r--r--otherlibs/unix/gethost.c2
-rw-r--r--otherlibs/unix/putenv.c4
-rw-r--r--otherlibs/unix/read.c2
-rw-r--r--otherlibs/unix/sendrecv.c8
-rw-r--r--otherlibs/unix/socketaddr.c2
-rw-r--r--otherlibs/unix/write.c2
-rw-r--r--otherlibs/win32unix/read.c2
-rw-r--r--otherlibs/win32unix/sendrecv.c8
-rw-r--r--otherlibs/win32unix/write.c2
-rw-r--r--utils/config.mlp2
17 files changed, 29 insertions, 30 deletions
diff --git a/otherlibs/bigarray/bigarray_stubs.c b/otherlibs/bigarray/bigarray_stubs.c
index e7c1dc5e0..fa127f899 100644
--- a/otherlibs/bigarray/bigarray_stubs.c
+++ b/otherlibs/bigarray/bigarray_stubs.c
@@ -797,7 +797,7 @@ value bigarray_blit(value vsrc, value vdst)
bigarray_num_elts(src)
* bigarray_element_size[src->flags & BIGARRAY_KIND_MASK];
/* Do the copying */
- bcopy(src->data, dst->data, num_bytes);
+ memmove (dst->data, src->data, num_bytes);
return Val_unit;
blit_error:
invalid_argument("Bigarray.blit: dimension mismatch");
diff --git a/otherlibs/db/dbstubs.c b/otherlibs/db/dbstubs.c
index 698d6fa5f..d8d38e9a1 100644
--- a/otherlibs/db/dbstubs.c
+++ b/otherlibs/db/dbstubs.c
@@ -113,7 +113,7 @@ value caml_db_get(value cdb, value vkey, value vflags) /* ML */
case 0: /* success */
{
value res = alloc_string(data.size);
- bcopy(data.data, String_val(res), data.size);
+ memmove (String_val (res), data.data, data.size);
return res;
}
case 1: /* not found */
@@ -164,8 +164,8 @@ value caml_db_seq(value cdb, value vkey, value vflags) /* ML */
reskey = alloc_string(key.size);
resdata = alloc_string(data.size);
res = alloc_small(2, 0);
- bcopy(key.data, String_val(reskey), key.size);
- bcopy(data.data, String_val(resdata), data.size);
+ memmove (String_val (reskey), key.data, key.size);
+ memmove (String_val (resdata), data.data, data.size);
Field(res, 0) = reskey;
Field(res, 1) = resdata;
End_roots();
diff --git a/otherlibs/dbm/cldbm.c b/otherlibs/dbm/cldbm.c
index fa25899af..1ec8ca149 100644
--- a/otherlibs/dbm/cldbm.c
+++ b/otherlibs/dbm/cldbm.c
@@ -82,7 +82,7 @@ value caml_dbm_fetch(value vdb, value vkey) /* ML */
answer = dbm_fetch(extract_dbm(vdb), key);
if (answer.dptr) {
value res = alloc_string(answer.dsize);
- bcopy(answer.dptr,String_val(res),answer.dsize);
+ memmove (String_val (res), answer.dptr, answer.dsize);
return res;
}
else raise_not_found();
@@ -141,7 +141,7 @@ value caml_dbm_firstkey(value vdb) /* ML */
if (key.dptr) {
value res = alloc_string(key.dsize);
- bcopy(key.dptr,String_val(res),key.dsize);
+ memmove (String_val (res), key.dptr, key.dsize);
return res;
}
else raise_not_found();
@@ -153,7 +153,7 @@ value caml_dbm_nextkey(value vdb) /* ML */
if (key.dptr) {
value res = alloc_string(key.dsize);
- bcopy(key.dptr,String_val(res),key.dsize);
+ memmove (String_val (res), key.dptr, key.dsize);
return res;
}
else raise_not_found();
diff --git a/otherlibs/labltk/support/cltkMisc.c b/otherlibs/labltk/support/cltkMisc.c
index 2640427a7..f16928fb8 100644
--- a/otherlibs/labltk/support/cltkMisc.c
+++ b/otherlibs/labltk/support/cltkMisc.c
@@ -50,7 +50,7 @@ char *string_to_c(value s)
{
int l = string_length(s);
char *res = stat_alloc(l + 1);
- bcopy(String_val(s),res,l);
+ memmove (res, String_val (s), l);
res[l] = '\0';
return res;
}
diff --git a/otherlibs/str/strstubs.c b/otherlibs/str/strstubs.c
index ef8fe96c9..d4427152a 100644
--- a/otherlibs/str/strstubs.c
+++ b/otherlibs/str/strstubs.c
@@ -209,7 +209,7 @@ value str_replacement_text(value repl, value orig) /* ML */
case '5': case '6': case '7': case '8': case '9':
c -= '0';
len = end_regs[c] - start_regs[c];
- bcopy(&Byte(orig, start_regs[c]), q, len);
+ memmove (q, &Byte(orig, start_regs[c]), len);
q += len;
break;
default:
diff --git a/otherlibs/systhreads/posix.c b/otherlibs/systhreads/posix.c
index d46eb6310..5579d504b 100644
--- a/otherlibs/systhreads/posix.c
+++ b/otherlibs/systhreads/posix.c
@@ -698,8 +698,8 @@ static void caml_pthread_check(int retcode, char *msg)
msglen = strlen(msg);
errlen = strlen(err);
str = alloc_string(msglen + 2 + errlen);
- bcopy(msg, &Byte(str, 0), msglen);
- bcopy(": ", &Byte(str, msglen), 2);
- bcopy(err, &Byte(str, msglen + 2), errlen);
+ memmove (&Byte(str, 0), msg, msglen);
+ memmove (&Byte(str, msglen), ": ", 2);
+ memmove (&Byte(str, msglen + 2), err, errlen);
raise_sys_error(str);
}
diff --git a/otherlibs/threads/scheduler.c b/otherlibs/threads/scheduler.c
index 8d85c4958..f42ce6184 100644
--- a/otherlibs/threads/scheduler.c
+++ b/otherlibs/threads/scheduler.c
@@ -14,7 +14,6 @@
/* The thread scheduler */
-/* <string.h> must be included before we rededfine bcopy. */
#include <string.h>
#include "callback.h"
diff --git a/otherlibs/unix/gethost.c b/otherlibs/unix/gethost.c
index bae25f711..6e27928e4 100644
--- a/otherlibs/unix/gethost.c
+++ b/otherlibs/unix/gethost.c
@@ -34,7 +34,7 @@ extern int socket_domain_table[];
static value alloc_one_addr(char *a)
{
struct in_addr addr;
- bcopy(a, &addr, entry_h_length);
+ memmove (&addr, a, entry_h_length);
return alloc_inet_addr(addr.s_addr);
}
diff --git a/otherlibs/unix/putenv.c b/otherlibs/unix/putenv.c
index 33ab979a4..257a5c58d 100644
--- a/otherlibs/unix/putenv.c
+++ b/otherlibs/unix/putenv.c
@@ -28,9 +28,9 @@ value unix_putenv(value name, value val) /* ML */
mlsize_t vallen = string_length(val);
char * s = (char *) stat_alloc(namelen + 1 + vallen + 1);
- bcopy(String_val(name), s, namelen);
+ memmove (s, String_val(name), namelen);
s[namelen] = '=';
- bcopy(String_val(val), s + namelen + 1, vallen);
+ memmove (s + namelen + 1, String_val(val), vallen);
s[namelen + 1 + vallen] = 0;
if (putenv(s) == -1) uerror("putenv", name);
return Val_unit;
diff --git a/otherlibs/unix/read.c b/otherlibs/unix/read.c
index 9efb9ccf8..eab87d344 100644
--- a/otherlibs/unix/read.c
+++ b/otherlibs/unix/read.c
@@ -31,7 +31,7 @@ value unix_read(value fd, value buf, value ofs, value len) /* ML */
ret = read(Int_val(fd), iobuf, (int) numbytes);
leave_blocking_section();
if (ret == -1) uerror("read", Nothing);
- bcopy(iobuf, &Byte(buf, Long_val(ofs)), ret);
+ memmove (&Byte(buf, Long_val(ofs)), iobuf, ret);
End_roots();
return Val_int(ret);
}
diff --git a/otherlibs/unix/sendrecv.c b/otherlibs/unix/sendrecv.c
index 2f7e4a20d..f576fa4c7 100644
--- a/otherlibs/unix/sendrecv.c
+++ b/otherlibs/unix/sendrecv.c
@@ -40,7 +40,7 @@ value unix_recv(value sock, value buff, value ofs, value len, value flags) /* ML
convert_flag_list(flags, msg_flag_table));
leave_blocking_section();
if (ret == -1) uerror("recv", Nothing);
- bcopy(iobuf, &Byte(buff, Long_val(ofs)), ret);
+ memmove (&Byte(buff, Long_val(ofs)), iobuf, ret);
End_roots();
return Val_int(ret);
}
@@ -65,7 +65,7 @@ value unix_recvfrom(value sock, value buff, value ofs, value len, value flags) /
&addr.s_gen, &addr_len);
leave_blocking_section();
if (ret == -1) uerror("recvfrom", Nothing);
- bcopy(iobuf, &Byte(buff, Long_val(ofs)), ret);
+ memmove (&Byte(buff, Long_val(ofs)), iobuf, ret);
adr = alloc_sockaddr(&addr, addr_len);
res = alloc_small(2, 0);
Field(res, 0) = Val_int(ret);
@@ -82,7 +82,7 @@ value unix_send(value sock, value buff, value ofs, value len, value flags) /* ML
numbytes = Long_val(len);
if (numbytes > UNIX_BUFFER_SIZE) numbytes = UNIX_BUFFER_SIZE;
- bcopy(&Byte(buff, Long_val(ofs)), iobuf, numbytes);
+ memmove (iobuf, &Byte(buff, Long_val(ofs)), numbytes);
enter_blocking_section();
ret = send(Int_val(sock), iobuf, (int) numbytes,
convert_flag_list(flags, msg_flag_table));
@@ -102,7 +102,7 @@ value unix_sendto_native(value sock, value buff, value ofs, value len, value fla
get_sockaddr(dest, &addr, &addr_len);
numbytes = Long_val(len);
if (numbytes > UNIX_BUFFER_SIZE) numbytes = UNIX_BUFFER_SIZE;
- bcopy(&Byte(buff, Long_val(ofs)), iobuf, numbytes);
+ memmove (iobuf, &Byte(buff, Long_val(ofs)), numbytes);
enter_blocking_section();
ret = sendto(Int_val(sock), iobuf, (int) numbytes,
convert_flag_list(flags, msg_flag_table),
diff --git a/otherlibs/unix/socketaddr.c b/otherlibs/unix/socketaddr.c
index 1cc7a7af7..aa46f6da9 100644
--- a/otherlibs/unix/socketaddr.c
+++ b/otherlibs/unix/socketaddr.c
@@ -53,7 +53,7 @@ void get_sockaddr(value mladr,
if (len >= sizeof(adr->s_unix.sun_path)) {
unix_error(ENAMETOOLONG, "", path);
}
- bcopy(String_val(path), adr->s_unix.sun_path, (int) len + 1);
+ memmove (adr->s_unix.sun_path, String_val(path), len + 1);
*adr_len =
((char *)&(adr->s_unix.sun_path) - (char *)&(adr->s_unix))
+ len;
diff --git a/otherlibs/unix/write.c b/otherlibs/unix/write.c
index e154f80b6..b887f213c 100644
--- a/otherlibs/unix/write.c
+++ b/otherlibs/unix/write.c
@@ -38,7 +38,7 @@ value unix_write(value fd, value buf, value vofs, value vlen) /* ML */
written = 0;
while (len > 0) {
numbytes = len > UNIX_BUFFER_SIZE ? UNIX_BUFFER_SIZE : len;
- bcopy(&Byte(buf, ofs), iobuf, numbytes);
+ memmove (iobuf, &Byte(buf, ofs), numbytes);
enter_blocking_section();
ret = write(Int_val(fd), iobuf, numbytes);
leave_blocking_section();
diff --git a/otherlibs/win32unix/read.c b/otherlibs/win32unix/read.c
index f9f0e0f8a..cc3fdc441 100644
--- a/otherlibs/win32unix/read.c
+++ b/otherlibs/win32unix/read.c
@@ -35,7 +35,7 @@ value unix_read(value fd, value buf, value ofs, value len) /* ML */
_dosmaperr(GetLastError());
uerror("read", Nothing);
}
- bcopy(iobuf, &Byte(buf, Long_val(ofs)), numread);
+ memmove (&Byte(buf, Long_val(ofs)), iobuf, numread);
End_roots();
return Val_int(numread);
}
diff --git a/otherlibs/win32unix/sendrecv.c b/otherlibs/win32unix/sendrecv.c
index 46ae14fa0..6e56ccd17 100644
--- a/otherlibs/win32unix/sendrecv.c
+++ b/otherlibs/win32unix/sendrecv.c
@@ -36,7 +36,7 @@ value unix_recv(value sock, value buff, value ofs, value len, value flags)
convert_flag_list(flags, msg_flag_table));
leave_blocking_section();
if (ret == -1) unix_error(WSAGetLastError(), "recv", Nothing);
- bcopy(iobuf, &Byte(buff, Long_val(ofs)), ret);
+ memmove (&Byte(buff, Long_val(ofs)), iobuf, ret);
End_roots();
return Val_int(ret);
}
@@ -62,7 +62,7 @@ value unix_recvfrom(value sock, value buff, value ofs, value len, value flags) /
&addr.s_gen, &addr_len);
leave_blocking_section();
if (ret == -1) unix_error(WSAGetLastError(), "recvfrom", Nothing);
- bcopy(iobuf, &Byte(buff, Long_val(ofs)), ret);
+ memmove (&Byte(buff, Long_val(ofs)), iobuf, ret);
adr = alloc_sockaddr(&addr, addr_len);
res = alloc_small(2, 0);
Field(res, 0) = Val_int(ret);
@@ -79,7 +79,7 @@ value unix_send(value sock, value buff, value ofs, value len, value flags) /* ML
numbytes = Long_val(len);
if (numbytes > UNIX_BUFFER_SIZE) numbytes = UNIX_BUFFER_SIZE;
- bcopy(&Byte(buff, Long_val(ofs)), iobuf, numbytes);
+ memmove (iobuf, &Byte(buff, Long_val(ofs)), numbytes);
enter_blocking_section();
ret = send((SOCKET) Handle_val(sock), iobuf, (int) numbytes,
convert_flag_list(flags, msg_flag_table));
@@ -99,7 +99,7 @@ value unix_sendto_native(value sock, value buff, value ofs, value len, value fla
get_sockaddr(dest, &addr, &addr_len);
numbytes = Long_val(len);
if (numbytes > UNIX_BUFFER_SIZE) numbytes = UNIX_BUFFER_SIZE;
- bcopy(&Byte(buff, Long_val(ofs)), iobuf, numbytes);
+ memmove (iobuf, &Byte(buff, Long_val(ofs)), numbytes);
enter_blocking_section();
ret = sendto((SOCKET) Handle_val(sock),
iobuf, (int) numbytes,
diff --git a/otherlibs/win32unix/write.c b/otherlibs/win32unix/write.c
index ed09e2b74..4864ea7aa 100644
--- a/otherlibs/win32unix/write.c
+++ b/otherlibs/win32unix/write.c
@@ -33,7 +33,7 @@ value unix_write(value fd, value buf, value vofs, value vlen) /* ML */
written = 0;
while (len > 0) {
numbytes = len > UNIX_BUFFER_SIZE ? UNIX_BUFFER_SIZE : len;
- bcopy(&Byte(buf, ofs), iobuf, numbytes);
+ memmove (iobuf, &Byte(buf, ofs), numbytes);
enter_blocking_section();
ret = WriteFile(h, iobuf, numbytes, &numwritten, NULL);
leave_blocking_section();
diff --git a/utils/config.mlp b/utils/config.mlp
index 7ee676d83..eb552c481 100644
--- a/utils/config.mlp
+++ b/utils/config.mlp
@@ -12,7 +12,7 @@
(* $Id$ *)
-let version = "3.00+19 (2000-11-06)"
+let version = "3.00+19 (2000-11-20)"
let standard_library =
try