diff options
-rw-r--r-- | Makefile | 2 | ||||
-rw-r--r-- | byterun/alloc.c | 2 | ||||
-rw-r--r-- | byterun/compact.c | 3 | ||||
-rw-r--r-- | byterun/config.h | 10 | ||||
-rw-r--r-- | byterun/debugger.c | 2 | ||||
-rw-r--r-- | byterun/extern.c | 12 | ||||
-rw-r--r-- | byterun/instruct.h | 2 | ||||
-rw-r--r-- | byterun/intern.c | 10 | ||||
-rw-r--r-- | byterun/ints.c | 4 | ||||
-rw-r--r-- | byterun/io.c | 22 | ||||
-rw-r--r-- | byterun/printexc.c | 4 | ||||
-rw-r--r-- | byterun/stacks.c | 6 | ||||
-rw-r--r-- | byterun/str.c | 2 | ||||
-rw-r--r-- | byterun/sys.c | 6 |
14 files changed, 43 insertions, 44 deletions
@@ -16,7 +16,7 @@ include config/Makefile -CAMLC=boot/ocamlrun boot/ocamlc -I boot +CAMLC=boot/ocamlrun boot/ocamlc -I boot -g CAMLOPT=boot/ocamlrun ./ocamlopt -I stdlib COMPFLAGS=$(INCLUDES) LINKFLAGS= diff --git a/byterun/alloc.c b/byterun/alloc.c index eb75fef16..603c519ef 100644 --- a/byterun/alloc.c +++ b/byterun/alloc.c @@ -95,7 +95,7 @@ value copy_string(char *s) len = strlen(s); res = alloc_string(len); - bcopy(s, String_val(res), len); + memmove(String_val(res), s, len); return res; } diff --git a/byterun/compact.c b/byterun/compact.c index 68054d4af..66e88415e 100644 --- a/byterun/compact.c +++ b/byterun/compact.c @@ -329,8 +329,7 @@ void compact_heap (void) if (Color_hd (q) == Caml_white){ size_t sz = Bhsize_hd (q); char *newadr = compact_allocate (sz); Assert (newadr <= (char *)p); - /* bcopy (source, destination, length) */ - bcopy (p, newadr, sz); + memmove (newadr, p, sz); p += Wsize_bsize (sz); }else{ Assert (Color_hd (q) == Caml_blue); diff --git a/byterun/config.h b/byterun/config.h index 1d2d4e9b6..c70601b44 100644 --- a/byterun/config.h +++ b/byterun/config.h @@ -56,14 +56,14 @@ typedef uint64 int64; /* Library dependencies */ #ifdef HAS_MEMMOVE -#undef bcopy -#define bcopy(src,dst,len) memmove((dst), (src), (len)) +/* nothing to do */ #else #ifdef HAS_BCOPY -/* Nothing to do */ +#undef memmove +#define memmove(dst,src,len) bcopy((src), (dst), (len)) #else -#undef bcopy -#define bcopy(src,dst,len) memmov((dst), (src), (len)) +#undef memmove +#define memmove(dst,src,len) memmov((dst), (src), (len)) #define USING_MEMMOV #endif #endif diff --git a/byterun/debugger.c b/byterun/debugger.c index 8a41312a7..afaba483f 100644 --- a/byterun/debugger.c +++ b/byterun/debugger.c @@ -121,7 +121,7 @@ void debugger_init(void) host = gethostbyname(address); if (host == NULL) fatal_error_arg("Unknown debugging host %s\n", address); - bcopy(host->h_addr, &sock_addr.s_inet.sin_addr, host->h_length); + memmove(&sock_addr.s_inet.sin_addr, host->h_addr, host->h_length); } sock_addr.s_inet.sin_port = htons(atoi(port)); sock_addr_len = sizeof(sock_addr.s_inet); diff --git a/byterun/extern.c b/byterun/extern.c index abcae9649..eadea2040 100644 --- a/byterun/extern.c +++ b/byterun/extern.c @@ -136,7 +136,7 @@ static void resize_extern_block(int required) static void writeblock(char *data, long int len) { if (extern_ptr + len > extern_limit) resize_extern_block(len); - bcopy(data, extern_ptr, len); + memmove(extern_ptr, data, len); extern_ptr += len; } @@ -433,7 +433,7 @@ value output_value_to_string(value v, value flags) /* ML */ alloc_extern_block(); len = extern_value(v, flags); res = alloc_string(len); - bcopy(extern_block, String_val(res), len); + memmove(String_val(res), extern_block, len); stat_free(extern_block); return res; } @@ -504,7 +504,7 @@ void serialize_float_8(double f) void serialize_block_1(void * data, long len) { if (extern_ptr + len > extern_limit) resize_extern_block(len); - bcopy(data, extern_ptr, len); + memmove(extern_ptr, data, len); extern_ptr += len; } @@ -518,7 +518,7 @@ void serialize_block_2(void * data, long len) Reverse_16(q, p); extern_ptr = q; #else - bcopy(data, extern_ptr, len * 2); + memmove(extern_ptr, data, len * 2); extern_ptr += len * 2; #endif } @@ -533,7 +533,7 @@ void serialize_block_4(void * data, long len) Reverse_32(q, p); extern_ptr = q; #else - bcopy(data, extern_ptr, len * 4); + memmove(extern_ptr, data, len * 4); extern_ptr += len * 4; #endif } @@ -548,7 +548,7 @@ void serialize_block_8(void * data, long len) Reverse_64(q, p); extern_ptr = q; #else - bcopy(data, extern_ptr, len * 8); + memmove(extern_ptr, data, len * 8); extern_ptr += len * 8; #endif } diff --git a/byterun/instruct.h b/byterun/instruct.h index 80d9ed1ea..c9a86f7b9 100644 --- a/byterun/instruct.h +++ b/byterun/instruct.h @@ -49,5 +49,5 @@ enum instructions { BEQ, BNEQ, BLTINT, BLEINT, BGTINT, BGEINT, ULTINT, UGEINT, BULTINT, BUGEINT, STOP, - EVENT, BREAK, + EVENT, BREAK }; diff --git a/byterun/intern.c b/byterun/intern.c index bec0ed8be..2e7fc09e3 100644 --- a/byterun/intern.c +++ b/byterun/intern.c @@ -93,7 +93,7 @@ static long read64s(void) #endif #define readblock(dest,len) \ - (bcopy(intern_src, dest, len), intern_src += len) + (memmove(dest, intern_src, len), intern_src += len) static void intern_cleanup(void) { @@ -550,7 +550,7 @@ double deserialize_float_8(void) void deserialize_block_1(void * data, long len) { - bcopy(intern_src, data, len); + memmove(data, intern_src, len); intern_src += len; } @@ -562,7 +562,7 @@ void deserialize_block_2(void * data, long len) Reverse_16(q, p); intern_src = p; #else - bcopy(intern_src, data, len * 2); + memmove(data, intern_src, len * 2); intern_src += len * 2; #endif } @@ -575,7 +575,7 @@ void deserialize_block_4(void * data, long len) Reverse_32(q, p); intern_src = p; #else - bcopy(intern_src, data, len * 4); + memmove(data, intern_src, len * 4); intern_src += len * 4; #endif } @@ -588,7 +588,7 @@ void deserialize_block_8(void * data, long len) Reverse_64(q, p); intern_src = p; #else - bcopy(intern_src, data, len * 8); + memmove(data, intern_src, len * 8); intern_src += len * 8; #endif } diff --git a/byterun/ints.c b/byterun/ints.c index c86d13398..2893b6988 100644 --- a/byterun/ints.c +++ b/byterun/ints.c @@ -97,10 +97,10 @@ static char * parse_format(value fmt, len_suffix = strlen(suffix); if (len + len_suffix + 1 >= FORMAT_BUFFER_SIZE) invalid_argument("format_int: format too long"); - bcopy(String_val(fmt), format_string, len); + memmove(format_string, String_val(fmt), len); p = format_string + len - 1; lastletter = *p; - bcopy(suffix, p, len_suffix); p += len_suffix; + memmove(p, suffix, len_suffix); p += len_suffix; *p++ = lastletter; *p = 0; /* Determine space needed for result and allocate it dynamically if needed */ diff --git a/byterun/io.c b/byterun/io.c index 6104e8f41..eb003463d 100644 --- a/byterun/io.c +++ b/byterun/io.c @@ -150,7 +150,7 @@ int flush_partial(struct channel *channel) written = do_write(channel->fd, channel->buff, towrite); channel->offset += written; if (written < towrite) - bcopy(channel->buff + written, channel->buff, towrite - written); + memmove(channel->buff, channel->buff + written, towrite - written); channel->curr -= written; } return (channel->curr == channel->buff); @@ -183,17 +183,17 @@ int putblock(struct channel *channel, char *p, long int len) free = channel->end - channel->curr; if (n <= free) { /* Write request small enough to fit in buffer: transfer to buffer. */ - bcopy(p, channel->curr, n); + memmove(channel->curr, p, n); channel->curr += n; return n; } else { /* Write request overflows buffer: transfer whatever fits to buffer and write the buffer */ - bcopy(p, channel->curr, free); + memmove(channel->curr, p, free); towrite = channel->end - channel->buff; written = do_write(channel->fd, channel->buff, towrite); if (written < towrite) - bcopy(channel->buff + written, channel->buff, towrite - written); + memmove(channel->buff, channel->buff + written, towrite - written); channel->offset += written; channel->curr = channel->end - written; channel->max = channel->end - written; @@ -278,11 +278,11 @@ int getblock(struct channel *channel, char *p, long int len) n = len >= INT_MAX ? INT_MAX : (int) len; avail = channel->max - channel->curr; if (n <= avail) { - bcopy(channel->curr, p, n); + memmove(p, channel->curr, n); channel->curr += n; return n; } else if (avail > 0) { - bcopy(channel->curr, p, avail); + memmove(p, channel->curr, avail); channel->curr += avail; return avail; } else { @@ -290,7 +290,7 @@ int getblock(struct channel *channel, char *p, long int len) channel->offset += nread; channel->max = channel->buff + nread; if (n > nread) n = nread; - bcopy(channel->buff, p, n); + memmove(p, channel->buff, n); channel->curr = channel->buff + n; return n; } @@ -337,7 +337,7 @@ long input_scan_line(struct channel *channel) if (channel->curr > channel->buff) { /* Try to make some room in the buffer by shifting the unread portion at the beginning */ - bcopy(channel->curr, channel->buff, channel->max - channel->curr); + memmove(channel->buff, channel->curr, channel->max - channel->curr); n = channel->curr - channel->buff; channel->curr -= n; channel->max -= n; @@ -555,10 +555,10 @@ value caml_input(value vchannel,value buff,value vstart,value vlength) /* ML */ n = len >= INT_MAX ? INT_MAX : (int) len; avail = channel->max - channel->curr; if (n <= avail) { - bcopy(channel->curr, &Byte(buff, start), n); + memmove(&Byte(buff, start), channel->curr, n); channel->curr += n; } else if (avail > 0) { - bcopy(channel->curr, &Byte(buff, start), avail); + memmove(&Byte(buff, start), channel->curr, avail); channel->curr += avail; n = avail; } else { @@ -566,7 +566,7 @@ value caml_input(value vchannel,value buff,value vstart,value vlength) /* ML */ channel->offset += nread; channel->max = channel->buff + nread; if (n > nread) n = nread; - bcopy(channel->buff, &Byte(buff, start), n); + memmove(&Byte(buff, start), channel->buff, n); channel->curr = channel->buff + n; } Unlock(channel); diff --git a/byterun/printexc.c b/byterun/printexc.c index 3bff25b02..c6e247882 100644 --- a/byterun/printexc.c +++ b/byterun/printexc.c @@ -39,7 +39,7 @@ static void add_string(struct stringbuf *buf, char *s) { int len = strlen(s); if (buf->ptr + len > buf->end) len = buf->end - buf->ptr; - if (len > 0) bcopy(s, buf->ptr, len); + if (len > 0) memmove(buf->ptr, s, len); buf->ptr += len; } @@ -86,7 +86,7 @@ char * format_caml_exception(value exn) i = buf.ptr - buf.data + 1; res = malloc(i); if (res == NULL) return NULL; - bcopy(buf.data, res, i); + memmove(res, buf.data, i); return res; } diff --git a/byterun/stacks.c b/byterun/stacks.c index ff26855c1..9ca38ec6b 100644 --- a/byterun/stacks.c +++ b/byterun/stacks.c @@ -63,9 +63,9 @@ void realloc_stack(void) ((char *) new_high - ((char *) stack_high - (char *) (ptr))) new_sp = (value *) shift(extern_sp); - bcopy((char *) extern_sp, - (char *) new_sp, - (stack_high - extern_sp) * sizeof(value)); + memmove((char *) new_sp, + (char *) extern_sp, + (stack_high - extern_sp) * sizeof(value)); stat_free(stack_low); trapsp = (value *) shift(trapsp); trap_barrier = (value *) shift(trap_barrier); diff --git a/byterun/str.c b/byterun/str.c index 102912a95..51ff4aa9f 100644 --- a/byterun/str.c +++ b/byterun/str.c @@ -80,7 +80,7 @@ value string_notequal(value s1, value s2) /* ML */ value blit_string(value s1, value ofs1, value s2, value ofs2, value n) /* ML */ { - bcopy(&Byte(s1, Long_val(ofs1)), &Byte(s2, Long_val(ofs2)), Int_val(n)); + memmove(&Byte(s2, Long_val(ofs2)), &Byte(s1, Long_val(ofs1)), Int_val(n)); return Val_unit; } diff --git a/byterun/sys.c b/byterun/sys.c index ebcdc6077..03f5acb65 100644 --- a/byterun/sys.c +++ b/byterun/sys.c @@ -102,9 +102,9 @@ void sys_error(value arg) int err_len = strlen(err); int arg_len = string_length(arg); str = alloc_string(arg_len + 2 + err_len); - bcopy(String_val(arg), &Byte(str, 0), arg_len); - bcopy(": ", &Byte(str, arg_len), 2); - bcopy(err, &Byte(str, arg_len + 2), err_len); + memmove(&Byte(str, 0), String_val(arg), arg_len); + memmove(&Byte(str, arg_len), ": ", 2); + memmove(&Byte(str, arg_len + 2), err, err_len); } raise_sys_error(str); } |