Add cplugins and option -fPIC to ./configure

master
Fabrice Le Fessant 2016-07-06 16:37:56 +02:00
parent 18cd8a6c01
commit 6a83bdd593
7 changed files with 242 additions and 18 deletions

View File

@ -124,7 +124,101 @@ CAMLnoreturn_end;
CAMLextern char * caml_strdup(const char * s);
CAMLextern char * caml_strconcat(int n, ...); /* n args of const char * type */
#ifdef CAML_INTERNALS
/* Use macros for some system calls being called from OCaml itself.
These calls can be either traced for security reasons, or changed to
virtualize the program. */
#ifndef CAML_WITH_CPLUGINS
#define CAML_SYS_EXIT(retcode) exit(retcode)
#define CAML_SYS_OPEN(filename,flags,perm) open(filename,flags,perm)
#define CAML_SYS_CLOSE(fd) close(fd)
#define CAML_SYS_STAT(filename,st) stat(filename,st)
#define CAML_SYS_UNLINK(filename) unlink(filename)
#define CAML_SYS_RENAME(old_name,new_name) rename(old_name, new_name)
#define CAML_SYS_CHDIR(dirname) chdir(dirname)
#define CAML_SYS_GETENV(varname) getenv(varname)
#define CAML_SYS_SYSTEM(command) system(command)
#define CAML_SYS_READ_DIRECTORY(dirname,tbl) caml_read_directory(dirname,tbl)
#else
#define CAML_CPLUGINS_EXIT 0
#define CAML_CPLUGINS_OPEN 1
#define CAML_CPLUGINS_CLOSE 2
#define CAML_CPLUGINS_STAT 3
#define CAML_CPLUGINS_UNLINK 4
#define CAML_CPLUGINS_RENAME 5
#define CAML_CPLUGINS_CHDIR 6
#define CAML_CPLUGINS_GETENV 7
#define CAML_CPLUGINS_SYSTEM 8
#define CAML_CPLUGINS_READ_DIRECTORY 9
#define CAML_CPLUGINS_PRIMS_MAX 9
#define CAML_CPLUGINS_PRIMS_BITMAP ((1 << CAML_CPLUGINS_PRIMS_MAX)-1)
extern intnat (*caml_cplugins_prim)(int,intnat,intnat,intnat);
#define CAML_SYS_PRIM_1(code,prim,arg1) \
(caml_cplugins_prim == NULL) ? prim(arg1) : \
caml_cplugins_prim(code,(intnat) (arg1),0,0)
#define CAML_SYS_STRING_PRIM_1(code,prim,arg1) \
(caml_cplugins_prim == NULL) ? prim(arg1) : \
(char*)caml_cplugins_prim(code,(intnat) (arg1),0,0)
#define CAML_SYS_PRIM_2(code,prim,arg1,arg2) \
(caml_cplugins_prim == NULL) ? prim(arg1,arg2) : \
caml_cplugins_prim(code,(intnat) (arg1), (intnat) (arg2),0)
#define CAML_SYS_PRIM_3(code,prim,arg1,arg2,arg3) \
(caml_cplugins_prim == NULL) ? prim(arg1,arg2,arg3) : \
caml_cplugins_prim(code,(intnat) (arg1), (intnat) (arg2),(intnat) (arg3))
#define CAML_SYS_EXIT(retcode) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_EXIT,exit,retcode)
#define CAML_SYS_OPEN(filename,flags,perm) \
CAML_SYS_PRIM_3(CAML_CPLUGINS_OPEN,open,filename,flags,perm)
#define CAML_SYS_CLOSE(fd) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_CLOSE,close,fd)
#define CAML_SYS_STAT(filename,st) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_STAT,stat,filename,st)
#define CAML_SYS_UNLINK(filename) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_UNLINK,unlink,filename)
#define CAML_SYS_RENAME(old_name,new_name) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_RENAME,rename,old_name,new_name)
#define CAML_SYS_CHDIR(dirname) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_CHDIR,chdir,dirname)
#define CAML_SYS_GETENV(varname) \
CAML_SYS_STRING_PRIM_1(CAML_CPLUGINS_GETENV,getenv,varname)
#define CAML_SYS_SYSTEM(command) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_SYSTEM,system,command)
#define CAML_SYS_READ_DIRECTORY(dirname,tbl) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_READ_DIRECTORY,caml_read_directory, \
dirname,tbl)
#define CAML_CPLUGIN_CONTEXT_API 0
struct cplugin_context {
int api_version;
int prims_bitmap;
char *exe_name;
char** argv;
char *plugin; /* absolute filename of plugin, do a copy if you need it ! */
char *ocaml_version;
/* end of CAML_CPLUGIN_CONTEXT_API version 0 */
};
extern void caml_cplugins_init(char * exe_name, char **argv);
/* A plugin MUST define a symbol "caml_cplugin_init" with the prototype:
void caml_cplugin_init(struct cplugin_context *ctx)
*/
/* to write plugins for CAML_SYS_READ_DIRECTORY, we will need the
definition of struct ext_table to be public. */
#endif /* CAML_WITH_CPLUGINS */
/* Data structures */
@ -140,6 +234,11 @@ 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);
CAMLextern int caml_read_directory(char * dirname, struct ext_table * contents);
#ifdef CAML_INTERNALS
/* GC flags and messages */
extern uintnat caml_verb_gc;

