File 4674-Teach-erlc-to-use-the-compile-server.patch of Package erlang

From 3e9cba0f0b4fecd4e5115f9e90b15dd5cc835acc Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 14 May 2019 06:54:09 +0200
Subject: [PATCH 4/6] Teach erlc to use the compile server

---
 Makefile.in                        |  11 +-
 erts/doc/src/erlc.xml              |  63 +++++
 erts/etc/common/Makefile.in        |  12 +-
 erts/etc/common/erlc.c             | 544 +++++++++++++++++++++++++++++++++++--
 erts/test/erlc_SUITE.erl           |  23 +-
 lib/erl_interface/doc/src/Makefile |   2 +-
 lib/erl_interface/src/Makefile     |   2 +
 7 files changed, 628 insertions(+), 29 deletions(-)

diff --git a/Makefile.in b/Makefile.in
index 25003f47a9..9be91a4b20 100644
--- a/Makefile.in
+++ b/Makefile.in
@@ -338,7 +338,8 @@ endif
 else
 # Cross compiling
 
-all: cross_check_erl depend emulator libs start_scripts check_dev_rt_dep
+all: cross_check_erl depend build_erl_interface \
+     emulator libs start_scripts check_dev_rt_dep
 
 endif
 
@@ -376,11 +377,17 @@ endif
 # With all bootstraps we mean all bootstrapping that is done when
 # the system is delivered in open source, the primary
 # bootstrap is not included, it requires a pre built emulator...
-all_bootstraps: emulator \
+all_bootstraps: build_erl_interface emulator \
      bootstrap_setup \
      secondary_bootstrap_build secondary_bootstrap_copy \
      tertiary_bootstrap_build tertiary_bootstrap_copy
 
+.PHONY: build_erl_interface
+
+build_erl_interface:
+	$(make_verbose)cd lib/erl_interface && \
+	  ERL_TOP=$(ERL_TOP) PATH=$(BOOT_PREFIX)"$${PATH}" \
+		$(MAKE) $(TYPE)
 #
 # Use these targets when you want to use the erl and erlc
 # binaries in your PATH instead of those created from the
diff --git a/erts/doc/src/erlc.xml b/erts/doc/src/erlc.xml
index 62957d6a50..9d221a69ee 100644
--- a/erts/doc/src/erlc.xml
+++ b/erts/doc/src/erlc.xml
@@ -138,6 +138,16 @@
           for compiling native code, which must be compiled with the same
           runtime system that it is to be run on.</p>
       </item>
+      <tag><c>-no-server</c></tag>
+      <item>
+        <p>Do not use the
+	<seealso marker="#compile_server">compile server</seealso>.</p>
+      </item>
+      <tag><c>-server</c></tag>
+      <item>
+        <p>Use the
+	<seealso marker="#compile_server">compile server</seealso>.</p>
+      </item>
       <tag><c>-M</c></tag>
       <item>
         <p>Produces a Makefile rule to track header dependencies. The
@@ -298,6 +308,52 @@ erlc +export_all file.erl</pre>
   </section>
 
   <section>
+    <marker id="compile_server"></marker>
+    <title>Compile Server</title>
+    <p>The compile server can be used to potentially speed up the
+    build of multi-file projects by avoiding to start an Erlang system
+    for each file to compile. Whether it will speed up the build
+    depends on the nature of the project and the build machine.</p>
+
+    <p>By default, the compile server is not used. It can be
+    enabled by giving <c>erlc</c> the option <c>-server</c> or by
+    setting the environment variable <c>ERLC_USE_SERVER</c> to
+    <c>yes</c> or <c>true</c>.</p>
+
+    <p>When the compile server is enabled, <c>erlc</c> will
+    automatically use the server if it is started and start the server
+    if has not already started. The server will terminate itself when
+    it has been idle for some number of seconds.</p>
+
+    <p><c>erlc</c> and the compile server communicate using the
+    Erlang distribution. The compile server is started as a hidden
+    node, with a name that includes the current user. Thus, each user
+    on a computer has their own compile server.</p>
+
+    <p>Using the compile server does not always speed up the build, as
+    the compile server sometimes must be restarted to ensure correctness.
+    Here are some examples of situtations that force a restart:</p>
+
+    <list type="bulleted">
+      <item><c>erlc</c> wants to use a different version of Erlang
+      than the compile server is using.</item>
+      <item><c>erlc</c> wants to use different options for <c>erl</c>
+      than the compile server was started with. (A change to code path
+      using the option <c>-pa</c> could cause different parse
+      transforms to be loaded. To be safe, the compile server will be
+      restarted when any <c>erl</c> option is changed.)</item>
+      <item>If the current working directory for <c>erlc</c> is
+      different from the working directory active when the compile
+      server was started, <strong>and</strong> if the compile server
+      has active jobs, it will be restarted as soon as those jobs have
+      finished. (Build systems that build files randomly across multiple
+      directories in parallel will probably not benefit from the
+      compile server.)</item>
+    </list>
+  </section>
+
+    <section>
+    <marker id="environment_variables"></marker>
     <title>Environment Variables</title>
     <taglist>
       <tag><c>ERLC_EMULATOR</c></tag>
