Skip to content

Commit

Permalink
Remove the C plugins mechanism (#1867)
Browse files Browse the repository at this point in the history
The mechanism complicates the runtime system and is not very general
(only a few system functions are instrumented).  There are other ways
to intercept system calls that are more general and require no
modification to the source code of the runtime system.
  • Loading branch information
xavierleroy committed Jul 3, 2018
1 parent 9b44db6 commit 7e79186
Show file tree
Hide file tree
Showing 8 changed files with 21 additions and 217 deletions.
5 changes: 4 additions & 1 deletion Changes
Expand Up @@ -106,7 +106,10 @@ Working version
- GPR#1723: Remove internal Meta.static_{alloc,free} primitives.
(Stephen Dolan, review by Gabriel Scherer)

### Tools:
- GPR#1867: Remove the C plugins mechanism.
(Xavier Leroy, review by David Allsopp, Damien Doligez, Sébastien Hinderer)

### Tools

- GPR#1711: the new 'open' flag in OCAMLRUNPARAM takes a comma-separated list of
modules to open as if they had been passed via the command line -open flag.
Expand Down
17 changes: 1 addition & 16 deletions configure
Expand Up @@ -66,7 +66,6 @@ force_safe_string=false
default_safe_string=true
afl_instrument=false
max_testsuite_dir_retries=0
with_cplugins=false
with_fpic=false
flat_float_array=true
with_flambda_invariants=false
Expand Down Expand Up @@ -224,7 +223,7 @@ while : ; do
-with-flambda-invariants|--with-flambda-invariants)
with_flambda_invariants=true;;
-with-cplugins|--with-cplugins)
with_cplugins=true;;
err "--with-cplugins is no longer supported";;
-no-cplugins|--no-cplugins)
;; # Ignored for backward compatibility
-fPIC|--fPIC)
Expand Down Expand Up @@ -2046,20 +2045,12 @@ if $with_spacetime; then
fi
fi

if ! $shared_libraries_supported; then
with_cplugins=false
fi

if $with_fpic; then
common_cflags="$common_cflags $sharedlib_cflags"
aspp="$aspp $sharedlib_cflags"
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
Expand Down Expand Up @@ -2151,7 +2142,6 @@ config LIBUNWIND_AVAILABLE "$libunwind_available"
config LIBUNWIND_INCLUDE_FLAGS "$libunwind_include"
config LIBUNWIND_LINK_FLAGS "$libunwind_lib"
config PROFINFO_WIDTH "$profinfo_width"
config WITH_CPLUGINS "$with_cplugins"
config WITH_FPIC "$with_fpic"
config TARGET "$target"
config HOST "$host"
Expand Down Expand Up @@ -2263,11 +2253,6 @@ else
*)
;;
esac
if $with_cplugins; then
inf " C plugins................. yes"
else
inf " C plugins................. no"
fi
if $with_fpic; then
inf " compile with -fPIC........ yes"
else
Expand Down
99 changes: 0 additions & 99 deletions runtime/caml/misc.h
Expand Up @@ -244,105 +244,6 @@ extern int caml_umul_overflow(uintnat a, uintnat b, uintnat * res);
#endif /* _WIN32 */


/* 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_os(filename,flags,perm)
#define CAML_SYS_CLOSE(fd) close(fd)
#define CAML_SYS_STAT(filename,st) stat_os(filename,st)
#define CAML_SYS_UNLINK(filename) unlink_os(filename)
#define CAML_SYS_RENAME(old_name,new_name) rename_os(old_name, new_name)
#define CAML_SYS_CHDIR(dirname) chdir_os(dirname)
#define CAML_SYS_GETENV(varname) getenv(varname)
#define CAML_SYS_SYSTEM(command) system_os(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_os*)caml_cplugins_prim(code,(intnat) (arg1),0,0)
#define CAML_SYS_VOID_PRIM_1(code,prim,arg1) \
(caml_cplugins_prim == NULL) ? prim(arg1) : \
(void)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_VOID_PRIM_1(CAML_CPLUGINS_EXIT,exit,retcode)
#define CAML_SYS_OPEN(filename,flags,perm) \
CAML_SYS_PRIM_3(CAML_CPLUGINS_OPEN,open_os,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_os,filename,st)
#define CAML_SYS_UNLINK(filename) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_UNLINK,unlink_os,filename)
#define CAML_SYS_RENAME(old_name,new_name) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_RENAME,rename_os,old_name,new_name)
#define CAML_SYS_CHDIR(dirname) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_CHDIR,chdir_os,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_os,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_os *exe_name;
char_os** argv;
char_os *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_os * exe_name, char_os **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 */

struct ext_table {
Expand Down
5 changes: 0 additions & 5 deletions runtime/caml/sys.h
Expand Up @@ -37,14 +37,9 @@ 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);
Expand Down
4 changes: 2 additions & 2 deletions runtime/io.c
Expand Up @@ -118,7 +118,7 @@ static void unlink_channel(struct channel *channel)

CAMLexport void caml_close_channel(struct channel *channel)
{
CAML_SYS_CLOSE(channel->fd);
close(channel->fd);
if (channel->refcount > 0) return;
if (caml_channel_mutex_free != NULL) (*caml_channel_mutex_free)(channel);
unlink_channel(channel);
Expand Down Expand Up @@ -545,7 +545,7 @@ CAMLprim value caml_ml_close_channel(value vchannel)

if (do_syscall) {
caml_enter_blocking_section();
result = CAML_SYS_CLOSE(fd);
result = close(fd);
caml_leave_blocking_section();
}

Expand Down
3 changes: 1 addition & 2 deletions runtime/printexc.c
Expand Up @@ -149,7 +149,6 @@ void caml_fatal_uncaught_exception(value exn)
if (caml_abort_on_uncaught_exn) {
abort();
} else {
CAML_SYS_EXIT(2);
exit(2); /* Second exit needed for the Noreturn flag */
exit(2);
}
}

0 comments on commit 7e79186

Please sign in to comment.