View File

@ -20,6 +20,10 @@
#include "misc.h"
#ifdef __cplusplus
extern "C" {
#endif
#define NO_ARG Val_int(0)
CAMLextern void caml_sys_error (value);
@ -31,6 +35,10 @@ CAMLextern value caml_sys_get_argv(value unit);
extern char * caml_exe_name;
#ifdef __cplusplus
}
#endif
#endif /* CAML_INTERNALS */
#endif /* CAML_SYS_H */

View File

@ -112,7 +112,7 @@ static void unlink_channel(struct channel *channel)
CAMLexport void caml_close_channel(struct channel *channel)
{
close(channel->fd);
CAML_SYS_CLOSE(channel->fd);
if (channel->refcount > 0) return;
if (caml_channel_mutex_free != NULL) (*caml_channel_mutex_free)(channel);
unlink_channel(channel);
@ -534,7 +534,7 @@ CAMLprim value caml_ml_close_channel(value vchannel)
if (do_syscall) {
caml_enter_blocking_section();
result = close(fd);
result = CAML_SYS_CLOSE(fd);
caml_leave_blocking_section();
}

View File

@ -143,5 +143,6 @@ void caml_fatal_uncaught_exception(value exn)
else
default_fatal_uncaught_exception(exn);
/* Terminate the process */
exit(2);
CAML_SYS_EXIT(2);
exit(2); /* Second exit needed for the Noreturn flag */
}

View File