@@ -305,6 +361,13 @@ erlc +export_all file.erl</pre>
         in the same directory as the <c>erlc</c> program itself,
         or, if it does not exist, <c>erl</c> in any of the directories
         specified in environment variable <c>PATH</c>.</item>
+      <tag><c>ERLC_USE_SERVER</c></tag>
+      <item>Allowed values are <c>yes</c> or <c>true</c> to use the
+      <seealso marker="#compile_server">compile
+      server</seealso>, and <c>no</c> or <c>false</c> to not use the
+      compile server. If other values are given, <c>erlc</c> will
+      print a warning message and continue.
+      </item>
     </taglist>
   </section>
 
diff --git a/erts/etc/common/Makefile.in b/erts/etc/common/Makefile.in
index 1f35cef669..3a03374fbf 100644
--- a/erts/etc/common/Makefile.in
+++ b/erts/etc/common/Makefile.in
@@ -54,6 +54,8 @@ ERTS_INCL = -I$(ERL_TOP)/erts/include \
             -I$(ERL_TOP)/erts/include/internal \
             -I$(ERL_TOP)/erts/include/internal/$(TARGET)
 
+EI_INCL   = -I$(ERL_TOP)/lib/erl_interface/include
+
 CC        = @CC@
 WFLAGS    = @WFLAGS@
 CFLAGS    = @CFLAGS@ @DEFS@ $(TYPE_FLAGS) @WFLAGS@ -I$(SYSOSDIR) -I$(EMUDIR) -I. \
@@ -87,6 +89,10 @@ DRVDIR    = $(ERL_TOP)/erts/emulator/drivers/@ERLANG_OSTYPE@
 UXETC     = ../unix
 WINETC	  = ../win32
 
+# Threads flags and libs
+THR_DEFS=@THR_DEFS@
+THR_LIBS=@THR_LIBS@
+
 ifeq ($(TARGET), win32)
 ETC       = $(WINETC)
 else
@@ -108,6 +114,8 @@ endif
 
 ERTS_LIB = $(ERL_TOP)/erts/lib_src/obj/$(TARGET)/$(TYPE)/MADE
 
+EI_LIB = -L$(ERL_TOP)/lib/erl_interface/obj/$(TARGET) -lei $(THR_LIBS)
+
 # ----------------------------------------------------
 # Release directory specification
 # ----------------------------------------------------
@@ -426,10 +434,10 @@ $(OBJDIR)/$(ERLEXEC).o: $(ERLEXECDIR)/$(ERLEXEC).c $(RC_GENERATED)
 endif
 
 $(BINDIR)/erlc@EXEEXT@: $(OBJDIR)/erlc.o $(ERTS_LIB)
-	$(ld_verbose)$(PURIFY) $(LD) $(LDFLAGS) -o $@ $(OBJDIR)/erlc.o -L$(OBJDIR) $(LIBS) $(ERTS_INTERNAL_LIBS)
+	$(ld_verbose)$(PURIFY) $(LD) $(LDFLAGS) -o $@ $(OBJDIR)/erlc.o -L$(OBJDIR) $(LIBS) $(ERTS_INTERNAL_LIBS) $(EI_LIB)
 
 $(OBJDIR)/erlc.o: erlc.c $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -o $@ -c erlc.c
