diff -r 54b43754447d -r 25dc4ec2c60b erts/emulator/beam/erl_bif_ffi.c
--- a/erts/emulator/beam/erl_bif_ffi.c
+++ b/erts/emulator/beam/erl_bif_ffi.c
@@ -211,12 +211,17 @@ BIF_RETTYPE ffi_raw_call_3(BIF_ALIST_3)
     /* FIXME: is it possible that drv_ptr->handle is NULL? */
     handle = ((DE_Handle*) prt->drv_ptr->handle)->handle;
 
+    /* Release the port lock as soon as possible, keeping its refcount
+     * (since the port is still in use, even if indirectly: we just
+     * need its driver handle) */
+    erts_smp_port_unlock_noderef(prt);
+
     /* Extract function name from the first tuple element... */
     if ((fname = pick_list_or_atom(calltp[0])) == NULL)
-        goto error;
+        goto late_error;
     /* ...and finally get function pointer */
     if ((fptr = driver_dl_sym(handle, fname)) == NULL)
-        goto error;
+        goto late_error;
 
     {
 	Uint nargs_1 = nargs - 1;
@@ -260,13 +265,18 @@ BIF_RETTYPE ffi_raw_call_3(BIF_ALIST_3)
 	}
     }
 
-    erts_smp_port_unlock(prt);
+    /* "Fix" reference counting after the previous
+     * erts_smp_port_unlock_noderef() call */
+    erts_smp_port_deref(prt);
     BIF_RET(res);
 
     late_error:
     erts_free(ERTS_ALC_T_DDLL_TMP_BUF, (void *) fname);
-    erts_smp_port_unlock(prt);
+    /* "Fix" reference counting after the previous
+     * erts_smp_port_unlock_noderef() call */
+    erts_smp_port_deref(prt);
     switch (status) {
+    case 0:
     case ERL_FFI_STATUS_BADARG:
 	BIF_ERROR(BIF_P, BADARG);
     case ERL_FFI_STATUS_BUG:
@@ -326,23 +336,29 @@ BIF_RETTYPE ffi_raw_call_2(BIF_ALIST_2)
     if (!prt->drv_ptr)
         goto error; /* The port is not associated to a driver */    
     de_handle = (DE_Handle*) prt->drv_ptr->handle;
+
+    /* Release the port lock as soon as possible, keeping its refcount
+     * (since it's still in use, even if indirectly - we just need its
+     * driver handle) */
+    erts_smp_port_unlock_noderef(prt);
+
     npreloads = de_handle->npreloads;
 
     /* Is the given function index within bounds? */
     if ((func_idx > npreloads) || (func_idx == 0))
-	goto error;
+	goto late_error;
 
     preload = de_handle->preloads + (func_idx - 1);
 
     /* The selected function may have been disabled, e.g. if the
      * library was reloaded and the symbol disappeared */
     if (preload->function == NULL)
-	goto error;
+	goto late_error;
 
     /* Is the function call arity compatible with the precompiled FFI
      * signature? */
     if (nargs != preload->nargs)
-	goto error;
+	goto late_error;
 
     {
 	Uint nargs_1 = nargs - 1;
@@ -378,26 +394,26 @@ BIF_RETTYPE ffi_raw_call_2(BIF_ALIST_2)
 	}
     }
 
-    erts_smp_port_unlock(prt);
+    /* "Fix" reference counting after the previous
+     * erts_smp_port_unlock_noderef() call */
+    erts_smp_port_deref(prt);
     BIF_RET(res);
 
     late_error:
-    erts_smp_port_unlock(prt);
-    if (status) {
-        switch (status) {
-        case ERL_FFI_STATUS_BADARG:
-            BIF_ERROR(BIF_P, BADARG);
-        case ERL_FFI_STATUS_BUG:
-        case ERL_FFI_STATUS_FFI_ERROR:
-            BIF_ERROR(BIF_P, EXC_INTERNAL_ERROR);
-        case ERL_FFI_STATUS_TOO_MANY_ARGS:
-            BIF_ERROR(BIF_P, EXC_SYSTEM_LIMIT);
-        default:
-            /* It should never happen */
-            BIF_ERROR(BIF_P, EXC_INTERNAL_ERROR);
-        }
-    } else {
-	/* This should never happen, but we shut up compiler warnings */
+    /* "Fix" reference counting after the previous
+     * erts_smp_port_unlock_noderef() call */
+    erts_smp_port_deref(prt);
+    switch (status) {
+    case 0:
+    case ERL_FFI_STATUS_BADARG:
+	BIF_ERROR(BIF_P, BADARG);
+    case ERL_FFI_STATUS_BUG:
+    case ERL_FFI_STATUS_FFI_ERROR:
+	BIF_ERROR(BIF_P, EXC_INTERNAL_ERROR);
+    case ERL_FFI_STATUS_TOO_MANY_ARGS:
+	BIF_ERROR(BIF_P, EXC_SYSTEM_LIMIT);
+    default:
+	/* It should never happen */
 	BIF_ERROR(BIF_P, EXC_INTERNAL_ERROR);
     }
 }
diff -r 54b43754447d -r 25dc4ec2c60b erts/emulator/beam/global.h
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -930,6 +930,10 @@ ERTS_GLB_INLINE void erts_smp_port_lock(
 ERTS_GLB_INLINE void erts_smp_port_lock(Port *prt);
 ERTS_GLB_INLINE void erts_smp_port_unlock(Port *prt);
 
+/* Functions for two-phase unlock/deref, used by FFI */
+ERTS_GLB_INLINE void erts_smp_port_unlock_noderef(Port *prt);
+ERTS_GLB_INLINE void erts_smp_port_deref(Port *prt);
+
 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
 
 ERTS_GLB_INLINE void
@@ -978,6 +982,36 @@ erts_smp_port_unlock(Port *prt)
 {
 #ifdef ERTS_SMP
     long refc;
+    refc = erts_smp_atomic_dectest(&prt->refc);
+    ASSERT(refc >= 0);
+    if (refc == 0)
+	erts_port_cleanup(prt);
+    else
+	erts_smp_mtx_unlock(prt->lock);
+#endif
+}
+
+/* Unlock a port without decrementing its refcount.  When this
+ * function is used, it MUST be followed by a erts_smp_port_deref() call */
+ERTS_GLB_INLINE void
+erts_smp_port_unlock_noderef(Port *prt)
+{
+#ifdef ERTS_SMP
+    ASSERT(erts_smp_atomic_read(&prt->refc) > 0);
+    erts_smp_mtx_unlock(prt->lock);
+#endif
+}
+
+/* Decrement the reference counting of a port.  This function MUST be
+ * called if and only if erts_smp_port_unlock_noderef() is used */
+ERTS_GLB_INLINE void
+erts_smp_port_deref(Port *prt)
+{
+#ifdef ERTS_SMP
+    long refc;
+
+    erts_smp_mtx_lock(prt->lock);
+
     refc = erts_smp_atomic_dectest(&prt->refc);
     ASSERT(refc >= 0);
     if (refc == 0)