@ -57,6 +57,7 @@
#include "caml/signals.h"
#include "caml/stacks.h"
#include "caml/sys.h"
#include "caml/version.h"
static char * error_message(void)
{
@ -110,8 +111,10 @@ static void caml_sys_check_path(value name)
}
}
CAMLprim value caml_sys_exit(value retcode)
CAMLprim value caml_sys_exit(value retcode_v)
{
int retcode = Int_val(retcode_v);
if ((caml_verb_gc & 0x400) != 0) {
/* cf caml_gc_counters */
double minwords = caml_stat_minor_words
@ -141,7 +144,7 @@ CAMLprim value caml_sys_exit(value retcode)
caml_debugger(PROGRAM_EXIT);
#endif
CAML_INSTR_ATEXIT ();
exit(Int_val(retcode));
CAML_SYS_EXIT(retcode);
return Val_unit;
}
@ -176,7 +179,7 @@ CAMLprim value caml_sys_open(value path, value vflags, value vperm)
perm = Int_val(vperm);
/* open on a named FIFO can block (PR#1533) */
caml_enter_blocking_section();
fd = open(p, flags, perm);
fd = CAML_SYS_OPEN(p, flags, perm);
/* fcntl on a fd can block (PR#5069)*/
#if defined(F_SETFD) && defined(FD_CLOEXEC)
if (fd != -1)
@ -188,10 +191,11 @@ CAMLprim value caml_sys_open(value path, value vflags, value vperm)
CAMLreturn(Val_long(fd));
}
CAMLprim value caml_sys_close(value fd)
CAMLprim value caml_sys_close(value fd_v)
{
int fd = Int_val(fd_v);
caml_enter_blocking_section();
close(Int_val(fd));
CAML_SYS_CLOSE(fd);
caml_leave_blocking_section();
return Val_unit;
}
@ -212,7 +216,7 @@ CAMLprim value caml_sys_file_exists(value name)
#ifdef _WIN32
ret = _stati64(p, &st);
#else
ret = stat(p, &st);
ret = CAML_SYS_STAT(p, &st);
#endif
caml_leave_blocking_section();
caml_stat_free(p);
@ -237,7 +241,7 @@ CAMLprim value caml_sys_is_directory(value name)
#ifdef _WIN32
ret = _stati64(p, &st);
#else
ret = stat(p, &st);
ret = CAML_SYS_STAT(p, &st);
#endif
caml_leave_blocking_section();
caml_stat_free(p);
@ -258,7 +262,7 @@ CAMLprim value caml_sys_remove(value name)
caml_sys_check_path(name);
p = caml_strdup(String_val(name));
caml_enter_blocking_section();
ret = unlink(p);
ret = CAML_SYS_UNLINK(p);
caml_leave_blocking_section();
caml_stat_free(p);
if (ret != 0) caml_sys_error(name);
@ -275,7 +279,7 @@ CAMLprim value caml_sys_rename(value oldname, value newname)
p_old = caml_strdup(String_val(oldname));
p_new = caml_strdup(String_val(newname));
caml_enter_blocking_section();
ret = rename(p_old, p_new);
ret = CAML_SYS_RENAME(p_old, p_new);
caml_leave_blocking_section();
caml_stat_free(p_new);
caml_stat_free(p_old);
@ -292,7 +296,7 @@ CAMLprim value caml_sys_chdir(value dirname)
caml_sys_check_path(dirname);
p = caml_strdup(String_val(dirname));
caml_enter_blocking_section();
ret = chdir(p);
ret = CAML_SYS_CHDIR(p);
caml_leave_blocking_section();
caml_stat_free(p);
if (ret != 0) caml_sys_error(dirname);
@ -315,7 +319,7 @@ CAMLprim value caml_sys_getenv(value var)
char * res;
if (! caml_string_is_c_safe(var)) caml_raise_not_found();
res = getenv(String_val(var));
res = CAML_SYS_GETENV(String_val(var));
if (res == 0) caml_raise_not_found();
return caml_copy_string(res);
}
@ -337,6 +341,9 @@ CAMLprim value caml_sys_get_argv(value unit)
void caml_sys_init(char * exe_name, char **argv)
{
#ifdef CAML_WITH_CPLUGINS
caml_cplugins_init(exe_name, argv);
#endif
caml_exe_name = exe_name;
caml_main_argv = argv;
}
@ -364,7 +371,7 @@ CAMLprim value caml_sys_system_command(value command)
}
buf = caml_strdup(String_val(command));
caml_enter_blocking_section ();
status = system(buf);
status = CAML_SYS_SYSTEM(buf);
caml_leave_blocking_section ();
caml_stat_free(buf);
if (status == -1) caml_sys_error(command);
@ -528,7 +535,7 @@ CAMLprim value caml_sys_read_directory(value path)
caml_ext_table_init(&tbl, 50);
p = caml_strdup(String_val(path));
caml_enter_blocking_section();
ret = caml_read_directory(p, &tbl);
ret = CAML_SYS_READ_DIRECTORY(p, &tbl);
caml_leave_blocking_section();
caml_stat_free(p);
if (ret == -1){
@ -558,3 +565,74 @@ CAMLprim value caml_sys_isatty(value chan)
return ret;
}
/* Load dynamic plugins indicated in the CAML_CPLUGINS environment
variable. These plugins can be used to set currently existing
hooks, such as GC hooks and system calls tracing (see misc.h).
*/
#ifdef CAML_WITH_CPLUGINS
value (*caml_cplugins_prim)(int,value,value,value) = NULL;
#define DLL_EXECUTABLE 1
#define DLL_NOT_GLOBAL 0
static struct cplugin_context cplugin_context;
void caml_load_plugin(char *plugin)
{
void* dll_handle = NULL;
dll_handle = caml_dlopen(plugin, DLL_EXECUTABLE, DLL_NOT_GLOBAL);
if( dll_handle != NULL ){
void (* dll_init)(struct cplugin_context*) =
caml_dlsym(dll_handle, "caml_cplugin_init");
if( dll_init != NULL ){
cplugin_context.plugin=plugin;
dll_init(&cplugin_context);
} else {
caml_dlclose(dll_handle);
}
} else {
fprintf(stderr, "Cannot load C plugin %s\nReason: %s\n",
plugin, caml_dlerror());
}
}
void caml_cplugins_load(char *env_variable)
{
char *plugins = getenv(env_variable);
if(plugins != NULL){
char* curs = plugins;
while(*curs != 0){
if(*curs == ','){
if(curs > plugins){
*curs = 0;
caml_load_plugin(plugins);
}
plugins = curs+1;
}
curs++;
}
if(curs > plugins) caml_load_plugin(plugins);
}
}
void caml_cplugins_init(char * exe_name, char **argv)
{
cplugin_context.api_version = CAML_CPLUGIN_CONTEXT_API;
cplugin_context.prims_bitmap = CAML_CPLUGINS_PRIMS_BITMAP;
cplugin_context.exe_name = exe_name;
cplugin_context.argv = argv;
cplugin_context.ocaml_version = OCAML_VERSION_STRING;
caml_cplugins_load("CAML_CPLUGINS");
#ifdef NATIVE_CODE
caml_cplugins_load("CAML_NATIVE_CPLUGINS");
#else
caml_cplugins_load("CAML_BYTE_CPLUGINS");
#endif
}
#endif /* CAML_WITH_CPLUGINS */