+	$(V_CC) $(CFLAGS) $(THR_DEFS) $(EI_INCL) $(MT_FLAG) -o $@ -c erlc.c
 
 $(BINDIR)/dialyzer@EXEEXT@: $(OBJDIR)/dialyzer.o $(ERTS_LIB)
 	$(ld_verbose)$(PURIFY) $(LD) $(LDFLAGS) -o $@ $(OBJDIR)/dialyzer.o -L$(OBJDIR) $(LIBS) $(ERTS_INTERNAL_LIBS)
diff --git a/erts/etc/common/erlc.c b/erts/etc/common/erlc.c
index aa99c69100..a9ee023727 100644
--- a/erts/etc/common/erlc.c
+++ b/erts/etc/common/erlc.c
@@ -20,14 +20,32 @@
 /*
  * Purpose: Common compiler front-end.
  */
+
+#ifdef __WIN32__
+#  include <winsock2.h>
+#else
+#  include <stdio.h>
+#  include <limits.h>
+#  include <stdlib.h>
+#  include <signal.h>
+#  include <sys/stat.h>
+#endif
+
 #include "etc_common.h"
+#include "ei.h"
 
 #define NO 0
 #define YES 1
 
 #define ASIZE(a) (sizeof(a)/sizeof(a[0]))
 
-static int debug = 0;		/* Bit flags for debug printouts. */
+#ifndef PATH_MAX
+# define PATH_MAX 4096
+#endif
+
+static int debug = 0;		/* Debug level. */
+static int use_server = 0;      /* Use compile server. */
+static char* source_file = "<no source>"; /* Source file (last argument). */
 
 static char** eargv_base;	/* Base of vector. */
 static char** eargv;		/* First argument for erl. */
@@ -57,6 +75,7 @@ static int pause_after_execution = 0;
  * Local functions.
  */
 
+static void get_env_compile_server(void);
 static char* process_opt(int* pArgc, char*** pArgv, int offset);
 static void error(char* format, ...);
 static void* emalloc(size_t size);
@@ -66,7 +85,17 @@ static void efree(void *p);
 static char* strsave(char* string);
 static void push_words(char* src);
 static int run_erlang(char* name, char** argv);
+static void call_compile_server(char** argv);
+static void encode_env(ei_x_buff* buf);
+#ifndef __WIN32__
+static char* find_executable(char* progname);
+static char* safe_realpath(char* file);
+#endif
+static char* get_encoding(void);
+static char* decode_binary(const char* buf, int* dec_index, int* dec_size);
+static void start_compile_server(char* node_name, char** argv);
 static char* get_default_emulator(char* progname);
+static char* possibly_unquote(char* arg);
 #ifdef __WIN32__
 static char* possibly_quote(char* arg);
 static void* erealloc(void *p, size_t size);
@@ -194,17 +223,42 @@ int main(int argc, char** argv)
     argv[argc] = NULL;
 #endif
 
+    get_env_compile_server();
+
+    ei_init();
+
     env = get_env("ERLC_EMULATOR");
     emulator = env ? env : get_default_emulator(argv[0]);
 
     if (strlen(emulator) >= MAXPATHLEN)
         error("Value of environment variable ERLC_EMULATOR is too large");
 
+#ifndef __WIN32__
+    emulator = find_executable(emulator);
+#endif
+
     /*
      * Add scriptname to env
      */
+
     set_env("ESCRIPT_NAME", argv[0]);
 
+    /*
+     * Save a piece of configuration in an environment variable.  The
+     * point is that the compile server needs to know that the same
+     * Erlang/OTP system would be started. On Unix, we save the full
+     * path to the Erlang emulator. On Windows, we save the value of
+     * the environment variable PATH. If the compile server finds that
+     * another Erlang/OTP system would be started, it will terminate
+     * itself.
+     */
+
+#ifdef __WIN32__
+    set_env("ERLC_CONFIGURATION", get_env("PATH"));
+#else
+    set_env("ERLC_CONFIGURATION", emulator);
+#endif
+
     /*
      * Allocate the argv vector to be used for arguments to Erlang.
      * Arrange for starting to pushing information in the middle of
@@ -252,6 +306,7 @@ int main(int argc, char** argv)
 	 * Options starting with '+' are passed on to Erlang.
 	 */
 
