diff -r b3977fb10b6e -r 9a79d846ae21 erts/emulator/beam/atom.names
--- a/erts/emulator/beam/atom.names
+++ b/erts/emulator/beam/atom.names
@@ -355,6 +355,7 @@ atom pid
 atom pid
 atom port
 atom port_count
+atom preload
 atom print
 atom priority
 atom private
diff -r b3977fb10b6e -r 9a79d846ae21 erts/emulator/beam/erl_bif_ddll.c
--- a/erts/emulator/beam/erl_bif_ddll.c
+++ b/erts/emulator/beam/erl_bif_ddll.c
@@ -44,6 +44,7 @@
 #include "big.h"
 #include "dist.h"
 #include "erl_version.h"
+#include "erl_bif_ffi.h"
 
 #ifdef ERTS_SMP
 #define DDLL_SMP 1
@@ -74,7 +75,8 @@ static void set_driver_reloading(DE_Hand
 static void set_driver_reloading(DE_Handle *dh, Process *proc, char *path, char *name, Uint flags);
 static int load_driver_entry(DE_Handle **dhp, char *path, char *name,
 			     int need_driver_init);
-static int do_unload_driver_entry(DE_Handle *dh, Eterm *save_name);
+static int do_unload_driver_entry(DE_Handle *dh, Eterm *save_name,
+				  int keep_preloads);
 static int do_load_driver_entry(DE_Handle *dh, char *path, char *name,
 				int need_driver_init);
 #if 0
@@ -101,6 +103,11 @@ static void dereference_all_processes(DE
 static void dereference_all_processes(DE_Handle *dh);
 static void restore_process_references(DE_Handle *dh);
 static void ddll_no_more_references(void *vdh);
+#ifdef HAVE_LIBFFI
+static int build_ffi_preloads(Eterm lst, FFIPreload **preloads,
+			      DE_Handle *dh);
+static void refresh_ffi_preloads(DE_Handle *dh);
+#endif /* HAVE_LIBFFI */
 
 #define lock_drv_list() erts_smp_mtx_lock(&erts_driver_list_lock)
 #define unlock_drv_list() erts_smp_mtx_unlock(&erts_driver_list_lock)
@@ -163,6 +170,11 @@ BIF_RETTYPE erl_ddll_try_load_3(Process 
     int do_build_load_error = 0;
     int build_this_load_error = 0;
     int need_driver_init = 1;
+#ifdef HAVE_LIBFFI
+    FFIPreload *preloads = NULL;
+    int npreloads = 0; /* Number of FFI preloads */
+#endif /* HAVE_LIBFFI */
+    Eterm preloads_lst = am_false;
 
     for(l = options; is_list(l); l =  CDR(list_val(l))) {
 	Eterm opt = CAR(list_val(l));
@@ -217,6 +229,12 @@ BIF_RETTYPE erl_ddll_try_load_3(Process 
 	    } else {
 		goto error;
 	    }
+	    break;
+	case am_preload:
+	    if (is_not_list(tp[2]) && is_not_nil(tp[2])) {
+		goto error;
+	    }
+	    preloads_lst = tp[2];
 	    break;
 	default:
 	    goto error;
@@ -424,6 +442,31 @@ BIF_RETTYPE erl_ddll_try_load_3(Process 
 	hp = HAlloc(p,3);
 	t = TUPLE2(hp, am_ok, ok_term);
     }
+
+    if (preloads_lst != am_false) {
+	/* We are required to (re)build the FFI preload list.  Even if
+	 * we fail, the driver/library will remain loaded (but without
+	 * the preloaded symbols).  It will be possible to repeat the
+	 * preloading by (re)loading the driver/library again. */
+#ifdef HAVE_LIBFFI
+	if ((npreloads = build_ffi_preloads(preloads_lst, &preloads, dh)) <0) {
+	    do_build_load_error = 1;
+	    build_this_load_error = ERL_DE_FFI_PRELOADING_ERROR;
+	    goto soft_error;
+	} else {
+	    if (dh->preloads != NULL) {
+		/* We are rebuilding the preloads, free the old stuff */
+		erts_free(ERTS_ALC_T_DDLL_HANDLE, dh->preloads);
+	    }
+	    dh->npreloads = npreloads;
+	    dh->preloads = preloads;
+	}
+#else
+	do_build_load_error = 1;
+	build_this_load_error = ERL_DE_ERROR_NO_FFI_FUNCTIONALITY;
+	goto soft_error;
+#endif /* HAVE_LIBFFI */
+    }
 #if DDLL_SMP
     unlock_drv_list();
 #endif
@@ -1218,7 +1262,9 @@ static void ddll_no_more_references(void
 	DE_ProcEntry **p = &(dh->procs);
 	Eterm save_driver_name;
 	ASSERT(dh->status != ERL_DE_OK);
-	do_unload_driver_entry(dh,&save_driver_name);
+	do_unload_driver_entry(dh, &save_driver_name,
+			       dh->status == ERL_DE_RELOAD
+			       || dh->status == ERL_DE_FORCE_RELOAD);
 	while (*p != NULL) {
 	    DE_ProcEntry *q;
 	    if ((*p)->awaiting_status == ERL_DE_PROC_AWAIT_UNLOAD ||
@@ -1298,6 +1344,10 @@ char *erts_ddll_error(int code) {
 	return "Unspecified dynamic library error";
     case ERL_DE_LOOKUP_ERROR_NOT_FOUND:
 	return "Symbol not found in dynamic library";
+    case ERL_DE_FFI_PRELOADING_ERROR:
+	return "Could not preload symbols and/or compile FFI structures";
+    case ERL_DE_ERROR_NO_FFI_FUNCTIONALITY:
+	return "FFI functionality not available on this platform";
     default:
 	return erts_sys_ddll_error(code);
     }
@@ -1648,6 +1698,13 @@ static int do_load_driver_entry(DE_Handl
     dh->flags = 0;
     dh->status = ERL_DE_OK;
     dh->need_driver_init = need_driver_init;
+
+#ifdef HAVE_LIBFFI
+    /* FFI preloads will be set elsewhere */
+    dh->npreloads = 0;
+    dh->preloads = NULL;
+#endif /* HAVE_LIBFFI */
+
     dp->handle = dh;
 
     erts_add_driver_entry(dp,1); /* io.c */
@@ -1655,7 +1712,8 @@ static int do_load_driver_entry(DE_Handl
     return ERL_DE_NO_ERROR;
 }
 
-static int do_unload_driver_entry(DE_Handle *dh, Eterm *save_name)
+static int do_unload_driver_entry(DE_Handle *dh, Eterm *save_name,
+				  int keep_preloads)
 {
     DE_List *p = driver_list;
     DE_List *q;
@@ -1695,6 +1753,14 @@ static int do_unload_driver_entry(DE_Han
 		erts_free(ERTS_ALC_T_DRV, q->drv->driver_name);
 		erts_free(ERTS_ALC_T_DRV, q->drv);
 	    }
+
+#ifdef HAVE_LIBFFI
+	    if (dh->preloads != NULL) {
+		if (!keep_preloads)
+		    erts_free(ERTS_ALC_T_DDLL_HANDLE, dh->preloads);
+	    }
+#endif /* HAVE_LIBFFI */
+
 	    erts_free(ERTS_ALC_T_DRV_ENTRY_LIST, (void *) q);
 	    return 1;
 	}
@@ -1734,7 +1800,7 @@ static int load_driver_entry(DE_Handle *
 #if 0
 static void unload_driver_entry(DE_Handle *dh)
 {
-    do_unload_driver_entry(dh, NULL);
+    do_unload_driver_entry(dh, NULL, 0);
     if (dh->full_path != NULL) {
 	erts_free(ERTS_ALC_T_DDLL_HANDLE, (void *) dh->full_path);
     }
@@ -1747,6 +1813,10 @@ static int reload_driver_entry(DE_Handle
     char *name = dh->reload_driver_name;
     int loadres;
     Uint flags = dh->reload_flags;
+#ifdef HAVE_LIBFFI
+    Uint npreloads = dh->npreloads;
+    FFIPreload *preloads = dh->preloads;
+#endif /* HAVE_LIBFFI */
 
     assert_drv_list_locked();
 
@@ -1764,6 +1834,15 @@ static int reload_driver_entry(DE_Handle
     if (loadres == ERL_DE_NO_ERROR) {
 	dh->status = ERL_DE_OK;
 	dh->flags = flags;
+
+#ifdef HAVE_LIBFFI
+	if (preloads != NULL) {
+	    dh->npreloads = npreloads;
+	    dh->preloads = preloads;
+	    /* FFI symbols may have changed address, let's refresh them */
+	    refresh_ffi_preloads(dh);
+	}
+#endif /* HAVE_LIBFFI */
     }
     restore_process_references(dh);
     return loadres;
@@ -1849,6 +1928,7 @@ static ErrcodeEntry errcode_tab[] = {
     {"no_ddll_available",  ERL_DE_ERROR_NO_DDLL_FUNCTIONALITY},
     {"unspecified_error", ERL_DE_ERROR_UNSPECIFIED},
     {"symbol_not_found", ERL_DE_LOOKUP_ERROR_NOT_FOUND},
+    {"ffi_preloading_error", ERL_DE_FFI_PRELOADING_ERROR},
     {NULL,0}
 };
 
@@ -2007,4 +2087,135 @@ static DE_List *lookup_driver(char *name
 	;
     return de;
 }
-    
+
+#ifdef HAVE_LIBFFI
+/*
+ * Build an array of preloaded and precompiled FFI call structures, to
+ * be written on **preloads.  Return the number of preloads, or a
+ * negative number (an FFI error status) on error.
+ */
+static int build_ffi_preloads(Eterm lst, FFIPreload **ret_preloads,
+			      DE_Handle *dh)
+{
+    Uint npreloads = 0, total_ftypes = 0, total_strlen = 0;
+    Uint i, nargs;
+    int status = 0;
+    FFIPreload *preloads = NULL;
+    Eterm l, tp, argstp, *tpval, *argstpval;
+    char *funcname = NULL, *fnames;
+    ffi_type **ftypes;
+    void *fptr;
+
+    /* We want one single allocation for all the preload data, so we
+     * need to count how many preloads and ffi_type's we are going to
+     * handle */
+    for(l = lst; is_list(l); l = CDR(list_val(l))) {
+	npreloads++;
+
+	tp = CAR(list_val(l));
+	if (is_not_tuple(tp))
+	    goto error;
+	tpval = tuple_val(tp);
+	if (*tpval != make_arityval(2))
+	    goto error;
+	argstp = tpval[2];
+	if (is_not_tuple(argstp))
+	    goto error;
+	argstpval = tuple_val(argstp);
+	if (is_not_arity_value(argstpval[0]))
+	    goto error;
+	nargs = arityval(argstpval[0]);
+	if (nargs == 0) {
+	    /* We need at least the return type of the function */
+	    goto error;
+	}
+	total_ftypes += nargs;
+
+	/* We also put the function names at the end of the allocated
+	 * memory block */
+	if ((funcname = pick_list_or_atom(tpval[1])) == NULL)
+	    goto error;
+	total_strlen += strlen(funcname);
+	erts_free(ERTS_ALC_T_DDLL_TMP_BUF, funcname);
+	funcname = NULL;
+    }
+
+    if (npreloads == 0)
+	return 0;
+
+    /* FIXME: is this allocation type correct? */
+    preloads = erts_alloc(ERTS_ALC_T_DDLL_HANDLE,
+			  (npreloads * sizeof(FFIPreload))
+			  + (total_ftypes * sizeof(ffi_type*))
+			  + (total_strlen + npreloads /* For final \0's */));
+    ftypes = (ffi_type**)(preloads + npreloads);
+    fnames = (char*)(ftypes + total_ftypes);
+
+    /* Let's actually build the FFI preloads */
+    for(l = lst, i = 0; is_list(l); l = CDR(list_val(l)), ++i, ftypes +=nargs){
+	/* We don't repeat the checks performed in the loop above */
+	tp = CAR(list_val(l));
+	tpval = tuple_val(tp);
+	argstp = tpval[2];
+	argstpval = tuple_val(argstp);
+	nargs = arityval(argstpval[0]);
+
+	if ((funcname = pick_list_or_atom(tpval[1])) == NULL)
+	    goto error;
+
+	if ((fptr = driver_dl_sym(dh->handle, funcname)) == NULL)
+	    goto error;
+	
+	preloads[i].name = strcpy(fnames, funcname);
+	fnames += strlen(funcname) + 1;
+
+	preloads[i].function = fptr;
+	preloads[i].nargs = nargs;
+
+	if ((status = erl_ffi_build_types_array(argstpval+1, ftypes,
+						preloads[i].nargs)))
+	    goto error;
+	preloads[i].ftypes = ftypes;
+
+        if (ffi_prep_cif(&preloads[i].cif, FFI_DEFAULT_ABI, nargs-1,
+                         ftypes[0], ftypes+1) != FFI_OK) {
+	    status = ERL_FFI_STATUS_FFI_ERROR;
+            goto error;
+	}
+
+	erts_free(ERTS_ALC_T_DDLL_TMP_BUF, funcname);
+	funcname = NULL;
+    }
+
+    *ret_preloads = preloads;
+    return npreloads;
+
+    error:
+    if (preloads != NULL)
+	erts_free(ERTS_ALC_T_DDLL_HANDLE, preloads);
+    if (funcname != NULL)
+	erts_free(ERTS_ALC_T_DDLL_TMP_BUF, funcname);
+    if (status == 0) {
+	/* Default error (if we are here, then something went wrong) */
+	return ERL_FFI_STATUS_BADARG;
+    }
+    return status;
+}
+
+/* Reload FFI symbols on the given FFIPreload structures, without
+ * touching the CIFs.  Missing function pointers will be set to NULL,
+ * and thus will not be callable anymore */
+static void refresh_ffi_preloads(DE_Handle *dh)
+{
+    FFIPreload *preloads = dh->preloads;
+    Uint npreloads = dh->npreloads;
+    Uint i;
+
+    if (dh->preloads == NULL)
+	return;
+
+    for (i = 0; i < npreloads; ++i) {
+	preloads[i].function = driver_dl_sym(dh->handle, preloads[i].name);
+    }
+}
+#endif /* HAVE_LIBFFI */
diff -r b3977fb10b6e -r 9a79d846ae21 erts/emulator/beam/global.h
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -18,6 +18,10 @@
 
 #ifndef __GLOBAL_H__
 #define __GLOBAL_H__
+
+#ifdef HAVE_CONFIG_H
+#  include "config.h"
+#endif
 
 #include "sys.h"
 #include "erl_alloc.h"
@@ -185,7 +189,21 @@ struct port {
 #define ERL_DE_ERROR_NO_DDLL_FUNCTIONALITY -6
 #define ERL_DE_ERROR_UNSPECIFIED -7
 #define ERL_DE_LOOKUP_ERROR_NOT_FOUND -8
-#define ERL_DE_DYNAMIC_ERROR_OFFSET -10
+#define ERL_DE_FFI_PRELOADING_ERROR -9
+#define ERL_DE_ERROR_NO_FFI_FUNCTIONALITY -10
+#define ERL_DE_DYNAMIC_ERROR_OFFSET -12
+
+#ifdef HAVE_LIBFFI
+#include <ffi.h>
+
+typedef struct {
+    char *name;        /* Function name */
+    void *function;    /* Function pointer */
+    ffi_cif cif;       /* FFI Call InterFace (CIF) */
+    Uint nargs;        /* Number of FFI call arguments */
+    ffi_type** ftypes; /* Pointer to the array of ffi_type*'s */
+} FFIPreload;
+#endif /* HAVE_LIBFFI */
 
 typedef struct de_proc_entry {
     Process *proc;                   /* The process... */
@@ -218,6 +236,10 @@ typedef struct {
 				       * initialization structure? */
     int          need_drventry_free;  /* Does the associated
 				       * ErlDrvEntry need to be freed? */
+#ifdef HAVE_LIBFFI
+    Uint         npreloads;           /* Number of preloaded FFI symbols */
+    FFIPreload   *preloads;           /* Array of preloaded FFI stuff */
+#endif /* HAVE_LIBFFI */
 } DE_Handle;
 
 /*
