summaryrefslogtreecommitdiffstats
path: root/byterun/str.c
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2014-04-15 17:09:13 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2014-04-15 17:09:13 +0000
commit774e30e138dc22a5acd6cfac03ae25194ae8cd6e (patch)
tree2acda83264153258c7f978efeae08d260598c023 /byterun/str.c
parent2fc7ac7e8b95a143b6b38eab28622389cc19001b (diff)
PR#6075: avoid using unsafe C library functions (strcpy, strcat, sprintf).
An ISO C99-compliant C compiler and standard library is now assumed. (Plus special exceptions for MSVC.) In particular, emulation code for 64-bit integer arithmetic was removed, the C compiler must support a 64-bit integer type. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14607 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'byterun/str.c')
-rw-r--r--byterun/str.c124
1 files changed, 93 insertions, 31 deletions
diff --git a/byterun/str.c b/byterun/str.c
index 9e157a816..e2e0f4d26 100644
--- a/byterun/str.c
+++ b/byterun/str.c
@@ -15,6 +15,8 @@
#include <string.h>
#include <ctype.h>
+#include <stdio.h>
+#include <stdarg.h>
#include "alloc.h"
#include "fail.h"
#include "mlvalues.h"
@@ -97,16 +99,9 @@ CAMLprim value caml_string_get32(value str, value index)
return caml_copy_int32(res);
}
-#ifdef ARCH_INT64_TYPE
-#include "int64_native.h"
-#else
-#include "int64_emul.h"
-#endif
-
CAMLprim value caml_string_get64(value str, value index)
{
- uint32 reshi;
- uint32 reslo;
+ uint64 res;
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
intnat idx = Long_val(index);
if (idx < 0 || idx + 7 >= caml_string_length(str)) caml_array_bound_error();
@@ -119,13 +114,17 @@ CAMLprim value caml_string_get64(value str, value index)
b7 = Byte_u(str, idx + 6);
b8 = Byte_u(str, idx + 7);
#ifdef ARCH_BIG_ENDIAN
- reshi = b1 << 24 | b2 << 16 | b3 << 8 | b4;
- reslo = b5 << 24 | b6 << 16 | b7 << 8 | b8;
+ res = (uint64) b1 << 56 | (uint64) b2 << 48
+ | (uint64) b3 << 40 | (uint64) b4 << 32
+ | (uint64) b5 << 24 | (uint64) b6 << 16
+ | (uint64) b7 << 8 | (uint64) b8;
#else
- reshi = b8 << 24 | b7 << 16 | b6 << 8 | b5;
- reslo = b4 << 24 | b3 << 16 | b2 << 8 | b1;
+ res = (uint64) b8 << 56 | (uint64) b7 << 48
+ | (uint64) b6 << 40 | (uint64) b5 << 32
+ | (uint64) b4 << 24 | (uint64) b3 << 16
+ | (uint64) b2 << 8 | (uint64) b1;
#endif
- return caml_copy_int64(I64_literal(reshi,reslo));
+ return caml_copy_int64(res);
}
CAMLprim value caml_string_set16(value str, value index, value newval)
@@ -175,30 +174,28 @@ CAMLprim value caml_string_set32(value str, value index, value newval)
CAMLprim value caml_string_set64(value str, value index, value newval)
{
unsigned char b1, b2, b3, b4, b5, b6, b7, b8;
- uint32 lo,hi;
int64 val;
intnat idx = Long_val(index);
if (idx < 0 || idx + 7 >= caml_string_length(str)) caml_array_bound_error();
val = Int64_val(newval);
- I64_split(val,hi,lo);
#ifdef ARCH_BIG_ENDIAN
- b1 = 0xFF & hi >> 24;
- b2 = 0xFF & hi >> 16;
- b3 = 0xFF & hi >> 8;
- b4 = 0xFF & hi;
- b5 = 0xFF & lo >> 24;
- b6 = 0xFF & lo >> 16;
- b7 = 0xFF & lo >> 8;
- b8 = 0xFF & lo;
+ b1 = 0xFF & val >> 56;
+ b2 = 0xFF & val >> 48;
+ b3 = 0xFF & val >> 40;
+ b4 = 0xFF & val >> 32;
+ b5 = 0xFF & val >> 24;
+ b6 = 0xFF & val >> 16;
+ b7 = 0xFF & val >> 8;
+ b8 = 0xFF & val;
#else
- b8 = 0xFF & hi >> 24;
- b7 = 0xFF & hi >> 16;
- b6 = 0xFF & hi >> 8;
- b5 = 0xFF & hi;
- b4 = 0xFF & lo >> 24;
- b3 = 0xFF & lo >> 16;
- b2 = 0xFF & lo >> 8;
- b1 = 0xFF & lo;
+ b8 = 0xFF & val >> 56;
+ b7 = 0xFF & val >> 48;
+ b6 = 0xFF & val >> 40;
+ b5 = 0xFF & val >> 32;
+ b4 = 0xFF & val >> 24;
+ b3 = 0xFF & val >> 16;
+ b2 = 0xFF & val >> 8;
+ b1 = 0xFF & val;
#endif
Byte_u(str, idx) = b1;
Byte_u(str, idx + 1) = b2;
@@ -299,3 +296,68 @@ 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)));
}
+
+CAMLexport value caml_alloc_sprintf(const char * format, ...)
+{
+ va_list args;
+ char buf[64];
+ int n;
+ value res;
+
+#ifndef _WIN32
+ /* C99-compliant implementation */
+ va_start(args, format);
+ /* "vsnprintf(dest, sz, format, args)" writes at most "sz" characters
+ into "dest", including the terminating '\0'.
+ It returns the number of characters of the formatted string,
+ excluding the terminating '\0'. */
+ n = vsnprintf(buf, sizeof(buf), format, args);
+ va_end(args);
+ /* Allocate a Caml string with length "n" as computed by vsnprintf. */
+ res = caml_alloc_string(n);
+ if (n < sizeof(buf)) {
+ /* All output characters were written to buf, including the
+ terminating '\0'. Just copy them to the result. */
+ memcpy(String_val(res), buf, n);
+ } else {
+ /* Re-do the formatting, outputting directly in the Caml string.
+ Note that caml_alloc_string left room for a '\0' at position n,
+ so the size passed to vsnprintf is n+1. */
+ va_start(args, format);
+ vsnprintf(String_val(res), n + 1, format, args);
+ va_end(args);
+ }
+ return res;
+#else
+ /* Implementation specific to the Microsoft CRT library */
+ va_start(args, format);
+ /* "_vsnprintf(dest, sz, format, args)" writes at most "sz" characters
+ into "dest". Let "len" be the number of characters of the formatted
+ string.
+ If "len" < "sz", a null terminator was appended, and "len" is returned.
+ If "len" == "sz", no null termination, and "len" is returned.
+ If "len" > "sz", a negative value is returned. */
+ n = _vsnprintf(buf, sizeof(buf), format, args);
+ va_end(args);
+ if (n >= 0 && n <= sizeof(buf)) {
+ /* All output characters were written to buf.
+ "n" is the actual length of the output.
+ Copy the characters to a Caml string of length n. */
+ res = caml_alloc_string(n);
+ memcpy(String_val(res), buf, n);
+ } else {
+ /* Determine actual length of output, excluding final '\0' */
+ va_start(args, format);
+ n = _vscprintf(format, args);
+ va_end(args);
+ res = caml_alloc_string(n);
+ /* Re-do the formatting, outputting directly in the Caml string.
+ Note that caml_alloc_string left room for a '\0' at position n,
+ so the size passed to _vsnprintf is n+1. */
+ va_start(args, format);
+ _vsnprintf(String_val(res), n + 1, format, args);
+ va_end(args);
+ }
+ return res;
+#endif
+}