+        source_file = "<no source>";
 	switch (argv[1][0]) {
 	case '+':
             if (strcmp(argv[1], "+native") == 0) {
@@ -260,11 +315,18 @@ int main(int argc, char** argv)
 	    switch (argv[1][1]) {
 	    case 'd':
 		if (argv[1][2] == '\0') {
-		    debug = 1;
+		    debug++;
 		} else {
 		    PUSH(argv[1]);
 		}
 		break;
+            case 'n':
+                if (strcmp(argv[1], "-no-server") == 0) {
+                    use_server = 0;
+                } else {
+                    PUSH(argv[1]);
+                }
+		break;
 	    case 'p':
 		{
 		    int c = argv[1][2];
@@ -290,6 +352,8 @@ int main(int argc, char** argv)
 	    case 's':
 		if (strcmp(argv[1], "-smp") == 0) {
 		    UNSHIFT(argv[1]);
+                } else if (strcmp(argv[1], "-server") == 0) {
+                    use_server = 1;
 		} else {
 		    PUSH(argv[1]);
 		}
@@ -300,6 +364,7 @@ int main(int argc, char** argv)
 	    }
 	    break;
 	default:
+            source_file = argv[1];
 	    PUSH(argv[1]);
 	    break;
 	}
@@ -320,6 +385,9 @@ int main(int argc, char** argv)
      */
 
     PUSH(NULL);
+    if (use_server) {
+        call_compile_server(eargv);
+    }
     return run_erlang(eargv[0], eargv);
 }
 
@@ -349,6 +417,45 @@ process_opt(int* pArgc, char*** pArgv, int offset)
     return argv[1];
 }
 
+static void
+get_env_compile_server(void)
+{
+    char* us = get_env("ERLC_USE_SERVER");
+
+    if (us == NULL) {
+        return;                 /* Keep default */
+    }
+
+    switch (us[0]) {
+    case 'f':
+        if (strcmp(us+1, "alse") == 0) {
+            use_server = 0;
+            return;
+        }
+        break;
+    case 'n':
+        if (strcmp(us+1, "o") == 0) {
+            use_server = 0;
+            return;
+        }
+        break;
+    case 't':
+        if (strcmp(us+1, "rue") == 0) {
+            use_server = 1;
+            return;
+        }
+        break;
+    case 'y':
+        if (strcmp(us+1, "es") == 0) {
+            use_server = 1;
+            return;
+        }
+        break;
+    }
+    fprintf(stderr, "erlc: Warning: Ignoring unrecognized value '%s' "
+            "for environment value ERLC_USE_SERVER\n", us);
+}
+
 static void
 push_words(char* src)
 {
@@ -369,11 +476,12 @@ push_words(char* src)
     if (sbuf[0])
 	PUSH(strsave(sbuf));
 }
+
 #ifdef __WIN32__
 wchar_t *make_commandline(char **argv)
 {
-    static wchar_t *buff = NULL;
-    static int siz = 0;
+    wchar_t *buff = NULL;
+    int siz = 0;
     int num = 0, len;
     char **arg;
     wchar_t *p;
@@ -400,17 +508,17 @@ wchar_t *make_commandline(char **argv)
     }
     *(--p) = L'\0';
 
-    if (debug) {
-	printf("Processed command line:%S\n",buff);
+    if (debug > 1) {
+	fprintf(stderr, "Processed command line: %S\n", buff);
     }
     return buff;
 }
 
-int my_spawnvp(char **argv)
+int my_spawnvp(int wait, char **argv)
 {
     STARTUPINFOW siStartInfo;
     PROCESS_INFORMATION piProcInfo;
-    DWORD ec;
+    DWORD ec = 0;
 
     memset(&siStartInfo,0,sizeof(STARTUPINFOW));
     siStartInfo.cb = sizeof(STARTUPINFOW); 
@@ -436,12 +544,14 @@ int my_spawnvp(char **argv)
     }
     CloseHandle(piProcInfo.hThread);
 
-    WaitForSingleObject(piProcInfo.hProcess,INFINITE);
-    if (!GetExitCodeProcess(piProcInfo.hProcess,&ec)) {
-	return 0;
+    if (wait) {
+        WaitForSingleObject(piProcInfo.hProcess,INFINITE);
+        if (!GetExitCodeProcess(piProcInfo.hProcess,&ec)) {
+            return 0;
+        }
     }
     return (int) ec;
-}    
+}
 #endif /* __WIN32__ */
 
 
