Cleaning up the C code (#1812)

Running Clang 6.0 and GCC 8 with full warnings on suggests a few simple improvements and clean-ups to the C code of OCaml.  This commit implements them.

* Remove old-style, unprototyped function declarations

It's `int f(void)`, not `int f()`.  [-Wstrict-prototypes]

* Be more explicit about conversions involving `float` and `double`

byterun/bigarray.c, byterun/ints.c:
  add explicit casts to clarify the intent
  renamed float field of conversion union from `d` to `f`.

byterun/compact.c, byterun/gc_ctrl.c:
  some local variables were of type `float` while all FP computations
  here are done in double precision;
  turned these variables into `double`.

[-Wdouble-promotion -Wfloat-conversion]

*Add explicit initialization of struct field `compare_ext`

[-Wmissing-field-initializers]

* Declare more functions "noreturn"

[-Wmissing-noreturn]

* Make CAMLassert compliant with ISO C

In `e1 ? e2 : e3`, expressions `e2` and `e3` must have the same type.
`e2` of type `void` and `e3` of type `int`, as in the original code,
is a GNU extension.

* Remove or conditionalize unused macros

Some macros were defined and never used.
Some other macros were always defined but conditionally used.

[-Wunused-macros]

* Replace some uses of `int` by more appropriate types like `intnat`

On a 64-bit platform, `int` is only 32 bits and may not represent correctly
the length of a string or the size of an OCaml heap block.

This commit replaces a number of uses of `int` by other types that
are 64-bit wide on 64-bit architectures, such as `intnat` or `uintnat`
or `size_t` or `mlsize_t`.

Sometimes an `intnat` was used as an `int` and is intended as a Boolean
(0 or 1); then it was replaced by an `int`.

There are many remaining cases where we assign a 64-bit quantity to a
32-bit `int` variable.  Either I believe these cases are safe
(e.g. the 64-bit quantity is the difference between two pointers
within an I/O buffer, something that always fits in 32 bits), or
the code change was not obvious and too risky.

[-Wshorten-64-to-32]

* Put `inline` before return type

`static inline void f(void)` is cleaner than `static void inline f(void)`.

[-Wold-style-declaration]

* Unused assignment to unused parameter

Looks very useless.  [-Wunused-but-set-parameter]
master
Xavier Leroy 2018-06-07 12:55:09 +02:00 committed by GitHub
parent ac3ed00e67
commit 1c4e822bed
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
33 changed files with 105 additions and 68 deletions

View File

@ -37,7 +37,7 @@ void (*caml_scan_roots_hook) (scanning_action) = NULL;
/* The hashtable of frame descriptors */
frame_descr ** caml_frame_descriptors = NULL;
int caml_frame_descriptors_mask = 0;
uintnat caml_frame_descriptors_mask = 0;
/* Linked-list */
@ -61,7 +61,7 @@ static link *cons(void *data, link *tl) {
static link *frametables = NULL;
static intnat num_descr = 0;
static int count_descriptors(link *list) {
static intnat count_descriptors(link *list) {
intnat num_descr = 0;
link *lnk;
iter_list(list,lnk) {
@ -241,7 +241,8 @@ void caml_oldify_local_roots (void)
value * regs;
frame_descr * d;
uintnat h;
int i, j, n, ofs;
intnat i, j;
int n, ofs;
#ifdef Stack_grows_upwards
short * p; /* PR#4339: stack offsets are negative in this case */
#else

View File

@ -130,7 +130,7 @@ CAMLexport value caml_alloc_final (mlsize_t len, final_fun fun,
CAMLexport value caml_copy_string(char const *s)
{
int len;
mlsize_t len;
value res;
len = strlen(s);

View File

@ -321,10 +321,6 @@ CAMLprim value caml_get_current_callstack(value max_frames_value)
/* Read the debugging info contained in the current bytecode executable. */
#ifndef O_BINARY
#define O_BINARY 0
#endif
static void read_main_debug_info(struct debug_info *di)
{
CAMLparam0();

View File

@ -573,7 +573,7 @@ value caml_ba_get_N(value vb, value * vind, int nind)
default:
CAMLassert(0);
case CAML_BA_FLOAT32:
return caml_copy_double(((float *) b->data)[offset]);
return caml_copy_double((double) ((float *) b->data)[offset]);
case CAML_BA_FLOAT64:
return caml_copy_double(((double *) b->data)[offset]);
case CAML_BA_SINT8:
@ -594,7 +594,7 @@ value caml_ba_get_N(value vb, value * vind, int nind)
return Val_long(((intnat *) b->data)[offset]);
case CAML_BA_COMPLEX32:
{ float * p = ((float *) b->data) + offset * 2;
return copy_two_doubles(p[0], p[1]); }
return copy_two_doubles((double) p[0], (double) p[1]); }
case CAML_BA_COMPLEX64:
{ double * p = ((double *) b->data) + offset * 2;
return copy_two_doubles(p[0], p[1]); }
@ -647,7 +647,7 @@ CAMLprim value caml_ba_uint8_get16(value vb, value vind)
CAMLprim value caml_ba_uint8_get32(value vb, value vind)
{
intnat res;
uint32_t res;
unsigned char b1, b2, b3, b4;
intnat idx = Long_val(vind);
struct caml_ba_array * b = Caml_ba_array_val(vb);

View File

@ -24,8 +24,8 @@ void caml_final_update_mark_phase (void);
void caml_final_update_clean_phase (void);
void caml_final_do_calls (void);
void caml_final_do_roots (scanning_action f);
void caml_final_invert_finalisable_values ();
void caml_final_oldify_young_roots ();
void caml_final_invert_finalisable_values (void);
void caml_final_oldify_young_roots (void);
void caml_final_empty_young (void);
void caml_final_update_minor_roots(void);
value caml_final_register (value f, value v);

View File

@ -26,9 +26,9 @@
extern intnat caml_icount;
void caml_stop_here (void);
void caml_disasm_instr (code_t pc);
void caml_trace_value_file (value v, code_t prog, int proglen, FILE * f);
void caml_trace_accu_sp_file(value accu, value * sp, code_t prog, int proglen,
FILE * f);
void caml_trace_value_file (value v, code_t prog, asize_t proglen, FILE * f);
void caml_trace_accu_sp_file(value accu, value * sp, code_t prog,
asize_t proglen, FILE * f);
#endif /* CAML_INTERNALS */

View File

@ -181,7 +181,11 @@ CAMLextern void caml_deserialize_block_2(void * data, intnat len);
CAMLextern void caml_deserialize_block_4(void * data, intnat len);
CAMLextern void caml_deserialize_block_8(void * data, intnat len);
CAMLextern void caml_deserialize_block_float_8(void * data, intnat len);
CAMLextern void caml_deserialize_error(char * msg);
CAMLnoreturn_start
CAMLextern void caml_deserialize_error(char * msg)
CAMLnoreturn_end;
#ifdef CAML_INTERNALS

View File

@ -100,7 +100,7 @@ extern caml_timing_hook caml_finalise_begin_hook, caml_finalise_end_hook;
#define CAMLassert(x) \
((x) ? (void) 0 : caml_failed_assert ( #x , __FILE__, __LINE__))
CAMLnoreturn_start
CAMLextern int caml_failed_assert (char *, char *, int)
CAMLextern void caml_failed_assert (char *, char *, int)
CAMLnoreturn_end;
#else
#define CAMLassert(x) ((void) 0)

View File

@ -93,7 +93,7 @@ typedef struct {
/* Hash table of frame descriptors */
extern frame_descr ** caml_frame_descriptors;
extern int caml_frame_descriptors_mask;
extern uintnat caml_frame_descriptors_mask;
#define Hash_retaddr(addr) \
(((uintnat)(addr) >> 3) & caml_frame_descriptors_mask)

View File

@ -33,7 +33,7 @@ extern uintnat caml_init_heap_wsz;
extern uintnat caml_init_max_stack_wsz;
extern uintnat caml_init_major_window;
extern uintnat caml_trace_level;
extern uintnat caml_cleanup_on_exit;
extern int caml_cleanup_on_exit;
extern void caml_parse_ocamlrunparam (void);

View File

@ -26,11 +26,26 @@ extern "C" {
#define NO_ARG Val_int(0)
CAMLextern void caml_sys_error (value);
CAMLextern void caml_sys_io_error (value);
CAMLnoreturn_start
CAMLextern void caml_sys_error (value)
CAMLnoreturn_end;
CAMLnoreturn_start
CAMLextern void caml_sys_io_error (value)
CAMLnoreturn_end;
CAMLextern double caml_sys_time_unboxed(value);
CAMLextern void caml_sys_init (char_os * exe_name, char_os ** argv);
#ifndef CAML_WITH_CPLUGINS
CAMLnoreturn_start
CAMLextern value caml_sys_exit (value)
CAMLnoreturn_end;
#else
CAMLextern value caml_sys_exit (value);
/* A plugin could cause caml_sys_exit to return normally */
#endif
extern double caml_sys_time_unboxed(value);
CAMLextern value caml_sys_get_argv(value unit);

View File

@ -58,7 +58,9 @@ extern void caml_shrink_heap (char *); /* memory.c */
#define Whsize_ehd(h) Whsize_hd (h)
#define Wosize_ehd(h) Wosize_hd (h)
#define Tag_ehd(h) (((h) >> 2) & 0xFF)
#ifdef WITH_PROFINFO
#define Profinfo_ehd(hd) Profinfo_hd(hd)
#endif
#define Ecolor(w) ((w) & 3)
typedef uintnat word;
@ -513,7 +515,7 @@ void caml_compact_heap_maybe (void)
Estimated free percentage: FP = 100 * FW / LW
We compact the heap if FP > caml_percent_max
*/
float fw, fp;
double fw, fp;
CAMLassert (caml_gc_phase == Phase_idle);
if (caml_percent_max >= 1000000) return;
if (caml_stat_major_collections < 3) return;

View File

@ -52,6 +52,10 @@ static void compare_free_stack(struct compare_stack* stk)
}
/* Same, then raise Out_of_memory */
CAMLnoreturn_start
static void compare_stack_overflow(struct compare_stack* stk)
CAMLnoreturn_end;
static void compare_stack_overflow(struct compare_stack* stk)
{
caml_gc_message (0x04, "Stack overflow in structural comparison\n");

View File

@ -360,7 +360,7 @@ static void writecode16(int code, intnat val)
{
if (extern_ptr + 3 > extern_limit) grow_extern_output(3);
extern_ptr[0] = code;
store16(extern_ptr + 1, val);
store16(extern_ptr + 1, (int) val);
extern_ptr += 3;
}

View File

@ -487,7 +487,7 @@ CAMLprim value caml_frexp_float(value f)
// Seems dumb but intnat could not correspond to int type.
double caml_ldexp_float_unboxed(double f, intnat i)
{
return ldexp(f, i);
return ldexp(f, (int) i);
}

View File

@ -480,7 +480,7 @@ CAMLprim value caml_gc_minor(value v)
static void test_and_compact (void)
{
float fp;
double fp;
fp = 100.0 * caml_fl_cur_wsz / (caml_stat_heap_wsz - caml_fl_cur_wsz);
if (fp > 999999.0) fp = 999999.0;

View File

@ -178,7 +178,7 @@ char * caml_instr_string (code_t pc)
void
caml_trace_value_file (value v, code_t prog, int proglen, FILE * f)
caml_trace_value_file (value v, code_t prog, asize_t proglen, FILE * f)
{
int i;
fprintf (f, "%#" ARCH_INTNAT_PRINTF_FORMAT "x", v);
@ -248,7 +248,7 @@ caml_trace_value_file (value v, code_t prog, int proglen, FILE * f)
}
void
caml_trace_accu_sp_file (value accu, value * sp, code_t prog, int proglen,
caml_trace_accu_sp_file (value accu, value * sp, code_t prog, asize_t proglen,
FILE * f)
{
int i;

View File

@ -54,7 +54,7 @@ static asize_t obj_counter;
static value * intern_obj_table = NULL;
/* The pointers to objects already seen */
static unsigned int intern_color;
static color_t intern_color;
/* Color to assign to newly created headers */
static header_t intern_header;
@ -264,6 +264,10 @@ static void intern_free_stack(void)
}
/* Same, then raise Out_of_memory */
CAMLnoreturn_start
static void intern_stack_overflow(void)
CAMLnoreturn_end;
static void intern_stack_overflow(void)
{
caml_gc_message (0x04, "Stack overflow in un-marshaling value\n");

View File

@ -213,7 +213,7 @@ value caml_interprete(code_t prog, asize_t prog_size)
value env;
intnat extra_args;
struct longjmp_buffer * initial_external_raise;
int initial_sp_offset;
intnat initial_sp_offset;
/* volatile ensures that initial_local_roots and saved_pc
will keep correct value across longjmp */
struct caml__roots_block * volatile initial_local_roots;

View File

@ -286,25 +286,25 @@ static int32_t caml_swap32(int32_t x)
}
value caml_int32_direct_bswap(value v)
{ return caml_swap32(v); }
{ return caml_swap32((int32_t) v); }
CAMLprim value caml_int32_bswap(value v)
{ return caml_copy_int32(caml_swap32(Int32_val(v))); }
CAMLprim value caml_int32_of_int(value v)
{ return caml_copy_int32(Long_val(v)); }
{ return caml_copy_int32((int32_t) Long_val(v)); }
CAMLprim value caml_int32_to_int(value v)
{ return Val_long(Int32_val(v)); }
int32_t caml_int32_of_float_unboxed(double x)
{ return x; }
{ return (int32_t) x; }
CAMLprim value caml_int32_of_float(value v)
{ return caml_copy_int32((int32_t)(Double_val(v))); }
double caml_int32_to_float_unboxed(int32_t x)
{ return x; }
{ return (double) x; }
CAMLprim value caml_int32_to_float(value v)
{ return caml_copy_double((double)(Int32_val(v))); }
@ -329,21 +329,21 @@ CAMLprim value caml_int32_format(value fmt, value arg)
CAMLprim value caml_int32_of_string(value s)
{
return caml_copy_int32(parse_intnat(s, 32, INT32_ERRMSG));
return caml_copy_int32((int32_t) parse_intnat(s, 32, INT32_ERRMSG));
}
int32_t caml_int32_bits_of_float_unboxed(double d)
{
union { float d; int32_t i; } u;
u.d = d;
union { float f; int32_t i; } u;
u.f = (float) d;
return u.i;
}
double caml_int32_float_of_bits_unboxed(int32_t i)
{
union { float d; int32_t i; } u;
union { float f; int32_t i; } u;
u.i = i;
return u.d;
return (double) u.f;
}
CAMLprim value caml_int32_bits_of_float(value vd)
@ -440,8 +440,6 @@ CAMLprim value caml_int64_sub(value v1, value v2)
CAMLprim value caml_int64_mul(value v1, value v2)
{ return caml_copy_int64(Int64_val(v1) * Int64_val(v2)); }
#define Int64_min_int ((intnat) 1 << (sizeof(intnat) * 8 - 1))
CAMLprim value caml_int64_div(value v1, value v2)
{
int64_t dividend = Int64_val(v1);
@ -522,13 +520,13 @@ CAMLprim value caml_int64_to_int(value v)
{ return Val_long((intnat) (Int64_val(v))); }
int64_t caml_int64_of_float_unboxed(double x)
{ return x; }
{ return (int64_t) x; }
CAMLprim value caml_int64_of_float(value v)
{ return caml_copy_int64((int64_t) (Double_val(v))); }
double caml_int64_to_float_unboxed(int64_t x)
{ return x; }
{ return (double) x; }
CAMLprim value caml_int64_to_float(value v)
{ return caml_copy_double((double) (Int64_val(v))); }
@ -788,13 +786,13 @@ CAMLprim value caml_nativeint_to_int(value v)
{ return Val_long(Nativeint_val(v)); }
intnat caml_nativeint_of_float_unboxed(double x)
{ return x; }
{ return (intnat) x; }
CAMLprim value caml_nativeint_of_float(value v)
{ return caml_copy_nativeint((intnat)(Double_val(v))); }
double caml_nativeint_to_float_unboxed(intnat x)
{ return x; }
{ return (double) x; }
CAMLprim value caml_nativeint_to_float(value v)
{ return caml_copy_double((double)(Nativeint_val(v))); }
@ -803,7 +801,7 @@ CAMLprim value caml_nativeint_of_int32(value v)
{ return caml_copy_nativeint(Int32_val(v)); }
CAMLprim value caml_nativeint_to_int32(value v)
{ return caml_copy_int32(Nativeint_val(v)); }
{ return caml_copy_int32((int32_t) Nativeint_val(v)); }
intnat caml_nativeint_compare_unboxed(intnat i1, intnat i2)
{

View File

@ -642,7 +642,7 @@ CAMLprim value caml_ml_output_int(value vchannel, value w)
struct channel * channel = Channel(vchannel);
Lock(channel);
caml_putword(channel, Long_val(w));
caml_putword(channel, (uint32_t) Long_val(w));
Unlock(channel);
CAMLreturn (Val_unit);
}

View File

@ -231,7 +231,8 @@ static void init_sweep_phase(void)
}
/* auxillary function of mark_slice */
static inline value* mark_slice_darken(value *gray_vals_ptr, value v, int i,
static inline value* mark_slice_darken(value *gray_vals_ptr,
value v, mlsize_t i,
int in_ephemeron, int *slice_pointers)
{
value child;

View File

@ -33,7 +33,7 @@ caml_timing_hook caml_finalise_end_hook = NULL;
#ifdef DEBUG
int caml_failed_assert (char * expr, char * file, int line)
void caml_failed_assert (char * expr, char * file, int line)
{
fprintf (stderr, "file %s; line %d ### Assertion failed: %s\n",
file, line, expr);

View File

@ -42,7 +42,7 @@ static void add_char(struct stringbuf *buf, char c)
static void add_string(struct stringbuf *buf, const char *s)
{
int len = strlen(s);
size_t len = strlen(s);
if (buf->ptr + len > buf->end) len = buf->end - buf->ptr;
if (len > 0) memmove(buf->ptr, s, len);
buf->ptr += len;

View File

@ -508,7 +508,7 @@ CAMLexport value caml_startup_code_exn(
caml_init_code_fragments();
caml_init_debug_info();
if (caml_debugger_in_use) {
int len, i;
uintnat len, i;
len = code_size / sizeof(opcode_t);
caml_saved_code = (unsigned char *) caml_stat_alloc(len);
for (i = 0; i < len; i++) caml_saved_code[i] = caml_start_code[i];

View File

@ -61,7 +61,7 @@ uintnat caml_init_max_stack_wsz = Max_stack_def;
uintnat caml_init_major_window = Major_window_def;
extern int caml_parser_trace;
uintnat caml_trace_level = 0;
uintnat caml_cleanup_on_exit = 0;
int caml_cleanup_on_exit = 0;
static void scanmult (char_os *opt, uintnat *var)
@ -90,14 +90,14 @@ void caml_parse_ocamlrunparam(void)
switch (*opt++){
case _T('a'): scanmult (opt, &p); caml_set_allocation_policy (p); break;
case _T('b'): scanmult (opt, &p); caml_record_backtrace(Val_bool (p)); break;
case _T('c'): scanmult (opt, &p); caml_cleanup_on_exit = p; break;
case _T('c'): scanmult (opt, &p); caml_cleanup_on_exit = (p != 0); break;
case _T('h'): scanmult (opt, &caml_init_heap_wsz); break;
case _T('H'): scanmult (opt, &caml_use_huge_pages); break;
case _T('i'): scanmult (opt, &caml_init_heap_chunk_sz); break;
case _T('l'): scanmult (opt, &caml_init_max_stack_wsz); break;
case _T('o'): scanmult (opt, &caml_init_percent_free); break;
case _T('O'): scanmult (opt, &caml_init_max_percent_free); break;
case _T('p'): scanmult (opt, &p); caml_parser_trace = p; break;
case _T('p'): scanmult (opt, &p); caml_parser_trace = (p != 0); break;
case _T('R'): break; /* see stdlib/hashtbl.mli */
case _T('s'): scanmult (opt, &caml_init_minor_heap_wsz); break;
case _T('t'): scanmult (opt, &caml_trace_level); break;

View File

@ -133,7 +133,7 @@ CAMLprim value caml_bytes_get16(value str, value index)
CAMLprim value caml_string_get32(value str, value index)
{
intnat res;
int32_t res;
unsigned char b1, b2, b3, b4;
intnat idx = Long_val(index);
if (idx < 0 || idx + 3 >= caml_string_length(str)) caml_array_bound_error();

View File

@ -82,8 +82,8 @@ CAMLexport void caml_sys_error(value arg)
if (arg == NO_ARG) {
str = caml_copy_string(err);
} else {
int err_len = strlen(err);
int arg_len = caml_string_length(arg);
mlsize_t err_len = strlen(err);
mlsize_t arg_len = caml_string_length(arg);
str = caml_alloc_string(arg_len + 2 + err_len);
memmove(&Byte(str, 0), String_val(arg), arg_len);
memmove(&Byte(str, arg_len), ": ", 2);
@ -157,7 +157,9 @@ CAMLprim value caml_sys_exit(value retcode_v)
caml_restore_win32_terminal();
#endif
CAML_SYS_EXIT(retcode);
#ifdef CAML_WITH_CPLUGINS
return Val_unit;
#endif
}
#ifndef O_BINARY

View File

@ -83,7 +83,6 @@ CAMLprim value caml_spacetime_unmarshal_trie (value v_channel)
CAMLprim value caml_spacetime_node_num_header_words(value unit)
{
unit = Val_unit;
return Val_long(Node_num_header_words);
}

View File

@ -76,6 +76,10 @@ static INLINE void st_thread_cleanup(void)
/* Thread termination */
CAMLnoreturn_start
static void st_thread_exit(void)
CAMLnoreturn_end;
static void st_thread_exit(void)
{
pthread_exit(NULL);
@ -89,7 +93,7 @@ static void st_thread_join(st_thread_id thr)
/* Scheduling hints */
static void INLINE st_thread_yield(void)
static INLINE void st_thread_yield(void)
{
#ifdef __linux__
/* sched_yield() doesn't do what we want in Linux 2.6 and up (PR#2663) */

View File

@ -39,8 +39,10 @@
#include "caml/spacetime.h"
#endif
#ifndef NATIVE_CODE
/* Initial size of bytecode stack when a thread is created (4 Ko) */
#define Thread_stack_size (Stack_size / 4)
#endif
/* Max computation time before rescheduling, in milliseconds */
#define Thread_timeout 50
@ -775,7 +777,8 @@ static struct custom_operations caml_mutex_ops = {
caml_mutex_compare,
caml_mutex_hash,
custom_serialize_default,
custom_deserialize_default
custom_deserialize_default,
custom_compare_ext_default
};
CAMLprim value caml_mutex_new(value unit) /* ML */

View File

@ -83,6 +83,10 @@ static void st_thread_cleanup(void)
/* Thread termination */
CAMLnoreturn_start
static void st_thread_exit(void)
CAMLnoreturn_end;
static void st_thread_exit(void)
{
TRACE("st_thread_exit");

View File

@ -25,14 +25,6 @@
#include <sys/resource.h>
#endif
#ifndef CLK_TCK
#ifdef HZ
#define CLK_TCK HZ
#else
#define CLK_TCK 60
#endif
#endif
CAMLprim value unix_times(value unit)
{
#ifdef HAS_GETRUSAGE
@ -52,6 +44,14 @@ CAMLprim value unix_times(value unit)
#else
#ifndef CLK_TCK
#ifdef HZ
#define CLK_TCK HZ
#else
#define CLK_TCK 60
#endif
#endif
value res;
struct tms buffer;