Skip to content

Commit

Permalink
PR#6075: avoid using unsafe C library functions (strcpy, strcat, spri…
Browse files Browse the repository at this point in the history
…ntf).

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
  • Loading branch information
xavierleroy committed Apr 15, 2014
1 parent 2fc7ac7 commit 774e30e
Show file tree
Hide file tree
Showing 51 changed files with 516 additions and 606 deletions.
5 changes: 5 additions & 0 deletions Changes
Expand Up @@ -55,6 +55,11 @@ Runtime system:
increments proportional to heap size
- PR#4765: Structural equality should treat exception specifically
- PR#5009: Extending exception tag blocks
- 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.

Standard library:
- PR#4986: add List.sort_uniq and Set.of_list
Expand Down
1 change: 1 addition & 0 deletions byterun/alloc.h
Expand Up @@ -37,6 +37,7 @@ CAMLextern value caml_copy_int64 (int64); /* defined in [ints.c] */
CAMLextern value caml_copy_nativeint (intnat); /* defined in [ints.c] */
CAMLextern value caml_alloc_array (value (*funct) (char const *),
char const ** array);
CAMLextern value caml_alloc_sprintf(const char * format, ...);

typedef void (*final_fun)(value);
CAMLextern value caml_alloc_final (mlsize_t, /*size in words*/
Expand Down
5 changes: 3 additions & 2 deletions byterun/callback.c
Expand Up @@ -216,6 +216,7 @@ CAMLprim value caml_register_named_value(value vname, value val)
{
struct named_value * nv;
char * name = String_val(vname);
size_t namelen = strlen(name);
unsigned int h = hash_value_name(name);

for (nv = named_value_table[h]; nv != NULL; nv = nv->next) {
Expand All @@ -225,8 +226,8 @@ CAMLprim value caml_register_named_value(value vname, value val)
}
}
nv = (struct named_value *)
caml_stat_alloc(sizeof(struct named_value) + strlen(name));
strcpy(nv->name, name);
caml_stat_alloc(sizeof(struct named_value) + namelen);
memcpy(nv->name, name, namelen + 1);
nv->val = val;
nv->next = named_value_table[h];
named_value_table[h] = nv;
Expand Down
56 changes: 29 additions & 27 deletions byterun/config.h
Expand Up @@ -25,30 +25,9 @@
#include "compatibility.h"
#endif

/* Types for signed chars, 32-bit integers, 64-bit integers,
/* Types for 32-bit integers, 64-bit integers,
native integers (as wide as a pointer type) */

typedef signed char schar;

#if SIZEOF_PTR == SIZEOF_LONG
/* Standard models: ILP32 or I32LP64 */
typedef long intnat;
typedef unsigned long uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT "l"
#elif SIZEOF_PTR == SIZEOF_INT
/* Hypothetical IP32L64 model */
typedef int intnat;
typedef unsigned int uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT ""
#elif SIZEOF_PTR == 8 && defined(ARCH_INT64_TYPE)
/* Win64 model: IL32LLP64 */
typedef ARCH_INT64_TYPE intnat;
typedef ARCH_UINT64_TYPE uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT ARCH_INT64_PRINTF_FORMAT
#else
#error "No integer type available to represent pointers"
#endif

#if SIZEOF_INT == 4
typedef int int32;
typedef unsigned int uint32;
Expand All @@ -68,12 +47,35 @@ typedef unsigned short uint32;
#if defined(ARCH_INT64_TYPE)
typedef ARCH_INT64_TYPE int64;
typedef ARCH_UINT64_TYPE uint64;
#elif SIZEOF_LONG == 8
typedef long int64;
typedef unsigned long uint64;
#define ARCH_INT64_PRINTF_FORMAT "l"
#elif SIZEOF_LONGLONG == 8
typedef long long int64;
typedef unsigned long long uint64;
#define ARCH_INT64_PRINTF_FORMAT "ll"
#else
# ifdef ARCH_BIG_ENDIAN
typedef struct { uint32 h, l; } uint64, int64;
# else
typedef struct { uint32 l, h; } uint64, int64;
# endif
#error "No 64-bit integer type available"
#endif

#if SIZEOF_PTR == SIZEOF_LONG
/* Standard models: ILP32 or I32LP64 */
typedef long intnat;
typedef unsigned long uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT "l"
#elif SIZEOF_PTR == SIZEOF_INT
/* Hypothetical IP32L64 model */
typedef int intnat;
typedef unsigned int uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT ""
#elif SIZEOF_PTR == 8
/* Win64 model: IL32LLP64 */
typedef int64 intnat;
typedef uint64 uintnat;
#define ARCH_INTNAT_PRINTF_FORMAT ARCH_INT64_PRINTF_FORMAT
#else
#error "No integer type available to represent pointers"
#endif

/* Endianness of floats */
Expand Down
4 changes: 1 addition & 3 deletions byterun/dynlink.c
Expand Up @@ -79,9 +79,7 @@ static char * parse_ld_conf(void)
stdlib = getenv("OCAMLLIB");
if (stdlib == NULL) stdlib = getenv("CAMLLIB");
if (stdlib == NULL) stdlib = OCAML_STDLIB_DIR;
ldconfname = caml_stat_alloc(strlen(stdlib) + 2 + sizeof(LD_CONF_NAME));
strcpy(ldconfname, stdlib);
strcat(ldconfname, "/" LD_CONF_NAME);
ldconfname = caml_strconcat(3, stdlib, "/", LD_CONF_NAME);
if (stat(ldconfname, &st) == -1) {
caml_stat_free(ldconfname);
return NULL;
Expand Down
48 changes: 5 additions & 43 deletions byterun/floats.c
Expand Up @@ -71,68 +71,29 @@ CAMLexport value caml_copy_double(double d)

CAMLprim value caml_format_float(value fmt, value arg)
{
#define MAX_DIGITS 350
/* Max number of decimal digits in a "natural" (not artificially padded)
representation of a float. Can be quite big for %f format.
Max exponent for IEEE format is 308 decimal digits.
Rounded up for good measure. */
char format_buffer[MAX_DIGITS + 20];
int prec, i;
char * p;
char * dest;
value res;
double d = Double_val(arg);

#ifdef HAS_BROKEN_PRINTF
if (isfinite(d)) {
#endif
prec = MAX_DIGITS;
for (p = String_val(fmt); *p != 0; p++) {
if (*p >= '0' && *p <= '9') {
i = atoi(p) + MAX_DIGITS;
if (i > prec) prec = i;
break;
}
}
for( ; *p != 0; p++) {
if (*p == '.') {
i = atoi(p+1) + MAX_DIGITS;
if (i > prec) prec = i;
break;
}
}
if (prec < sizeof(format_buffer)) {
dest = format_buffer;
} else {
dest = caml_stat_alloc(prec);
}
sprintf(dest, String_val(fmt), d);
res = caml_copy_string(dest);
if (dest != format_buffer) {
caml_stat_free(dest);
}
res = caml_alloc_sprintf(String_val(fmt), d);
#ifdef HAS_BROKEN_PRINTF
} else {
if (isnan(d))
{
if (isnan(d)) {
res = caml_copy_string("nan");
}
else
{
} else {
if (d > 0)
{
res = caml_copy_string("inf");
}
else
{
res = caml_copy_string("-inf");
}
}
}
#endif
return res;
}

#if 0
/*CAMLprim*/ value caml_float_of_substring(value vs, value idx, value l)
{
char parse_buffer[64];
Expand Down Expand Up @@ -163,6 +124,7 @@ CAMLprim value caml_format_float(value fmt, value arg)
if (buf != parse_buffer) caml_stat_free(buf);
caml_failwith("float_of_string");
}
#endif

CAMLprim value caml_float_of_string(value vs)
{
Expand Down
10 changes: 1 addition & 9 deletions byterun/hash.c
Expand Up @@ -21,12 +21,6 @@
#include "memory.h"
#include "hash.h"

#ifdef ARCH_INT64_TYPE
#include "int64_native.h"
#else
#include "int64_emul.h"
#endif

/* The new implementation, based on MurmurHash 3,
http://code.google.com/p/smhasher/ */

Expand Down Expand Up @@ -77,9 +71,7 @@ CAMLexport uint32 caml_hash_mix_intnat(uint32 h, intnat d)

CAMLexport uint32 caml_hash_mix_int64(uint32 h, int64 d)
{
uint32 hi, lo;

I64_split(d, hi, lo);
uint32 hi = (uint32) (d >> 32), lo = (uint32) d;
MIX(h, lo);
MIX(h, hi);
return h;
Expand Down
17 changes: 9 additions & 8 deletions byterun/instrtrace.c
Expand Up @@ -84,7 +84,7 @@ char * caml_instr_string (code_t pc)
char *nam;

nam = (instr < 0 || instr > STOP)
? (sprintf (nambuf, "???%d", instr), nambuf)
? (snprintf (nambuf, sizeof(nambuf), "???%d", instr), nambuf)
: names_of_instructions[instr];
pc++;
switch (instr) {
Expand Down Expand Up @@ -125,7 +125,7 @@ char * caml_instr_string (code_t pc)
case OFFSETREF:
case OFFSETCLOSURE:
case PUSHOFFSETCLOSURE:
sprintf(buf, "%s %d", nam, pc[0]);
snprintf(buf, sizeof(buf), "%s %d", nam, pc[0]);
break;
/* Instructions with two operands */
case APPTERM:
Expand All @@ -142,16 +142,16 @@ char * caml_instr_string (code_t pc)
case BGEINT:
case BULTINT:
case BUGEINT:
sprintf(buf, "%s %d, %d", nam, pc[0], pc[1]);
snprintf(buf, sizeof(buf), "%s %d, %d", nam, pc[0], pc[1]);
break;
case SWITCH:
sprintf(buf, "SWITCH sz%#lx=%ld::ntag%ld nint%ld",
snprintf(buf, sizeof(buf), "SWITCH sz%#lx=%ld::ntag%ld nint%ld",
(long) pc[0], (long) pc[0], (unsigned long) pc[0] >> 16,
(unsigned long) pc[0] & 0xffff);
break;
/* Instructions with a C primitive as operand */
case C_CALLN:
sprintf(buf, "%s %d,", nam, pc[0]);
snprintf(buf, sizeof(buf), "%s %d,", nam, pc[0]);
pc++;
/* fallthrough */
case C_CALL1:
Expand All @@ -160,12 +160,13 @@ char * caml_instr_string (code_t pc)
case C_CALL4:
case C_CALL5:
if (pc[0] < 0 || pc[0] >= caml_prim_name_table.size)
sprintf(buf, "%s unknown primitive %d", nam, pc[0]);
snprintf(buf, sizeof(buf), "%s unknown primitive %d", nam, pc[0]);
else
sprintf(buf, "%s %s", nam, (char *) caml_prim_name_table.contents[pc[0]]);
snprintf(buf, sizeof(buf), "%s %s",
nam, (char *) caml_prim_name_table.contents[pc[0]]);
break;
default:
sprintf(buf, "%s", nam);
snprintf(buf, sizeof(buf), "%s", nam);
break;
};
return buf;
Expand Down
3 changes: 2 additions & 1 deletion byterun/intern.c
Expand Up @@ -738,7 +738,8 @@ static char * intern_resolve_code_pointer(unsigned char digest[16],
static void intern_bad_code_pointer(unsigned char digest[16])
{
char msg[256];
sprintf(msg, "input_value: unknown code module "
snprintf(msg, sizeof(msg),
"input_value: unknown code module "
"%02X%02X%02X%02X%02X%02X%02X%02X"
"%02X%02X%02X%02X%02X%02X%02X%02X",
digest[0], digest[1], digest[2], digest[3],
Expand Down
16 changes: 0 additions & 16 deletions byterun/interp.c
Expand Up @@ -181,14 +181,6 @@ sp is a local copy of the global variable caml_extern_sp. */
#endif
#endif

/* Division and modulus madness */

#ifdef NONSTANDARD_DIV_MOD
extern intnat caml_safe_div(intnat p, intnat q);
extern intnat caml_safe_mod(intnat p, intnat q);
#endif


#ifdef DEBUG
static intnat caml_bcodcount;
#endif
Expand Down Expand Up @@ -962,21 +954,13 @@ value caml_interprete(code_t prog, asize_t prog_size)
Instruct(DIVINT): {
intnat divisor = Long_val(*sp++);
if (divisor == 0) { Setup_for_c_call; caml_raise_zero_divide(); }
#ifdef NONSTANDARD_DIV_MOD
accu = Val_long(caml_safe_div(Long_val(accu), divisor));
#else
accu = Val_long(Long_val(accu) / divisor);
#endif
Next;
}
Instruct(MODINT): {
intnat divisor = Long_val(*sp++);
if (divisor == 0) { Setup_for_c_call; caml_raise_zero_divide(); }
#ifdef NONSTANDARD_DIV_MOD
accu = Val_long(caml_safe_mod(Long_val(accu), divisor));
#else
accu = Val_long(Long_val(accu) % divisor);
#endif
Next;
}
Instruct(ANDINT):
Expand Down

0 comments on commit 774e30e

Please sign in to comment.