@@ -452,11 +562,18 @@ run_erlang(char* progname, char** argv)
     int status;
 #endif
 
-    if (debug) {
+    if (debug > 0) {
+        fprintf(stderr, "spawning erl for %s", source_file);
+    }
+    if (debug > 1) {
 	int i = 0;
-	while (argv[i] != NULL)
-	    printf(" %s", argv[i++]);
-	printf("\n");
+        fprintf(stderr, ":\n  ");
+	while (argv[i] != NULL) {
+	    fprintf(stderr, "%s ", argv[i++]);
+        }
+    }
+    if (debug) {
+        putc('\n', stderr);
     }
 
 #ifdef __WIN32__
@@ -466,7 +583,7 @@ run_erlang(char* progname, char** argv)
      * we are finished and print a prompt and read keyboard input.
      */
 
-    status = my_spawnvp(argv)/*_spawnvp(_P_WAIT,progname,argv)*/;
+    status = my_spawnvp(1, argv);
     if (status == -1) {
 	fprintf(stderr, "erlc: Error executing '%s': %d", progname, 
 		GetLastError());
@@ -478,12 +595,366 @@ run_erlang(char* progname, char** argv)
     }
     return status;
 #else
-    execvp(progname, argv);
+    execv(progname, argv);
     error("Error %d executing \'%s\'.", errno, progname);
     return 2;
 #endif
 }
 