View File

@ -324,7 +324,7 @@ char * caml_dlerror(void)
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(char * dirname, struct ext_table * contents)
CAMLexport int caml_read_directory(char * dirname, struct ext_table * contents)
{
DIR * d;
#ifdef HAS_DIRENT

38
configure vendored
View File

@ -54,6 +54,8 @@ TOOLPREF=""
with_cfi=true
flambda=false
max_testsuite_dir_retries=0
with_cplugins=true
with_fpic=false
# Try to turn internationalization off, can cause config.guess to malfunction!
unset LANG
@ -167,6 +169,10 @@ while : ; do
native_compiler=false;;
-flambda|--flambda)
flambda=true;;
-no-cplugins|--no-cplugins)
with_cplugins=false;;
-fPIC|--fPIC)
with_fpic=true;;
*) if echo "$1" | grep -q -e '^--\?[a-zA-Z0-9-]\+='; then
err "configure expects arguments of the form '-prefix /foo/bar'," \
"not '-prefix=/foo/bar' (note the '=')."
@ -1742,6 +1748,26 @@ else
has_huge_pages=false
fi
if ! $shared_libraries_supported; then
with_cplugins=false
fi
if $with_fpic; then
bytecccompopts="$bytecccompopts $sharedcccompopts"
nativecccompopts="$nativecccompopts $sharedcccompopts"
aspp="$aspp $sharedcccompopts"
fi
if $with_cplugins; then
echo "#define CAML_WITH_CPLUGINS" >> m.h
fi
if $with_fpic; then
echo "#define CAML_WITH_FPIC" >> m.h
fi
# Finish generated files
cclibs="$cclibs $mathlib"
@ -1816,6 +1842,8 @@ echo "WITH_DEBUGGER=${with_debugger}" >>Makefile
echo "WITH_OCAMLDOC=${with_ocamldoc}" >>Makefile
echo "ASM_CFI_SUPPORTED=$asm_cfi_supported" >> Makefile
echo "WITH_FRAME_POINTERS=$with_frame_pointers" >> Makefile
echo "WITH_CPLUGINS=$with_cplugins" >> Makefile
echo "WITH_FPIC=$with_fpic" >> Makefile
echo "TARGET=$target" >> Makefile
echo "HOST=$host" >> Makefile
if [ "$ostype" = Cygwin ]; then
@ -1885,6 +1913,16 @@ else
else
inf " naked pointers forbidden.. no"
fi
if $with_cplugins; then
inf " C plugins................. yes"
else
inf " C plugins................. no"
fi
if $with_fpic; then
inf " compile with -fPIC........ yes"
else
inf " compile with -fPIC........ no"
fi
inf " native dynlink ........... $natdynlink"
if test "$profiling" = "prof"; then
inf " profiling with gprof ..... supported"