File 6842-ei-Add-enable-ei-dynamic-lib.patch of Package erlang

From 96e8bea9c7f4e6071ae16588a6b2d3bbebff67f8 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Mon, 29 Nov 2021 16:51:08 +0100
Subject: [PATCH 2/2] ei: Add --enable-ei-dynamic-lib

This configure option makes it so that a shared library is
build as well as the archive to be included in ei.
---
 HOWTO/INSTALL.md                           |   2 +
 erts/aclocal.m4                            |  15 +-
 lib/erl_interface/configure                | 547 +++++++++++++++++++++
 lib/erl_interface/configure.in             |  11 +
 lib/erl_interface/src/Makefile.in          | 104 ++--
 lib/erl_interface/src/connect/ei_connect.c |   2 +-
 lib/erl_interface/src/connect/ei_resolve.c |  28 +-
 lib/erl_interface/src/misc/ei_locking.h    |   2 +-
 lib/erl_interface/src/prog/erl_call.c      |   5 -
 9 files changed, 642 insertions(+), 74 deletions(-)

diff --git a/HOWTO/INSTALL.md b/HOWTO/INSTALL.md
index 3a041f7e6c..e7fb4ad27a 100644
--- a/HOWTO/INSTALL.md
+++ b/HOWTO/INSTALL.md
@@ -422,6 +422,8 @@ Some of the available `configure` options are:
     and scalability compared to the default clock sources chosen.
 *   `--disable-saved-compile-time` - Disable saving of compile date and time
     in the emulator binary.
+*   `--enable-ei-dynamic-lib` - Make erl\_interface build a shared library in addition
+    to the archive normally built.
 
 If you or your system has special requirements please read the `Makefile` for
 additional configuration information.
diff --git a/erts/aclocal.m4 b/erts/aclocal.m4
index 4720a422c8..6f3238b3d2 100644
--- a/erts/aclocal.m4
+++ b/erts/aclocal.m4
@@ -3062,9 +3062,18 @@ case $host_os in
 		DED_LDFLAGS="-Bshareable"
 	;;
 	darwin*)
-		# Mach-O linker: a shared lib and a loadable
-		# object file is not the same thing.
-		DED_LDFLAGS="-bundle -bundle_loader ${ERL_TOP}/bin/$host/beam.smp"
+		# Mach-O linker: a shared lib and a loadable object file is not the same thing.
+
+                if test "X${ERL_DED_FLAT_BUNDLE}" = "Xtrue"; then
+                  # EI sets this variable when building its .so file as beam.smp
+                  # has not been built yet and any ei lib will not
+                  # link to beam.smp anyways
+		  DED_LDFLAGS="-bundle -flat_namespace -undefined suppress"
+                else
+                  # Cannot use flat namespaces for drivers/nifs as that may cause
+                  # symbols to collide during loading
+		  DED_LDFLAGS="-bundle -bundle_loader ${ERL_TOP}/bin/$host/beam.smp"
+                fi
 		if test X${enable_m64_build} = Xyes; then
 		  DED_LDFLAGS="-m64 $DED_LDFLAGS"
 		else
diff --git a/lib/erl_interface/configure b/lib/erl_interface/configure
index bc5aa490d7..fa5feb72f3 100755
--- a/lib/erl_interface/configure
+++ b/lib/erl_interface/configure
@@ -619,6 +619,21 @@ ac_includes_default="\
 #endif"
 
 ac_subst_vars='LTLIBOBJS
+DED_OSTYPE
+DED_LIBS
+DED_LD_FLAG_RUNTIME_LIBRARY_PATH
+DED_LDFLAGS
+DED_WERRORFLAGS
+DED_WARN_FLAGS
+DED_STATIC_CFLAGS
+DED_CFLAGS
+DED_BASIC_CFLAGS
+DED_INCLUDE
+DED_SYS_INCLUDE
+DED_EXT
+DED_GCC
+DED_CC
+DED_LD
 LIB_CFLAGS
 WFLAGS
 GETCONF
@@ -647,6 +662,7 @@ CPPFLAGS
 LDFLAGS
 CFLAGS
 CC
+DYNAMIC_LIB
 TARGET
 host_os
 host_vendor
@@ -700,6 +716,7 @@ ac_user_opts='
 enable_option_checking
 enable_threads
 enable_mask_real_errno
+enable_ei_dynamic_lib
 with_gmp
 enable_sanitizers
 '
@@ -1336,6 +1353,7 @@ Optional Features:
   --enable-FEATURE[=ARG]  include FEATURE [ARG=yes]
   --disable-threads       use to only build single threaded libs
   --disable-mask-real-errno do not mask real 'errno'
+  --enable-ei-dynamic-lib  build ei as a dynamic library
   --enable-sanitizers[=comma-separated list of sanitizers]
                           Default=address,undefined
 
@@ -2529,6 +2547,17 @@ else
 fi
 
 
+# Check whether --enable-ei-dynamic-lib was given.
+if test "${enable_ei_dynamic_lib+set}" = set; then :
+  enableval=$enable_ei_dynamic_lib;  case "$enableval" in
+    yes) DYNAMIC_LIB=yes ;;
+    *)   DYNAMIC_LIB=no ;;
+  esac
+else
+   DYNAMIC_LIB=no
+fi
+
+
 
 
 ac_ext=c
@@ -7967,6 +7996,524 @@ else
 fi
 
 