+static void
+call_compile_server(char** argv)
+{
+    ei_cnode ec;
+    char* user;
+    char node_name[MAXNODELEN+1];
+    char remote[MAXNODELEN+1];
+    short creation = 1;
+    int fd;
+    char cwd[MAXPATHLEN+1];
+    ei_x_buff args;
+    ei_x_buff reply;
+    int reply_size;
+    int dec_size, dec_index;
+    char atom[MAXATOMLEN];
+    int argc;
+
+#ifdef __WIN32__
+    if (_getcwd(cwd, sizeof(cwd)) == 0) {
+        fprintf(stderr, "erlc: failed to get current working directory\n");
+        exit(2);
+    }
+#else
+    if (getcwd(cwd, sizeof(cwd)) == 0) {
+        fprintf(stderr, "erlc: failed to get current working directory\n");
+        exit(2);
+    }
+#endif
+
+#ifndef __WIN32__
+    {
+        struct sigaction act;
+
+        /*
+         * If the node is terminating when ei_rpc() is executed, the process
+         * may receive a SIGPIPE signal. Make sure it does not kill this process.
+         */
+        act.sa_handler = SIG_IGN;
+        sigemptyset(&act.sa_mask);
+        act.sa_flags = 0;
+        sigaction(SIGPIPE, &act, NULL);
+    }
+#endif
+
+    /* Get user name */
+    user = get_env("USERNAME");  /* Windows */
+    if (!user) {
+        user = get_env("LOGNAME"); /* Unix */
+    }
+    if (!user) {
+        user = get_env("USER");  /* Unix */
+    }
+    if (!user) {
+        user = "nouser";
+    }
+
+    /* Create my own node name. */
+#ifdef __WIN32__
+    sprintf(node_name, "erlc_client_%s_%lu", user, (unsigned long) GetCurrentProcessId());
+#else
+    sprintf(node_name, "erlc_client_%s_%d", user, getpid());
+#endif
+
+    if (ei_connect_init(&ec, node_name, NULL, creation) < 0) {
+        /*
+         * There is probably no .erlang.cookie file.
+         */
+        if (debug > 1) {
+            fprintf(stderr, "\ncan't create C node %s: %s\n",
+                    node_name, strerror(erl_errno));
+        }
+        sprintf(remote, "erl_compile_server_%s@host", user);
+        goto start_compile_server;
+    }
+
+    /* Create node name for compile server. */
+
+    sprintf(remote, "erl_compile_server_%s@%s", user, ei_thishostname(&ec));
+
+    if ((fd = ei_connect(&ec, remote)) < 0) {
+        if (debug > 1) {
+            fprintf(stderr, "failed to connect to compile server %s: %s\n",
+                    remote, strerror(erl_errno));
+        }
+        goto start_compile_server;
+    }
+
+    /*
+     * Encode the request to the compile server.
+     */
+
+    ei_x_new_with_version(&args);
+    ei_x_encode_list_header(&args, 1);
+    ei_x_encode_map_header(&args, 4);
+    ei_x_encode_atom(&args, "encoding");
+    ei_x_encode_atom(&args, get_encoding());
+    ei_x_encode_atom(&args, "cwd");
+    ei_x_encode_string(&args, cwd);
+    ei_x_encode_atom(&args, "env");
+    encode_env(&args);
+    ei_x_encode_atom(&args, "command_line");
+    argc = 0;
+    while (argv[argc]) {
+        ei_x_encode_list_header(&args, 1);
+        ei_x_encode_string(&args, possibly_unquote(argv[argc]));
+        argc++;
+    }
+    ei_x_encode_empty_list(&args); /* End of command_line */
+    ei_x_encode_empty_list(&args); /* End of argument list for apply */
+
+    /*
+     * Do a RPC to the compile server.
+     */
+
+    ei_x_new_with_version(&reply);
+    reply_size = ei_rpc(&ec, fd, "erl_compile_server", "compile",
+                        args.buff+1, args.index-1, &reply);
+    if (reply_size < 0) {
+        if (debug > 1) {
+            fprintf(stderr, "failed to rpc to node %s: %s\n",
+                    remote, strerror(erl_errno));
+        }
+        goto start_compile_server;
+    }
+
+    /*
+     * Decode the answer.
+     */
+
+    dec_index = 0;
+    if (ei_decode_atom(reply.buff, &dec_index, atom) == 0 &&
+        strcmp(atom, "wrong_config") == 0) {
+        if (debug > 1) {
+            fprintf(stderr, "wrong configuration\n");
+        }
+        goto start_compile_server;
+    } else if (ei_decode_tuple_header(reply.buff, &dec_index, &dec_size) == 0) {
+        atom[0] = '\0';
+        if (dec_size >= 2) {
+            ei_decode_atom(reply.buff, &dec_index, atom);
+        }
+        if (dec_size == 2) {
+            if (strcmp(atom, "ok") == 0) {
+                char* output = decode_binary(reply.buff, &dec_index, &dec_size);
+                if (debug) {
+                    fprintf(stderr, "called server for %s => ok\n", source_file);
+                }
+                if (output) {
+                    fwrite(output, dec_size, 1, stdout);
+                    exit(0);
+                }
+            }
+        } else if (dec_size == 3 && strcmp(atom, "error") == 0) {
+            int std_size, err_size;
+            char* std;
+            char* err;
+
+            if (debug) {
+                fprintf(stderr, "called server for %s => error\n", source_file);
+            }
+            std = decode_binary(reply.buff, &dec_index, &std_size);
+            err = decode_binary(reply.buff, &dec_index, &err_size);
+            if (std && err) {
+                fwrite(err, err_size, 1, stderr);
+                fwrite(std, std_size, 1, stdout);
+                exit(1);
+            }
+        }
+    }
+
+    /*
+     * Unrecognized term, probably because the node was shutting down.
+     */
+
+    if (debug > 1) {
+        fprintf(stderr, "unrecognized term returned by compilation server:\n");
+        dec_index = 0;
+        ei_print_term(stderr, reply.buff, &dec_index);
+        putc('\n', stderr);
+    }
+
+ start_compile_server:
+    *strchr(remote, '@') = '\0';
+    start_compile_server(remote, argv);
+}
+
+static void
+encode_env(ei_x_buff* buf)
+{
+    char* env_names[] = {"ERL_AFLAGS",
+                         "ERL_FLAGS",
+                         "ERL_ZFLAGS",
+                         "ERL_COMPILER_OPTIONS",
+                         "ERL_LIBS",
+                         "ERLC_CONFIGURATION",
+                         0};
+    char** p = env_names;
+    while (p[0]) {
+        char* val;
+
+        if ((val = get_env(p[0])) != 0) {
+            ei_x_encode_list_header(buf, 1);
+            ei_x_encode_tuple_header(buf, 2);
+            ei_x_encode_string(buf, p[0]);
+            ei_x_encode_string(buf, val);
+        }
+        p++;
+    }
+    ei_x_encode_empty_list(buf);
+}
+
+#ifndef __WIN32__
+static char*
+find_executable(char* progname)
+{
+    char* path;
+    char* start_path;
+    char* real_name;
+    char buf[PATH_MAX];
+    size_t len_component;
+    size_t len_prog;
+
+    if (strchr(progname, '/')) {
+        return progname;
+    }
+
+    len_prog = strlen(progname);
+
+    if (!(path = getenv("PATH"))) {
+        path = "/bin:/usr/bin";
+    }
+
+    do {
+        for (start_path = path; *path != '\0' && *path != ':'; path++) {
+            ;
+        }
+        if (start_path == path) {
+            start_path = ".";
+            len_component = 1;
+        } else {
+            len_component = path - start_path;
+        }
+        memcpy(buf, start_path, len_component);
+        buf[len_component] = '/';
+        memcpy(buf + len_component + 1, progname, len_prog);
+        buf[len_component + len_prog + 1] = '\0';
+        if ((real_name = safe_realpath(buf)) != 0) {
+            struct stat s;
+            if (stat(real_name, &s) == 0 && s.st_mode & S_IFREG) {
+                return real_name;
+            }
+        }
+    } while (*path++ == ':');
+    return progname;
+}
+
+static char*
+safe_realpath(char* file)
+{
+    /*
+     * Always allocate a buffer for the result of realpath().
+     * realpath() on old versions of MacOS X will crash if the buffer
+     * argument is NULL, and realpath() will fail on old versions of
+     * Solaris.
+     */
+    char* real_name = emalloc(PATH_MAX + 1);
+    return realpath(file, real_name);
+}
+#endif
+
+static char*
+get_encoding(void)
+{
+#ifdef __WIN32__
+    return "latin1";
+#else
+    char* p;
+    p = get_env("LC_ALL");
+    if (!p) {
+        p = get_env("LC_CTYPE");
+    }
+    if (!p) {
+        p = get_env("LANG");
+    }
+    if (!p) {
+        return "latin1";
+    } else {
+        return strstr(p, "UTF-8") ? "utf8" : "latin1";
+    }
+#endif
+}
+
+static char*
+decode_binary(const char* buf, int* dec_index, int* dec_size)
+{
+    int dec_type;
+    char* bin;
+
+    ei_get_type(buf, dec_index, &dec_type, dec_size);
+    bin = emalloc(*dec_size);
+    if (ei_decode_binary(buf, dec_index, bin, NULL) < 0) {
+        return NULL;
+    }
+    return bin;
+}
+
+static void
+start_compile_server(char* node_name, char** argv)
+{
+    char* eargv[100];
+    int eargc = 0;
+    char* progname = argv[0];
+
+    while (strcmp(argv[0], "-mode") != 0) {
+        eargv[eargc++] = *argv++;
+    }
+    PUSH2("-boot", "no_dot_erlang");
+    PUSH2("-sname", node_name);
+    PUSH("-hidden");
+    PUSH("-detached");
+    PUSH3("-kernel", "start_compile_server", "true");
+
+    /*
+     * If this is an older Erlang system (before 22.1) that does not
+     * support the compile server, terminate immediately.
+     */
+    PUSH2("-eval", "is_pid(whereis(erl_compile_server)) orelse halt(1)");
+
+    PUSH(NULL);
+
+    if (debug == 1) {
+        fprintf(stderr, "starting compile server %s\n", node_name);
+    } else if (debug > 1) {
+	int i = 0;
+        fprintf(stderr, "starting compile server %s:\n", node_name);
+	while (eargv[i] != NULL) {
+	    fprintf(stderr, "%s ", eargv[i++]);
+        }
+        putc('\n', stderr);
+    }
+
+#ifdef __WIN32__
+    if (my_spawnvp(0, eargv) == -1) {
+	fprintf(stderr, "erlc: Error executing '%s': %d", progname,
+		GetLastError());
+    }
+#else
+    if (fork() == 0) {
+        execv(eargv[0], eargv);
+        error("Error %d executing \'%s\'.", errno, progname);
+    }
+#endif
+}
+
 static void
 error(char* format, ...)
 {
@@ -565,6 +1036,42 @@ get_default_emulator(char* progname)
     return ERL_NAME;
 }
 
