Remaining functions requiring explicit export

master
David Allsopp 2020-09-16 17:41:26 +01:00
parent f6a5b755f8
commit 17cceab054
14 changed files with 34 additions and 33 deletions

View File

@ -35,7 +35,7 @@ enum event_kind {
void caml_debugger_init (void);
void caml_debugger (enum event_kind event, value param);
void caml_debugger_cleanup_fork (void);
CAMLextern void caml_debugger_cleanup_fork (void);
opcode_t caml_debugger_saved_instruction(code_t pc);

View File

@ -65,7 +65,7 @@ struct longjmp_buffer {
int caml_is_special_exception(value exn);
value caml_raise_if_exception(value res);
CAMLextern value caml_raise_if_exception(value res);
#endif /* CAML_INTERNALS */

View File

@ -43,10 +43,10 @@ extern void caml_memprof_invert_tracked(void);
struct caml_memprof_th_ctx {
int suspended, callback_running;
};
extern void caml_memprof_init_th_ctx(struct caml_memprof_th_ctx* ctx);
extern void caml_memprof_stop_th_ctx(struct caml_memprof_th_ctx* ctx);
extern void caml_memprof_save_th_ctx(struct caml_memprof_th_ctx* ctx);
extern void caml_memprof_restore_th_ctx(const struct caml_memprof_th_ctx* ctx);
CAMLextern void caml_memprof_init_th_ctx(struct caml_memprof_th_ctx*);
CAMLextern void caml_memprof_stop_th_ctx(struct caml_memprof_th_ctx*);
CAMLextern void caml_memprof_save_th_ctx(struct caml_memprof_th_ctx*);
CAMLextern void caml_memprof_restore_th_ctx(const struct caml_memprof_th_ctx*);
#endif

View File

@ -336,6 +336,9 @@ extern void caml_ext_table_remove(struct ext_table * tbl, void * data);
extern void caml_ext_table_free(struct ext_table * tbl, int free_entries);
extern void caml_ext_table_clear(struct ext_table * tbl, int free_entries);
/* Add to [contents] the (short) names of the files contained in
the directory named [dirname]. No entries are added for [.] and [..].
Return 0 on success, -1 on error; set errno in the case of error. */
CAMLextern int caml_read_directory(char_os * dirname,
struct ext_table * contents);

View File

@ -91,11 +91,6 @@ extern void * caml_globalsym(const char * name);
/* Return an error message describing the most recent dynlink failure. */
extern char * caml_dlerror(void);
/* Add to [contents] the (short) names of the files contained in
the directory named [dirname]. No entries are added for [.] and [..].
Return 0 on success, -1 on error; set errno in the case of error. */
extern int caml_read_directory(char_os * dirname, struct ext_table * contents);
/* Recover executable name if possible (/proc/sef/exe under Linux,
GetModuleFileName under Windows). Return NULL on error,
string allocated with [caml_stat_alloc] on success. */
@ -123,11 +118,11 @@ extern wchar_t *caml_win32_getenv(wchar_t const *);
/* Windows Unicode support */
extern int win_multi_byte_to_wide_char(const char* s,
CAMLextern int win_multi_byte_to_wide_char(const char* s,
int slen,
wchar_t *out,
int outlen);
extern int win_wide_char_to_multi_byte(const wchar_t* s,
CAMLextern int win_wide_char_to_multi_byte(const wchar_t* s,
int slen,
char *out,
int outlen);
@ -140,7 +135,7 @@ extern int win_wide_char_to_multi_byte(const wchar_t* s,
The returned string is allocated with [caml_stat_alloc], so it should be free
using [caml_stat_free].
*/
extern wchar_t* caml_stat_strdup_to_utf16(const char *s);
CAMLextern wchar_t* caml_stat_strdup_to_utf16(const char *s);
/* [caml_stat_strdup_of_utf16(s)] returns a NULL-terminated copy of [s],
re-encoded in UTF-8 if [caml_windows_unicode_runtime_enabled] is non-zero or
@ -149,15 +144,15 @@ extern wchar_t* caml_stat_strdup_to_utf16(const char *s);
The returned string is allocated with [caml_stat_alloc], so it should be free
using [caml_stat_free].
*/
extern char* caml_stat_strdup_of_utf16(const wchar_t *s);
CAMLextern char* caml_stat_strdup_of_utf16(const wchar_t *s);
/* [caml_copy_string_of_utf16(s)] returns an OCaml string containing a copy of
[s] re-encoded in UTF-8 if [caml_windows_unicode_runtime_enabled] is non-zero
or in the current code page otherwise.
*/
extern value caml_copy_string_of_utf16(const wchar_t *s);
CAMLextern value caml_copy_string_of_utf16(const wchar_t *s);
extern int caml_win32_isatty(int fd);
CAMLextern int caml_win32_isatty(int fd);
CAMLextern void caml_expand_command_line (int *, wchar_t ***);

View File

@ -80,13 +80,13 @@ void caml_request_minor_gc (void);
CAMLextern int caml_convert_signal_number (int);
CAMLextern int caml_rev_convert_signal_number (int);
value caml_execute_signal_exn(int signal_number, int in_signal_handler);
void caml_record_signal(int signal_number);
value caml_process_pending_signals_exn(void);
CAMLextern void caml_record_signal(int signal_number);
CAMLextern value caml_process_pending_signals_exn(void);
void caml_set_action_pending (void);
value caml_do_pending_actions_exn (void);
value caml_process_pending_actions_with_root (value extra_root); // raises
int caml_set_signal_action(int signo, int action);
void caml_setup_stack_overflow_detection(void);
CAMLextern void caml_setup_stack_overflow_detection(void);
CAMLextern void (*caml_enter_blocking_section_hook)(void);
CAMLextern void (*caml_leave_blocking_section_hook)(void);

View File

@ -45,7 +45,7 @@ void caml_debugger(enum event_kind event, value param)
{
}
void caml_debugger_cleanup_fork(void)
CAMLexport void caml_debugger_cleanup_fork(void)
{
}
@ -562,7 +562,7 @@ void caml_debugger(enum event_kind event, value param)
}
}
void caml_debugger_cleanup_fork(void)
CAMLexport void caml_debugger_cleanup_fork(void)
{
/* We could remove all of the event points, but closing the connection
* means that they'll just be skipped anyway. */

View File

@ -192,7 +192,7 @@ CAMLexport void caml_raise_sys_blocked_io(void)
caml_raise_constant(Field(caml_global_data, SYS_BLOCKED_IO));
}
value caml_raise_if_exception(value res)
CAMLexport value caml_raise_if_exception(value res)
{
if (Is_exception_result(res)) caml_raise(Extract_exception(res));
return res;

View File

@ -177,7 +177,7 @@ void caml_raise_sys_blocked_io(void)
caml_raise_constant((value) caml_exn_Sys_blocked_io);
}
value caml_raise_if_exception(value res)
CAMLexport value caml_raise_if_exception(value res)
{
if (Is_exception_result(res)) caml_raise(Extract_exception(res));
return res;

View File

@ -996,12 +996,12 @@ CAMLprim value caml_memprof_stop(value unit)
/**** Interface with systhread. ****/
void caml_memprof_init_th_ctx(struct caml_memprof_th_ctx* ctx) {
CAMLexport void caml_memprof_init_th_ctx(struct caml_memprof_th_ctx* ctx) {
ctx->suspended = 0;
ctx->callback_running = 0;
}
void caml_memprof_stop_th_ctx(struct caml_memprof_th_ctx* ctx) {
CAMLexport void caml_memprof_stop_th_ctx(struct caml_memprof_th_ctx* ctx) {
/* Make sure that no memprof callback is being executed in this
thread. If so, memprof data structures may have pointers to the
thread's stack. */
@ -1009,12 +1009,13 @@ void caml_memprof_stop_th_ctx(struct caml_memprof_th_ctx* ctx) {
caml_fatal_error("Thread.exit called from a memprof callback.");
}
void caml_memprof_save_th_ctx(struct caml_memprof_th_ctx* ctx) {
CAMLexport void caml_memprof_save_th_ctx(struct caml_memprof_th_ctx* ctx) {
ctx->suspended = suspended;
ctx->callback_running = callback_running;
}
void caml_memprof_restore_th_ctx(const struct caml_memprof_th_ctx* ctx) {
CAMLexport void caml_memprof_restore_th_ctx
(const struct caml_memprof_th_ctx* ctx) {
callback_running = ctx->callback_running;
caml_memprof_set_suspended(ctx->suspended);
}

View File

@ -73,7 +73,7 @@ static int check_for_pending_signals(void)
/* Execute all pending signals */
value caml_process_pending_signals_exn(void)
CAMLexport value caml_process_pending_signals_exn(void)
{
int i;
#ifdef POSIX_SIGNALS
@ -129,7 +129,8 @@ void caml_set_action_pending(void)
caml_garbage_collection and caml_alloc_small_dispatch.
*/
CAMLno_tsan void caml_record_signal(int signal_number)
CAMLno_tsan
CAMLexport void caml_record_signal(int signal_number)
{
caml_pending_signals[signal_number] = 1;
signals_are_pending = 1;

View File

@ -81,4 +81,4 @@ int caml_set_signal_action(int signo, int action)
return 0;
}
void caml_setup_stack_overflow_detection(void) {}
CAMLexport void caml_setup_stack_overflow_detection(void) {}

View File

@ -283,7 +283,7 @@ void caml_init_signals(void)
#endif
}
void caml_setup_stack_overflow_detection(void)
CAMLexport void caml_setup_stack_overflow_detection(void)
{
#ifdef HAS_STACK_OVERFLOW_DETECTION
stack_t stk;

View File

@ -410,7 +410,8 @@ CAMLexport void caml_expand_command_line(int * argcp, wchar_t *** argvp)
the directory named [dirname]. No entries are added for [.] and [..].
Return 0 on success, -1 on error; set errno in the case of error. */
int caml_read_directory(wchar_t * dirname, struct ext_table * contents)
CAMLexport int caml_read_directory(wchar_t * dirname,
struct ext_table * contents)
{
size_t dirnamelen;
wchar_t * template;