+
+USER_LD=$LD
+USER_LDFLAGS="$LDFLAGS"
+
+DED_CC=$CC
+DED_GCC=$GCC
+
+DED_CFLAGS=
+DED_OSTYPE=unix
+case $host_os in
+     linux*)
+	DED_CFLAGS="-D_GNU_SOURCE" ;;
+     win32)
+	DED_CFLAGS="-D_WIN32_WINNT=0x0600 -DWINVER=0x0600"
+        DED_OSTYPE=win32 ;;
+     *)
+        ;;
+esac
+
+DED_WARN_FLAGS="-Wall -Wstrict-prototypes"
+case "$host_cpu" in
+  tile*)
+    # tile-gcc is a bit stricter with -Wmissing-prototypes than other gccs,
+    # and too strict for our taste.
+    ;;
+  *)
+    DED_WARN_FLAGS="$DED_WARN_FLAGS -Wmissing-prototypes";;
+esac
+
+
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can add -Wdeclaration-after-statement to DED_WARN_FLAGS (via CFLAGS)" >&5
+$as_echo_n "checking if we can add -Wdeclaration-after-statement to DED_WARN_FLAGS (via CFLAGS)... " >&6; }
+    saved_CFLAGS=$CFLAGS;
+    CFLAGS="-Wdeclaration-after-statement $DED_WARN_FLAGS";
+    cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+int
+main ()
+{
+return 0;
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_compile "$LINENO"; then :
+  can_enable_flag=true
+else
+  can_enable_flag=false
+fi
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
+    CFLAGS=$saved_CFLAGS;
+    if test "X$can_enable_flag" = "Xtrue"; then
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5
+$as_echo "yes" >&6; }
+        DED_WARN_FLAGS="-Wdeclaration-after-statement $DED_WARN_FLAGS"
+    else
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+    fi
+
+
+
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can add -Werror=return-type to DED_WERRORFLAGS (via CFLAGS)" >&5
+$as_echo_n "checking if we can add -Werror=return-type to DED_WERRORFLAGS (via CFLAGS)... " >&6; }
+    saved_CFLAGS=$CFLAGS;
+    CFLAGS="-Werror=return-type $DED_WERRORFLAGS";
+    cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+int
+main ()
+{
+return 0;
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_compile "$LINENO"; then :
+  can_enable_flag=true
+else
+  can_enable_flag=false
+fi
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
+    CFLAGS=$saved_CFLAGS;
+    if test "X$can_enable_flag" = "Xtrue"; then
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5
+$as_echo "yes" >&6; }
+        DED_WERRORFLAGS="-Werror=return-type $DED_WERRORFLAGS"
+    else
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+    fi
+
+
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can add -Werror=implicit to DED_WERRORFLAGS (via CFLAGS)" >&5
+$as_echo_n "checking if we can add -Werror=implicit to DED_WERRORFLAGS (via CFLAGS)... " >&6; }
+    saved_CFLAGS=$CFLAGS;
+    CFLAGS="-Werror=implicit $DED_WERRORFLAGS";
+    cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+int
+main ()
+{
+return 0;
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_compile "$LINENO"; then :
+  can_enable_flag=true
+else
+  can_enable_flag=false
+fi
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
+    CFLAGS=$saved_CFLAGS;
+    if test "X$can_enable_flag" = "Xtrue"; then
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5
+$as_echo "yes" >&6; }
+        DED_WERRORFLAGS="-Werror=implicit $DED_WERRORFLAGS"
+    else
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+    fi
+
+
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can add -Werror=undef to DED_WERRORFLAGS (via CFLAGS)" >&5
+$as_echo_n "checking if we can add -Werror=undef to DED_WERRORFLAGS (via CFLAGS)... " >&6; }
+    saved_CFLAGS=$CFLAGS;
+    CFLAGS="-Werror=undef $DED_WERRORFLAGS";
+    cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+int
+main ()
+{
+return 0;
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_compile "$LINENO"; then :
+  can_enable_flag=true
+else
+  can_enable_flag=false
+fi
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
+    CFLAGS=$saved_CFLAGS;
+    if test "X$can_enable_flag" = "Xtrue"; then
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5
+$as_echo "yes" >&6; }
+        DED_WERRORFLAGS="-Werror=undef $DED_WERRORFLAGS"
+    else
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+    fi
+
+
+DED_SYS_INCLUDE="-I${ERL_TOP}/erts/emulator/beam -I${ERL_TOP}/erts/include -I${ERL_TOP}/erts/include/$host -I${ERL_TOP}/erts/include/internal -I${ERL_TOP}/erts/include/internal/$host -I${ERL_TOP}/erts/emulator/sys/$DED_OSTYPE -I${ERL_TOP}/erts/emulator/sys/common"
+DED_INCLUDE=$DED_SYS_INCLUDE
+
+DED_CFLAGS="$CFLAGS $CPPFLAGS $DED_CFLAGS"
+if test "x$GCC" = xyes; then
+    # Use -fno-common for gcc, that is link error if multiple definitions of
+    # global variables are encountered. This is ISO C compliant.
+    # Until version 10, gcc has had -fcommon as default, which allows and merges
+    # such dubious duplicates.
+
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can add -fno-common to DED_CFLAGS (via CFLAGS)" >&5
+$as_echo_n "checking if we can add -fno-common to DED_CFLAGS (via CFLAGS)... " >&6; }
+    saved_CFLAGS=$CFLAGS;
+    CFLAGS="-fno-common $DED_CFLAGS";
+    cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+int
+main ()
+{
+return 0;
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_compile "$LINENO"; then :
+  can_enable_flag=true
+else
+  can_enable_flag=false
+fi
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
+    CFLAGS=$saved_CFLAGS;
+    if test "X$can_enable_flag" = "Xtrue"; then
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5
+$as_echo "yes" >&6; }
+        DED_CFLAGS="-fno-common $DED_CFLAGS"
+    else
+        { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+    fi
+
+
+    DED_STATIC_CFLAGS="$DED_CFLAGS"
+    DED_CFLAGS="$DED_CFLAGS -fPIC"
+    # Remove -fPIE and -fno-PIE
+    DED_CFLAGS=`echo $DED_CFLAGS | sed 's/-f\(no-\)\?PIE//g'`
+fi
+
+DED_EXT=so
+case $host_os in
+    win32) DED_EXT=dll;;
+    darwin*)
+	DED_CFLAGS="$DED_CFLAGS -fno-common"
+	DED_STATIC_CFLAGS="$DED_STATIC_CFLAGS -fno-common";;
+    *)
+	;;
+esac
+
+DED_STATIC_CFLAGS="$DED_STATIC_CFLAGS -DSTATIC_ERLANG_NIF -DSTATIC_ERLANG_DRIVER"
+
+if test "$CFLAG_RUNTIME_LIBRARY_PATH" = ""; then
+
+  CFLAG_RUNTIME_LIBRARY_PATH="-Wl,-R"
+  case $host_os in
+    darwin*)
+	CFLAG_RUNTIME_LIBRARY_PATH=
+	;;
+    win32)
+	CFLAG_RUNTIME_LIBRARY_PATH=
+	;;
+    osf*)
+	CFLAG_RUNTIME_LIBRARY_PATH="-Wl,-rpath,"
+	;;
+    *)
+	;;
+  esac
+
+fi
+
+# If DED_LD is set in environment, we expect all DED_LD* variables
+# to be specified (cross compiling)
+if test "x$DED_LD" = "x"; then
+
+DED_LDFLAGS_CONFTEST=
+
+DED_LD_FLAG_RUNTIME_LIBRARY_PATH="-R"
+case $host_os in
+	win32)
+		DED_LD="ld.sh"
+		DED_LDFLAGS="-dll"
+		DED_LD_FLAG_RUNTIME_LIBRARY_PATH=
+	;;
+	solaris2*|sysv4*)
+		DED_LDFLAGS="-G"
+		if test X${enable_m64_build} = Xyes; then
+			DED_LDFLAGS="-64 $DED_LDFLAGS"
+		fi
+	;;
+	aix*|os400*)
+		DED_LDFLAGS="-G -bnoentry -bexpall"
+	;;
+	freebsd2*)
+		# Non-ELF GNU linker
+		DED_LDFLAGS="-Bshareable"
+	;;
+	darwin*)
+		# Mach-O linker: a shared lib and a loadable
+		# object file is not the same thing.
+		DED_LDFLAGS="-bundle -bundle_loader ${ERL_TOP}/bin/$host/beam.smp"
+		# DED_LDFLAGS_CONFTEST is for use in configure tests only. We
+		# cannot use DED_LDFLAGS in configure tests since beam.smp has not
+		# been built yet...
+		DED_LDFLAGS_CONFTEST="-bundle"
+		if test X${enable_m64_build} = Xyes; then
+		  DED_LDFLAGS="-m64 $DED_LDFLAGS"
+		else
+		  if test X${enable_m32_build} = Xyes; then
+		    DED_LDFLAGS="-m32 $DED_LDFLAGS"
+		  else
+		    # The cast to long int works around a bug in the HP C Compiler
+# version HP92453-01 B.11.11.23709.GP, which incorrectly rejects
+# declarations like `int a3[[(sizeof (unsigned char)) >= 0]];'.
+# This bug is HP SR number 8606223364.
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking size of void *" >&5
+$as_echo_n "checking size of void *... " >&6; }
+if ${ac_cv_sizeof_void_p+:} false; then :
+  $as_echo_n "(cached) " >&6
+else
+  if ac_fn_c_compute_int "$LINENO" "(long int) (sizeof (void *))" "ac_cv_sizeof_void_p"        "$ac_includes_default"; then :
+
+else
+  if test "$ac_cv_type_void_p" = yes; then
+     { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5
+$as_echo "$as_me: error: in \`$ac_pwd':" >&2;}
+as_fn_error 77 "cannot compute sizeof (void *)
+See \`config.log' for more details" "$LINENO" 5; }
+   else
+     ac_cv_sizeof_void_p=0
+   fi
+fi
+
+fi
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_sizeof_void_p" >&5
+$as_echo "$ac_cv_sizeof_void_p" >&6; }
+
+
+
+cat >>confdefs.h <<_ACEOF
+#define SIZEOF_VOID_P $ac_cv_sizeof_void_p
+_ACEOF
+
+
+		    case "$ac_cv_sizeof_void_p" in
+		      8)
+			DED_LDFLAGS="-m64 $DED_LDFLAGS";;
+		      *)
+		        ;;
+		    esac
+		  fi
+		fi
+		DED_LD="$CC"
+		DED_LD_FLAG_RUNTIME_LIBRARY_PATH="$CFLAG_RUNTIME_LIBRARY_PATH"
+	;;
+	linux*)
+		DED_LD="$CC"
+		DED_LD_FLAG_RUNTIME_LIBRARY_PATH="$CFLAG_RUNTIME_LIBRARY_PATH"
+		DED_LDFLAGS="-shared -Wl,-Bsymbolic"
+		if test X${enable_m64_build} = Xyes; then
+			DED_LDFLAGS="-m64 $DED_LDFLAGS"
+		fi;
+		if test X${enable_m32_build} = Xyes; then
+			DED_LDFLAGS="-m32 $DED_LDFLAGS"
+		fi
+	;;
+	freebsd*)
+		DED_LD="$CC"
+		DED_LD_FLAG_RUNTIME_LIBRARY_PATH="$CFLAG_RUNTIME_LIBRARY_PATH"
+		DED_LDFLAGS="-shared"
+		if test X${enable_m64_build} = Xyes; then
+			DED_LDFLAGS="-m64 $DED_LDFLAGS"
+		fi;
+		if test X${enable_m32_build} = Xyes; then
+			DED_LDFLAGS="-m32 $DED_LDFLAGS"
+		fi
+	;;
+	openbsd*)
+		DED_LD="$CC"
+		DED_LD_FLAG_RUNTIME_LIBRARY_PATH="$CFLAG_RUNTIME_LIBRARY_PATH"
+		DED_LDFLAGS="-shared"
+	;;
+	osf*)
+		# NOTE! Whitespace after -rpath is important.
+		DED_LD_FLAG_RUNTIME_LIBRARY_PATH="-rpath "
+		DED_LDFLAGS="-shared -expect_unresolved '*'"
+	;;
+	*)
+		# assume GNU linker and ELF
+		DED_LDFLAGS="-shared"
+		# GNU linker has no option for 64bit build, should not propagate -m64
+	;;
+esac
+
+if test "$DED_LD" = "" && test "$USER_LD" != ""; then
+    DED_LD="$USER_LD"
+    DED_LDFLAGS="$USER_LDFLAGS $DED_LDFLAGS"
+fi
+
+DED_LIBS=$LIBS
+
+fi # "x$DED_LD" = "x"
+
+test "$DED_LDFLAGS_CONFTEST" != "" || DED_LDFLAGS_CONFTEST="$DED_LDFLAGS"
+
+if test -n "$ac_tool_prefix"; then
+  # Extract the first word of "${ac_tool_prefix}ld", so it can be a program name with args.
+set dummy ${ac_tool_prefix}ld; ac_word=$2
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5
+$as_echo_n "checking for $ac_word... " >&6; }
+if ${ac_cv_prog_DED_LD+:} false; then :
+  $as_echo_n "(cached) " >&6
+else
+  if test -n "$DED_LD"; then
+  ac_cv_prog_DED_LD="$DED_LD" # Let the user override the test.
+else
+as_save_IFS=$IFS; IFS=$PATH_SEPARATOR
+for as_dir in $PATH
+do
+  IFS=$as_save_IFS
+  test -z "$as_dir" && as_dir=.
+    for ac_exec_ext in '' $ac_executable_extensions; do
+  if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then
+    ac_cv_prog_DED_LD="${ac_tool_prefix}ld"
+    $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5
+    break 2
+  fi
+done
+  done
+IFS=$as_save_IFS
+
+fi
+fi
+DED_LD=$ac_cv_prog_DED_LD
+if test -n "$DED_LD"; then
+  { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_LD" >&5
+$as_echo "$DED_LD" >&6; }
+else
+  { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+fi
+
+
+fi
+if test -z "$ac_cv_prog_DED_LD"; then
+  ac_ct_DED_LD=$DED_LD
+  # Extract the first word of "ld", so it can be a program name with args.
+set dummy ld; ac_word=$2
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5
+$as_echo_n "checking for $ac_word... " >&6; }
+if ${ac_cv_prog_ac_ct_DED_LD+:} false; then :
+  $as_echo_n "(cached) " >&6
+else
+  if test -n "$ac_ct_DED_LD"; then
+  ac_cv_prog_ac_ct_DED_LD="$ac_ct_DED_LD" # Let the user override the test.
+else
+as_save_IFS=$IFS; IFS=$PATH_SEPARATOR
+for as_dir in $PATH
+do
+  IFS=$as_save_IFS
+  test -z "$as_dir" && as_dir=.
+    for ac_exec_ext in '' $ac_executable_extensions; do
+  if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then
+    ac_cv_prog_ac_ct_DED_LD="ld"
+    $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5
+    break 2
+  fi
+done
+  done
+IFS=$as_save_IFS
+
+fi
+fi
+ac_ct_DED_LD=$ac_cv_prog_ac_ct_DED_LD
+if test -n "$ac_ct_DED_LD"; then
+  { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DED_LD" >&5
+$as_echo "$ac_ct_DED_LD" >&6; }
+else
+  { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5
+$as_echo "no" >&6; }
+fi
+
+  if test "x$ac_ct_DED_LD" = x; then
+    DED_LD="false"
+  else
+    case $cross_compiling:$ac_tool_warned in
+yes:)
+{ $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5
+$as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;}
+ac_tool_warned=yes ;;
+esac
+    DED_LD=$ac_ct_DED_LD
+  fi
+else
+  DED_LD="$ac_cv_prog_DED_LD"
+fi
+
+test "$DED_LD" != "false" || as_fn_error $? "No linker found" "$LINENO" 5
+
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for static compiler flags" >&5
+$as_echo_n "checking for static compiler flags... " >&6; }
+DED_STATIC_CFLAGS="$DED_WERRORFLAGS $DED_WFLAGS $DED_THR_DEFS $DED_STATIC_CFLAGS"
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_STATIC_CFLAGS" >&5
+$as_echo "$DED_STATIC_CFLAGS" >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for basic compiler flags for loadable drivers" >&5
+$as_echo_n "checking for basic compiler flags for loadable drivers... " >&6; }
+DED_BASIC_CFLAGS=$DED_CFLAGS
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_CFLAGS" >&5
+$as_echo "$DED_CFLAGS" >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for compiler flags for loadable drivers" >&5
+$as_echo_n "checking for compiler flags for loadable drivers... " >&6; }
+DED_CFLAGS="$DED_WERRORFLAGS $DED_WARN_FLAGS $DED_THR_DEFS $DED_CFLAGS"
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_CFLAGS" >&5
+$as_echo "$DED_CFLAGS" >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for linker for loadable drivers" >&5
+$as_echo_n "checking for linker for loadable drivers... " >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_LD" >&5
+$as_echo "$DED_LD" >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for linker flags for loadable drivers" >&5
+$as_echo_n "checking for linker flags for loadable drivers... " >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_LDFLAGS" >&5
+$as_echo "$DED_LDFLAGS" >&6; }
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking for 'runtime library path' linker flag" >&5
+$as_echo_n "checking for 'runtime library path' linker flag... " >&6; }
+if test "x$DED_LD_FLAG_RUNTIME_LIBRARY_PATH" != "x"; then
+	{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $DED_LD_FLAG_RUNTIME_LIBRARY_PATH" >&5
+$as_echo "$DED_LD_FLAG_RUNTIME_LIBRARY_PATH" >&6; }
+else
+	{ $as_echo "$as_me:${as_lineno-$LINENO}: result: not found" >&5
+$as_echo "not found" >&6; }
+fi
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
 
 # Check whether --enable-sanitizers was given.
 if test "${enable_sanitizers+set}" = set; then :
diff --git a/lib/erl_interface/configure.in b/lib/erl_interface/configure.in
index fa07048424..7ce895683b 100644
--- a/lib/erl_interface/configure.in
+++ b/lib/erl_interface/configure.in
@@ -85,6 +85,14 @@ AC_ARG_ENABLE(mask-real-errno,
   esac ],
 [ mask_real_errno=yes ])
 
+AC_ARG_ENABLE(ei-dynamic-lib,
+[  --enable-ei-dynamic-lib  build ei as a dynamic library],
+[ case "$enableval" in
+    yes) DYNAMIC_LIB=yes ;;
+    *)   DYNAMIC_LIB=no ;;
+  esac ],
+[ DYNAMIC_LIB=no ])
+AC_SUBST(DYNAMIC_LIB)
 
 dnl ----------------------------------------------------------------------
 dnl Checks for programs
@@ -346,6 +354,9 @@ else
   fi
 fi
 
+ERL_DED_FLAT_BUNDLE=true
+ERL_DED_FLAGS
+
 dnl ----------------------------------------------------------------------
 dnl Enable -fsanitize= flags.
 dnl ----------------------------------------------------------------------
diff --git a/lib/erl_interface/src/Makefile.in b/lib/erl_interface/src/Makefile.in
index 466f6f5e87..e3ee72ad67 100644
--- a/lib/erl_interface/src/Makefile.in
+++ b/lib/erl_interface/src/Makefile.in
@@ -106,7 +106,10 @@ endif
 
 WARNFLAGS += -DEI_NO_DEPR_WARN
 
-CFLAGS = @LIB_CFLAGS@ $(WARNFLAGS) $(INCFLAGS) $(TYPE_FLAGS)
+CFLAGS = @DED_CFLAGS@ $(WARNFLAGS) $(INCFLAGS) $(TYPE_FLAGS)
+DED_LD = @DED_LD@
+DED_LDFLAGS = @DED_LDFLAGS@
+DED_LD_FLAG_RUNTIME_LIBRARY_PATH = @DED_LD_FLAG_RUNTIME_LIBRARY_PATH@
 PROG_CFLAGS = @CFLAGS@ $(WARNFLAGS) $(INCFLAGS) $(TYPE_FLAGS) -Iglobal
 
 INSTALL = @INSTALL@
@@ -127,6 +130,7 @@ MT_OBJDIR  = $(ERL_TOP)/lib/erl_interface/obj.mt$(TYPEMARKER)/$(TARGET)
 MD_OBJDIR  = $(ERL_TOP)/lib/erl_interface/obj.md$(TYPEMARKER)/$(TARGET)
 MDD_OBJDIR = $(ERL_TOP)/lib/erl_interface/obj.mdd$(TYPEMARKER)/$(TARGET)
 OBJDIR     = $(ERL_TOP)/lib/erl_interface/obj$(TYPEMARKER)/$(TARGET)
+LIBDIR     = $(ERL_TOP)/lib/erl_interface/lib/$(TARGET)
 BINDIR     = $(ERL_TOP)/lib/erl_interface/bin/$(TARGET)
 
 # FIXME maybe use this opt and remove (int) cast to is*() functions
@@ -149,14 +153,14 @@ ifeq ($(USING_VC),yes)
 LIBEXT=.lib
 LIBPRE=
 MTFLAG=-MT
-
 else
 LIBEXT=.a
 LIBPRE=lib
 MTFLAG=
-
 endif
 
+DYNLIBEXT=.@DED_EXT@
+
 ###########################################################################
 #  Specify targets names
 ###########################################################################
@@ -166,11 +170,16 @@ ERL_CALL   = $(BINDIR)/erl_call$(EXE)
 ifdef THR_DEFS
 ST_EILIB   = $(OBJDIR)/$(LIBPRE)ei_st$(LIBEXT)
 MT_EILIB   = $(OBJDIR)/$(LIBPRE)ei$(LIBEXT)
+ST_EISHLIB = $(LIBDIR)/$(LIBPRE)ei_st$(DYNLIBEXT)
+MT_EISHLIB = $(LIBDIR)/$(LIBPRE)ei$(DYNLIBEXT)
 else
 ST_EILIB   = $(OBJDIR)/$(LIBPRE)ei$(LIBEXT)
+ST_EISHLIB = $(LIBDIR)/$(LIBPRE)ei$(DYNLIBEXT)
 endif
 MD_EILIB   = $(OBJDIR)/$(LIBPRE)ei_md$(LIBEXT)
 MDD_EILIB  = $(OBJDIR)/$(LIBPRE)ei_mdd$(LIBEXT)
+MD_EISHLIB   = $(LIBDIR)/$(LIBPRE)ei_md$(DYNLIBEXT)
+MDD_EISHLIB  = $(LIBDIR)/$(LIBPRE)ei_mdd$(DYNLIBEXT)
 
 ###########################################################################
 #  Specify targets to build
@@ -183,17 +192,17 @@ ifeq ($(USING_VC),yes)
 
 # Windows targets
 
-TARGETS = \
-	$(OBJ_TARGETS) \
-	$(EXE_TARGETS) \
-	$(APP_TARGET)  \
-	$(APPUP_TARGET)
-
 OBJ_TARGETS = \
 	$(MT_EILIB) \
 	$(MD_EILIB) \
 	$(MDD_EILIB)
 
+SH_TARGETS = \
+	$(MT_EISHLIB) \
+	$(MD_EISHLIB) \
+	$(MDD_EISHLIB)
+
+
 FAKE_TARGETS = \
 	$(OBJDIR)/erl_fake_prog_mt$(EXE) \
 	$(OBJDIR)/ei_fake_prog_mt$(EXE) \
@@ -210,36 +219,18 @@ FAKE_TARGETS = \
 
 else
 
-ifeq ($USING_MINGW,yes)
-TARGETS = \
-	$(OBJ_TARGETS) \
-	$(EXE_TARGETS) \
-	$(APP_TARGET)  \
-	$(APPUP_TARGET)
-
-OBJ_TARGETS = \
-	$(MD_EILIB)
-
-FAKE_TARGETS = \
-	$(OBJDIR)/erl_fake_prog_md$(EXE) \
-	$(OBJDIR)/ei_fake_prog_md$(EXE) \
-	$(OBJDIR)/erl_fake_prog_cxx_md$(EXE) \
-	$(OBJDIR)/ei_fake_prog_cxx_md$(EXE) 
-else
 # Unix targets
 
 ifdef THR_DEFS
 
-TARGETS = \
-	$(OBJ_TARGETS) \
-	$(EXE_TARGETS) \
-	$(APP_TARGET)  \
-	$(APPUP_TARGET)
-
 OBJ_TARGETS = \
 	$(ST_EILIB) \
 	$(MT_EILIB)
 
+SH_TARGETS = \
+	$(ST_EISHLIB) \
+	$(MT_EISHLIB)
+
 FAKE_TARGETS = \
 	$(ST_OBJDIR)/erl_fake_prog_st$(EXE) \
 	$(ST_OBJDIR)/ei_fake_prog_st$(EXE) \
@@ -252,15 +243,12 @@ FAKE_TARGETS = \
 
 else
 
-TARGETS = \
-	$(OBJ_TARGETS) \
-	$(EXE_TARGETS) \
-	$(APP_TARGET)  \
-	$(APPUP_TARGET)
-
 OBJ_TARGETS = \
 	$(ST_EILIB)
 
+SH_TARGETS = \
+	$(ST_EISHLIB)
+
 FAKE_TARGETS = \
 	$(ST_OBJDIR)/erl_fake_prog_st$(EXE) \
 	$(ST_OBJDIR)/ei_fake_prog_st$(EXE) \
@@ -271,7 +259,13 @@ endif
 
 endif
 
-endif
+TARGETS = \
+	$(OBJ_TARGETS) \
+	$(SH_TARGETS) \
+	$(EXE_TARGETS) \
+	$(APP_TARGET)  \
+	$(APPUP_TARGET)
+
 ###########################################################################
 #  List all source files
 ###########################################################################
@@ -415,10 +409,10 @@ docs:
 tests:
 
 clean:
-	rm -f $(ST_EIOBJECTS)  $(ST_EILIB)
-	rm -f $(MT_EIOBJECTS)  $(MT_EILIB)
-	rm -f $(MD_EIOBJECTS)  $(MD_EILIB)
-	rm -f $(MDD_EIOBJECTS) $(MDD_EILIB)
+	rm -f $(ST_EIOBJECTS)  $(ST_EILIB) $(ST_EISHLIB)
+	rm -f $(MT_EIOBJECTS)  $(MT_EILIB) $(MT_EISHLIB)
+	rm -f $(MD_EIOBJECTS)  $(MD_EILIB) $(MD_EISHLIB)
+	rm -f $(MDD_EIOBJECTS) $(MDD_EILIB) $(MDD_EISHLIB)
 	rm -f $(ERL_CALL)
 	rm -f $(FAKE_TARGETS)
 	rm -f $(APP_TARGET)
@@ -451,7 +445,7 @@ $(MDD_OBJDIR)/%.o: %.c
 #  Create directories
 ###########################################################################
 
-_create_dirs := $(shell mkdir -p $(EBINDIR) $(BINDIR) $(OBJDIR) $(ST_OBJDIR) $(MT_OBJDIR) $(MD_OBJDIR) $(MDD_OBJDIR))
+_create_dirs := $(shell mkdir -p $(EBINDIR) $(BINDIR) $(OBJDIR) $(ST_OBJDIR) $(MT_OBJDIR) $(MD_OBJDIR) $(MDD_OBJDIR) $(LIBDIR))
 
 ###########################################################################
 #  Special rules
@@ -482,6 +476,8 @@ $(MDD_EILIB) : $(MDD_EIOBJECTS)
 	$(V_AR) -out:$@ $(MDD_EIOBJECTS)
 	$(V_RANLIB) $@
 
+WIN_SOCKET=-lsocket
+
 else
 
 # Unix archive creation
@@ -493,7 +489,6 @@ ifdef RANLIB
 	$(V_RANLIB) $@
 endif
 
-
 $(MT_EILIB) : $(MT_EIOBJECTS)
 	$(V_at)rm -f $@
 	$(V_AR) $(AR_FLAGS) $@ $(MT_EIOBJECTS)
@@ -503,6 +498,23 @@ endif
 
 endif
 
+$(ST_EISHLIB): $(ST_EIOBJECTS)
+	$(ld_verbose) $(DED_LD) $(DED_LDFLAGS) -o $@ \
+		$(DED_LD_FLAG_RUNTIME_LIBRARY_PATH) $(ST_EIOBJECTS) \
+	        $(THR_LIBS) $(LIBS) $(WIN_SOCKET)
+$(MT_EISHLIB): $(MT_EIOBJECTS)
+	$(ld_verbose) $(DED_LD) $(DED_LDFLAGS) -o $@ \
+		$(DED_LD_FLAG_RUNTIME_LIBRARY_PATH) $(MT_EIOBJECTS) \
+	        $(THR_LIBS) $(LIBS) $(WIN_SOCKET)
+$(MD_EISHLIB): $(MD_EIOBJECTS)
+	$(ld_verbose) $(DED_LD) -MD $(DED_LDFLAGS) -o $@ \
+		$(DED_LD_FLAG_RUNTIME_LIBRARY_PATH) $(MD_EIOBJECTS) \
+	        $(THR_LIBS) $(LIBS) $(WIN_SOCKET)
+$(MDD_EISHLIB): $(MDD_EIOBJECTS)
+	$(ld_verbose) $(DED_LD) -MDd $(DED_LDFLAGS) -o $@ \
+		$(DED_LD_FLAG_RUNTIME_LIBRARY_PATH) $(MDD_EIOBJECTS) \
+	        $(THR_LIBS) $(LIBS) $(WIN_SOCKET)
+
 ###########################################################################
 #  erl_call   FIXME how to avoid explicit -lsocket on winows??? 
 ###########################################################################
@@ -688,6 +700,10 @@ release: opt
 	$(INSTALL_DATA) $(HEADERS)     "$(RELEASE_PATH)/usr/include"
 	$(INSTALL_DATA) $(OBJ_TARGETS) "$(RELSYSDIR)/lib"
 	$(INSTALL_DATA) $(OBJ_TARGETS) "$(RELEASE_PATH)/usr/lib"
+ifeq (@DYNAMIC_LIB@, yes)
+	$(INSTALL_PROGRAM) $(SH_TARGETS) "$(RELSYSDIR)/lib"
+	$(INSTALL_PROGRAM) $(SH_TARGETS) "$(RELEASE_PATH)/usr/lib"
+endif
 	$(INSTALL_PROGRAM) $(EXE_TARGETS) "$(RELSYSDIR)/bin"
 	$(INSTALL_DATA) $(EXTRA)        "$(RELSYSDIR)/src"
 	$(INSTALL_DATA) connect/*.[ch]  "$(RELSYSDIR)/src/connect"
diff --git a/lib/erl_interface/src/connect/ei_connect.c b/lib/erl_interface/src/connect/ei_connect.c
index 99d709a97c..c310c93012 100644
--- a/lib/erl_interface/src/connect/ei_connect.c
+++ b/lib/erl_interface/src/connect/ei_connect.c
@@ -671,7 +671,7 @@ int ei_make_pid(ei_cnode *ec, erlang_pid *pid)
 
 #undef EI_MAKE_REF_ATOMIC__
 #ifdef _REENTRANT
-#  if ((SIZEOF_LONG == 8 || SIZEOF_LONGLONG == 8)         \
+#  if ((SIZEOF_LONG == 8 || SIZEOF_LONG_LONG == 8)        \
        && (ETHR_HAVE___atomic_compare_exchange_n & 8)     \
        && (ETHR_HAVE___atomic_load_n & 8))
 #    define EI_MAKE_REF_ATOMIC__
diff --git a/lib/erl_interface/src/connect/ei_resolve.c b/lib/erl_interface/src/connect/ei_resolve.c
index 1d11c5043d..e28902da82 100644
--- a/lib/erl_interface/src/connect/ei_resolve.c
+++ b/lib/erl_interface/src/connect/ei_resolve.c
@@ -102,7 +102,7 @@ int ei_init_resolve(void)
   return 0;
 }
 
-#if _REENTRANT
+#ifdef _REENTRANT
 
 /* 
  * Copy the contents of one struct hostent to another, i.e. don't just
@@ -290,10 +290,6 @@ static struct hostent *my_gethostbyname_r(const char *name,
   return rval;
 }
 
-#endif /* _REENTRANT */
-
-#if EI_THREADS != false
-
 static struct hostent *my_gethostbyaddr_r(const char *addr,
 					  int length, 
 					  int type, 
@@ -358,7 +354,7 @@ static struct hostent *my_gethostbyaddr_r(const char *addr,
   return rval;
 }
 
-#endif /*  EI_THREADS != false */
+#endif /* _REENTRANT */
 
 #endif /* !HAVE_GETHOSTBYNAME_R */
 
@@ -394,14 +390,12 @@ struct hostent *ei_gethostbyaddr_r(const char *addr,
 				int buflen, 
 				int *h_errnop)
 {
-#if (EI_THREADS == false)
+#ifndef _REENTRANT
   /* threads disabled, no need to call reentrant function */
-  return gethostbyaddr(addr, length, type); 
-#else
-#ifndef HAVE_GETHOSTBYNAME_R
+  return gethostbyaddr(addr, length, type);
+#elif !defined(HAVE_GETHOSTBYNAME_R)
   return my_gethostbyaddr_r(addr,length,type,hostp,buffer,buflen,h_errnop);
-#else
-#if (defined(__GLIBC__) || defined(__linux__) || (__FreeBSD_version >= 602000) || defined(__DragonFly__))
+#elif (defined(__GLIBC__) || defined(__linux__) || (__FreeBSD_version >= 602000) || defined(__DragonFly__))
   struct hostent *result;
 
   gethostbyaddr_r(addr, length, type, hostp, buffer, buflen, &result,
@@ -411,8 +405,6 @@ struct hostent *ei_gethostbyaddr_r(const char *addr,
 #else
   return gethostbyaddr_r(addr,length,type,hostp,buffer,buflen,h_errnop);
 #endif
-#endif
-#endif
 }
 
 struct hostent *ei_gethostbyname_r(const char *name, 
@@ -424,11 +416,9 @@ struct hostent *ei_gethostbyname_r(const char *name,
 #ifndef _REENTRANT
   /* threads disabled, no need to call reentrant function */
   return gethostbyname(name);
-#else
-#ifndef HAVE_GETHOSTBYNAME_R
+#elif !defined(HAVE_GETHOSTBYNAME_R)
   return my_gethostbyname_r(name,hostp,buffer,buflen,h_errnop);
-#else
-#if (defined(__GLIBC__) || defined(__linux__) || (__FreeBSD_version >= 602000) || defined(__DragonFly__) || defined(__ANDROID__))
+#elif (defined(__GLIBC__) || defined(__linux__) || (__FreeBSD_version >= 602000) || defined(__DragonFly__) || defined(__ANDROID__))
   struct hostent *result;
   int err;
 
@@ -440,8 +430,6 @@ struct hostent *ei_gethostbyname_r(const char *name,
 #else
   return gethostbyname_r(name,hostp,buffer,buflen,h_errnop);
 #endif
-#endif
-#endif
 }
 
 #endif /* win, unix */
diff --git a/lib/erl_interface/src/misc/ei_locking.h b/lib/erl_interface/src/misc/ei_locking.h
index ac9ba41a47..7ee7715448 100644
--- a/lib/erl_interface/src/misc/ei_locking.h
+++ b/lib/erl_interface/src/misc/ei_locking.h
@@ -32,7 +32,7 @@
 
 #ifdef HAVE_MIT_PTHREAD_H
 #include <pthread/mit/pthread.h>
-#elif HAVE_PTHREAD_H 
+#elif defined(HAVE_PTHREAD_H) && HAVE_PTHREAD_H
 #include <pthread.h>
 #endif
 
diff --git a/lib/erl_interface/src/prog/erl_call.c b/lib/erl_interface/src/prog/erl_call.c
index 7e58904a9b..e62931de35 100644
--- a/lib/erl_interface/src/prog/erl_call.c
+++ b/lib/erl_interface/src/prog/erl_call.c
@@ -1209,11 +1209,6 @@ void exit_free_flags_fields(int exit_status, struct call_flags* flags) {
 
 /* Constants and helper functions used by erl_start_sys */
 
-/* FIXME is this a case a vfork can be used? */
-#if !HAVE_WORKING_VFORK
-# define vfork fork
-#endif
-
 #ifndef MAXPATHLEN
 #define MAXPATHLEN 1024
 #endif
-- 
2.31.1

openSUSE Build Service is sponsored by