+
+static char*
+possibly_unquote(char* arg)
+{
+#ifndef __WIN32__
+    /* Nothing to do if not Windows. */
+    return arg;
+#else
+    char* unquoted;
+    char* dstp;
+
+    if (arg[0] != '"') {
+        /* Not quoted. Nothing to do. */
+        return arg;
+    }
+
+    /*
+     * Remove the quotes and remove backslashes before quotes.
+     */
+
+    unquoted = emalloc(strlen(arg) + 1);
+    arg++;
+    dstp = unquoted;
+    while (*arg) {
+        if (arg[0] == '\\' && arg[1] == '"') {
+            *dstp++ = '"';
+            arg += 2;
+        } else {
+            *dstp++ = *arg++;
+        }
+    }
+    *--dstp = 0;
+    return unquoted;
+#endif
+}
+
 #ifdef __WIN32__
 static char*
 possibly_quote(char* arg)
@@ -623,4 +1130,5 @@ possibly_quote(char* arg)
     *s = '\0';
     return narg;
 }
+
 #endif /* __WIN32__ */
diff --git a/erts/test/erlc_SUITE.erl b/erts/test/erlc_SUITE.erl
index 0c5b9f8358..c01506b1cd 100644
--- a/erts/test/erlc_SUITE.erl
+++ b/erts/test/erlc_SUITE.erl
@@ -32,22 +32,34 @@
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() -> 
+    [{group,with_server},{group,without_server}].
+
+groups() ->
+    Tests = tests(),
+    [{with_server,[],Tests},
+     {without_server,[],Tests}].
+
+tests() ->
     [compile_erl, compile_yecc, compile_script, compile_mib,
      good_citizen, deep_cwd, arg_overflow, make_dep_options].
 
-groups() -> 
-    [].
-
 init_per_suite(Config) ->
     Config.
 
 end_per_suite(_Config) ->
     ok.
 
-init_per_group(_GroupName, Config) ->
+init_per_group(with_server, Config) ->
+    os:putenv("ERLC_USE_SERVER", "yes"),
+    Config;
+init_per_group(without_server, Config) ->
+    os:putenv("ERLC_USE_SERVER", "no"),
+    Config;
+init_per_group(_, Config) ->
     Config.
 
 end_per_group(_GroupName, Config) ->
+    os:unsetenv("ERLC_USE_SERVER"),
     Config.
 
 %% Copy from erlc_SUITE_data/include/erl_test.hrl.
@@ -199,8 +211,7 @@ deep_cwd(Config) when is_list(Config) ->
 deep_cwd_1(PrivDir) ->
     DeepDir0 = filename:join(PrivDir, lists:duplicate(128, $a)),
     DeepDir = filename:join(DeepDir0, lists:duplicate(128, $b)),
-    ok = file:make_dir(DeepDir0),
-    ok = file:make_dir(DeepDir),
+    ok = filelib:ensure_dir(filename:join(DeepDir,"any_file")),
     ok = file:set_cwd(DeepDir),
     ok = file:write_file("test.erl", "-module(test).\n\n"),
     io:format("~s\n", [os:cmd("erlc test.erl")]),
diff --git a/lib/erl_interface/doc/src/Makefile b/lib/erl_interface/doc/src/Makefile
index 507a84a453..03044a0ddd 100644
--- a/lib/erl_interface/doc/src/Makefile
+++ b/lib/erl_interface/doc/src/Makefile
@@ -96,7 +96,7 @@ man: $(MAN1_FILES) $(MAN3_FILES)
 
 gifs: $(GIF_FILES:%=$(HTMLDIR)/%)
 
-debug opt:
+debug opt lcnt:
 
 clean clean_docs clean_tex:
 	rm -rf $(HTMLDIR)/*
diff --git a/lib/erl_interface/src/Makefile b/lib/erl_interface/src/Makefile
index 00c49f1622..6f728a0a28 100644
--- a/lib/erl_interface/src/Makefile
+++ b/lib/erl_interface/src/Makefile
@@ -33,3 +33,5 @@ endif
 
 clean depend docs release release_docs tests release_tests check xmllint:
 	$(make_verbose)$(MAKE) -f $(TARGET)/Makefile $@
+
+lcnt:
-- 
2.16.4

openSUSE Build Service is sponsored by