File otp_src_18.3.4.5-remove-OSE-port.patch of Package erlang

diff -Ndurp otp_src_18.3.4.5/erts/aclocal.m4 otp_src_18.3.4.5-remove-OSE-port/erts/aclocal.m4
--- otp_src_18.3.4.5/erts/aclocal.m4	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/aclocal.m4	2017-02-03 21:52:59.143952049 +0200
@@ -74,21 +74,6 @@ AC_ARG_VAR(erl_xcomp_clock_gettime_cpu_t
 AC_ARG_VAR(erl_xcomp_after_morecore_hook, [__after_morecore_hook can track malloc()s core memory usage: yes|no (only used when cross compiling)])
 AC_ARG_VAR(erl_xcomp_dlsym_brk_wrappers, [dlsym(RTLD_NEXT, _) brk wrappers can track malloc()s core memory usage: yes|no (only used when cross compiling)])
 
-dnl Cross compilation variables for OSE
-AC_ARG_VAR(erl_xcomp_ose_ldflags_pass1, [Linker flags for the OSE module (pass 1) (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_ldflags_pass2, [Linker flags for the OSE module (pass 2) (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_OSEROOT, [OSE installation root directory (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_STRIP, [Strip utility shipped with the OSE distribution(only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_LM_POST_LINK, [OSE postlink tool (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_LM_SET_CONF, [Sets the configuration for an OSE load module (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_LM_ELF_SIZE, [Prints the section size information for an OSE load module (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_LM_LCF, [OSE load module linker configuration file (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_BEAM_LM_CONF, [BEAM OSE load module default configuration file (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_EPMD_LM_CONF, [EPMD OSE load module default configuration file (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_RUN_ERL_LM_CONF, [run_erl_lm OSE load module default configuration file (only used when cross compiling for OSE)])
-AC_ARG_VAR(erl_xcomp_ose_CONFD, [OSE confd source file])
-AC_ARG_VAR(erl_xcomp_ose_CRT0_LM, [OSE crt0 lm source file])
-
 ])
 
 AC_DEFUN(ERL_XCOMP_SYSROOT_INIT,
@@ -503,8 +488,6 @@ AC_CACHE_VAL(ac_cv_sys_ipv6_support,
 #ifdef __WIN32__
 #include <winsock2.h>
 #include <ws2tcpip.h>
-#elif __OSE__
-#error "no ipv6"
 #else
 #include <netinet/in.h>
 #endif],
@@ -517,8 +500,6 @@ else
 #ifdef __WIN32__
 #include <winsock2.h>
 #include <ws2tcpip.h>
-#elif __OSE__
-#error "no ipv6"
 #else
 #include <netinet/in.h>
 #endif],
@@ -991,12 +972,6 @@ if test "X$host_os" = "Xwin32"; then
     THR_LIBS=
     THR_LIB_NAME=win32_threads
     THR_LIB_TYPE=win32_threads
-elif test "X$host_os" = "Xose"; then
-    AC_MSG_RESULT(yes)
-    THR_DEFS="-DOSE_THREADS"
-    THR_LIBS=
-    THR_LIB_NAME=ose_threads
-    THR_LIB_TYPE=ose_threads
 else
     AC_MSG_RESULT(no)
     THR_DEFS=
@@ -1583,22 +1558,9 @@ case "$THR_LIB_NAME" in
 	fi
 	;;
 
-    pthread|ose_threads)
-        case "$THR_LIB_NAME" in
-	     pthread)
-		ETHR_THR_LIB_BASE_DIR=pthread
-		AC_DEFINE(ETHR_PTHREADS, 1, [Define if you have pthreads])
-		;;
-	     ose_threads)
-		AC_DEFINE(ETHR_OSE_THREADS, 1,
-		   [Define if you have OSE style threads])
-		ETHR_THR_LIB_BASE_DIR=ose
-		AC_CHECK_HEADER(ose_spi/ose_spi.h,
-		  AC_DEFINE(HAVE_OSE_SPI_H, 1,
-		    [Define if you have the "ose_spi/ose_spi.h" header file.]))
-		;;
-	esac
-	if test "x$THR_LIB_NAME" = "xpthread"; then
+    pthread)
+	ETHR_THR_LIB_BASE_DIR=pthread
+	AC_DEFINE(ETHR_PTHREADS, 1, [Define if you have pthreads])
 	case $host_os in
 	    openbsd*)
 		# The default stack size is insufficient for our needs
@@ -1657,7 +1619,6 @@ case "$THR_LIB_NAME" in
 	    *) ;;
 	esac
 
-	fi
 	dnl We sometimes need ETHR_DEFS in order to find certain headers
 	dnl (at least for pthread.h on osf1).
 	saved_cppflags="$CPPFLAGS"
@@ -1702,7 +1663,6 @@ case "$THR_LIB_NAME" in
 	dnl
 	dnl Check for functions
 	dnl
-	if test "x$THR_LIB_NAME" = "xpthread"; then
 	AC_CHECK_FUNC(pthread_spin_lock, \
 			[ethr_have_native_spinlock=yes \
 			 AC_DEFINE(ETHR_HAVE_PTHREAD_SPIN_LOCK, 1, \
@@ -1922,8 +1882,6 @@ case "$THR_LIB_NAME" in
 	esac
 	CFLAGS=$old_CFLAGS
 
-        fi ## test "x$THR_LIB_NAME" = "xpthread"
-
 	if test "X$disable_native_ethr_impls" = "Xyes"; then
 	    ethr_have_native_atomics=no
 	else
diff -Ndurp otp_src_18.3.4.5/erts/configure.in otp_src_18.3.4.5-remove-OSE-port/erts/configure.in
--- otp_src_18.3.4.5/erts/configure.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/configure.in	2017-02-03 21:52:59.147951893 +0200
@@ -944,10 +944,7 @@ dnl what the user say. This might not be
 dnl for now that is the way we do it.
 USER_LD=$LD
 USER_LDFLAGS="$LDFLAGS"
-case $host in
-   *ose) ;;
-   *) LD='$(CC)' ;;
-esac
+LD='$(CC)'
 AC_SUBST(LD)
 
 LDFLAG_RUNTIME_LIBRARY_PATH="$CFLAG_RUNTIME_LIBRARY_PATH"
@@ -962,8 +959,6 @@ dnl This is the os flavour, should be un
 case $host in
    win32)
       ERLANG_OSTYPE=win32 ;;
-   *ose)
-      ERLANG_OSTYPE=ose ;;
    *)
       ERLANG_OSTYPE=unix ;;
 esac
@@ -1272,7 +1267,7 @@ case "$enable_threads"-"$found_threads"
 	AC_MSG_RESULT(yes; enabled by user) ;;
     unknown-yes)
 	case $host_os in
-	    solaris*|linux*|darwin*|win32|ose)
+	    solaris*|linux*|darwin*|win32)
 		emu_threads=yes
 		AC_MSG_RESULT(yes; default on this platform)
 		;;
@@ -1354,7 +1349,7 @@ else
 		    enable_child_waiter_thread=no
 		fi
 		;;
-	    win32|ose)
+	    win32)
 		# Child waiter thread cannot be enabled
 		disable_child_waiter_thread=yes
 		enable_child_waiter_thread=no
@@ -2118,7 +2113,7 @@ AC_CHECK_FUNCS([getipnodebyname getipnod
 AC_CHECK_FUNCS([ieee_handler fpsetmask finite isnan isinf res_gethostbyname dlopen \
 		pread pwrite memmove strerror strerror_r strncasecmp \
 		gethrtime localtime_r gmtime_r inet_pton \
-		memcpy mallopt sbrk _sbrk __sbrk brk _brk __brk \
+		mmap mremap memcpy mallopt sbrk _sbrk __sbrk brk _brk __brk \
 		flockfile fstat strlcpy strlcat setsid posix2time time2posix \
 		setlocale nl_langinfo poll mlockall ppoll])
 
@@ -2170,17 +2165,6 @@ case $host_os in
 	    AC_CHECK_FUNCS([writev]) ;;
 esac
 
-case $host_os in
-        *ose)
-	    AC_MSG_CHECKING([for mmap])
-	    AC_MSG_RESULT(not using for OSE)
-	    AC_MSG_CHECKING([for mremap])
-	    AC_MSG_RESULT(not using for OSE) ;;
-        *)
-	    AC_CHECK_FUNCS([mmap mremap]) ;;
-esac
-
-
 AC_CHECK_DECLS([posix2time, time2posix],,,[#include <time.h>])
 
 disable_vfork=false
@@ -4940,7 +4924,6 @@ AC_OUTPUT(
   Makefile:Makefile.in
   ../make/$host/otp.mk:../make/otp.mk.in
   ../make/$host/otp_ded.mk:../make/otp_ded.mk.in
-  ../make/$host/ose_lm.mk:../make/ose_lm.mk.in
 dnl
 dnl The ones below should be moved to their respective lib
 dnl
diff -Ndurp otp_src_18.3.4.5/erts/doc/src/driver_entry.xml otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/driver_entry.xml
--- otp_src_18.3.4.5/erts/doc/src/driver_entry.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/driver_entry.xml	2017-02-03 21:52:59.147951893 +0200
@@ -247,14 +247,10 @@ typedef struct erl_drv_entry {
           something that the <c>WaitForMultipleObjects</c> API
           function understands). (Some trickery in the emulator allows
           more than the built-in limit of 64 <c>Events</c> to be used.)</p>
-	  <p>On Enea OSE the <c>event</c> is one or more signals that can
-	  be retrieved using <seealso marker="ose:ose_erl_driver#erl_drv_ose_get_signal">erl_drv_ose_get_signal</seealso>.</p>
         <p>To use this with threads and asynchronous routines, create a
-          pipe on unix, an Event on Windows or a unique signal number on
-	  Enea OSE. When the routine
+          pipe on unix and an Event on Windows. When the routine
           completes, write to the pipe (use <c>SetEvent</c> on
-          Windows or send a message to the emulator process on Enea OSE),
-	  this will make the emulator call
+          Windows), this will make the emulator call
           <c>ready_input</c> or <c>ready_output</c>.</p>
           <p>Spurious events may happen. That is, calls to <c>ready_input</c>
           or <c>ready_output</c> even though no real events are signaled. In
diff -Ndurp otp_src_18.3.4.5/erts/doc/src/erlang.xml otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/erlang.xml
--- otp_src_18.3.4.5/erts/doc/src/erlang.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/erlang.xml	2017-02-03 21:52:59.147951893 +0200
@@ -1105,7 +1105,7 @@
       <fsummary>Prints a term on standard output.</fsummary>
       <desc>
         <p>Prints a text representation of <c><anno>Term</anno></c> on the
-          standard output. On OSE, the term is printed to the ramlog.</p>
+          standard output.</p>
         <warning>
           <p>This BIF is intended for debugging only.</p>
         </warning>
diff -Ndurp otp_src_18.3.4.5/erts/doc/src/erl_driver.xml otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/erl_driver.xml
--- otp_src_18.3.4.5/erts/doc/src/erl_driver.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/erl_driver.xml	2017-02-03 21:52:59.147951893 +0200
@@ -1077,9 +1077,7 @@ typedef struct ErlIOVec {
           <c>select</c>/<c>poll</c> can use).
           On windows, the Win32 API function <c>WaitForMultipleObjects</c>
           is used. This places other restrictions on the event object.
-          Refer to the Win32 SDK documentation.
-	  On Enea OSE, the receive function is used. See the <seealso
-	  marker="ose:ose_erl_driver"></seealso> for more details.</p>
+          Refer to the Win32 SDK documentation.</p>
         <p>The <c>on</c> parameter should be <c>1</c> for setting events
           and <c>0</c> for clearing them.</p>
         <p>The <c>mode</c> argument is a bitwise-or combination of
@@ -1091,7 +1089,7 @@ typedef struct ErlIOVec {
           <seealso marker="driver_entry#ready_output">ready_output</seealso>.
           </p>
     <note>
-      <p>Some OS (Windows and Enea OSE) do not differentiate between read and write events.
+      <p>Some OS (Windows) do not differentiate between read and write events.
          The call-back for a fired event then only depends on the value of <c>mode</c>.</p>
     </note>
         <p><c>ERL_DRV_USE</c> specifies if we are using the event object or if we want to close it.
diff -Ndurp otp_src_18.3.4.5/erts/doc/src/run_erl.xml otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/run_erl.xml
--- otp_src_18.3.4.5/erts/doc/src/run_erl.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/doc/src/run_erl.xml	2017-02-03 21:52:59.147951893 +0200
@@ -59,7 +59,7 @@
            first argument to run_erl on the command line.</item>
           <tag>pipe_dir</tag>
           <item>This is where to put the named pipe, usually
-          <c><![CDATA[/tmp/]]></c> on Unix or <c><![CDATA[/pipe/]]></c> on OSE. It shall be suffixed by a <c><![CDATA[/]]></c> (slash),
+          <c><![CDATA[/tmp/]]></c>. It shall be suffixed by a <c><![CDATA[/]]></c> (slash),
            i.e. not <c><![CDATA[/tmp/epipies]]></c>, but <c><![CDATA[/tmp/epipes/]]></c>. </item>
           <tag>log_dir</tag>
           <item>This is where the log files are written. There will be one
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/atom.names otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/atom.names
--- otp_src_18.3.4.5/erts/emulator/beam/atom.names	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/atom.names	2017-02-03 21:52:59.147951893 +0200
@@ -441,13 +441,6 @@ atom orelse
 atom os_pid
 atom os_type
 atom os_version
-atom ose_bg_proc
-atom ose_int_proc
-atom ose_phantom
-atom ose_pri_proc
-atom ose_process_prio
-atom ose_process_type
-atom ose_ti_proc
 atom out
 atom out_exited
 atom out_exiting
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_alloc.types otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_alloc.types
--- otp_src_18.3.4.5/erts/emulator/beam/erl_alloc.types	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_alloc.types	2017-02-03 21:52:59.147951893 +0200
@@ -432,21 +432,6 @@ type	SYS_WRITE_BUF	BINARY		SYSTEM		sys_w
 
 +endif
 
-+if ose
-
-type	SYS_READ_BUF	TEMPORARY	SYSTEM		sys_read_buf
-type	FD_TAB		LONG_LIVED	SYSTEM		fd_tab
-type	FD_ENTRY_BUF	STANDARD	SYSTEM		fd_entry_buf
-type	FD_SIG_LIST	SHORT_LIVED	SYSTEM		fd_sig_list
-type    DRV_EV		STANDARD	SYSTEM		driver_event
-type	CS_PROG_PATH	LONG_LIVED	SYSTEM		cs_prog_path
-type	ENVIRONMENT	TEMPORARY	SYSTEM		environment
-type	PUTENV_STR	SYSTEM		SYSTEM		putenv_string
-type	PRT_REP_EXIT	STANDARD	SYSTEM		port_report_exit
-
-+endif
-
-
 +if win32
 
 type	DRV_DATA_BUF	SYSTEM		SYSTEM		drv_data_buf
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_async.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_async.c
--- otp_src_18.3.4.5/erts/emulator/beam/erl_async.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_async.c	2017-02-03 21:52:59.151951737 +0200
@@ -167,7 +167,6 @@ async_ready_q(Uint sched_id)
 
 #endif
 
-
 void
 erts_init_async(void)
 {
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_driver.h otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_driver.h
--- otp_src_18.3.4.5/erts/emulator/beam/erl_driver.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_driver.h	2017-02-03 21:52:59.151951737 +0200
@@ -661,16 +661,6 @@ EXTERN char *driver_dl_error(void);
 EXTERN int erl_drv_putenv(const char *key, char *value);
 EXTERN int erl_drv_getenv(const char *key, char *value, size_t *value_size);
 
-#ifdef __OSE__
-typedef ErlDrvUInt ErlDrvOseEventId;
-EXTERN union SIGNAL *erl_drv_ose_get_signal(ErlDrvEvent ev);
-EXTERN ErlDrvEvent erl_drv_ose_event_alloc(SIGSELECT sig, ErlDrvOseEventId handle,
-					   ErlDrvOseEventId (*resolve_signal)(union SIGNAL *sig), void *extra);
-EXTERN void erl_drv_ose_event_free(ErlDrvEvent ev);
-EXTERN void erl_drv_ose_event_fetch(ErlDrvEvent ev, SIGSELECT *sig,
-                  ErlDrvOseEventId *handle, void **extra);
-#endif
-
 #endif /* !ERL_DRIVER_TYPES_ONLY */
 
 #ifdef WIN32_DYNAMIC_ERL_DRIVER
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_port_task.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_port_task.c
--- otp_src_18.3.4.5/erts/emulator/beam/erl_port_task.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_port_task.c	2017-02-03 21:52:59.151951737 +0200
@@ -1734,7 +1734,7 @@ erts_port_task_execute(ErtsRunQueue *run
 	    reds = ERTS_PORT_REDS_INPUT;
 	    ASSERT((state & ERTS_PORT_SFLGS_DEAD) == 0);
             DTRACE_DRIVER(driver_ready_input, pp);
-	    /* NOTE some windows/ose drivers use ->ready_input
+	    /* NOTE some windows drivers use ->ready_input
 	       for input and output */
 	    (*pp->drv_ptr->ready_input)((ErlDrvData) pp->drv_data,
 					ptp->u.alive.td.io.event);
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_process.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_process.c
--- otp_src_18.3.4.5/erts/emulator/beam/erl_process.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_process.c	2017-02-03 21:52:59.151951737 +0200
@@ -58,11 +58,7 @@
 
 #define ERTS_PROC_MIN_CONTEXT_SWITCH_REDS_COST (CONTEXT_REDS/10)
 
-#ifndef ERTS_SCHED_MIN_SPIN
 #define ERTS_SCHED_SPIN_UNTIL_YIELD 100
-#else
-#define ERTS_SCHED_SPIN_UNTIL_YIELD 1
-#endif
 
 #define ERTS_SCHED_SYS_SLEEP_SPINCOUNT_VERY_LONG 40
 #define ERTS_SCHED_AUX_WORK_SLEEP_SPINCOUNT_FACT_VERY_LONG 1000
@@ -152,12 +148,7 @@ extern BeamInstr beam_apply[];
 extern BeamInstr beam_exit[];
 extern BeamInstr beam_continue_exit[];
 
-#ifdef __OSE__
-/* Eager check I/O not supported on OSE yet. */
-int erts_eager_check_io = 0;
-#else
 int erts_eager_check_io = 1;
-#endif
 int erts_sched_compact_load;
 int erts_sched_balance_util = 0;
 Uint erts_no_schedulers;
@@ -2629,19 +2620,10 @@ try_set_sys_scheduling(void)
 #endif
 
 static ERTS_INLINE int
-prepare_for_sys_schedule(ErtsSchedulerData *esdp, int non_blocking)
+prepare_for_sys_schedule(int non_blocking)
 {
     if (non_blocking && erts_eager_check_io) {
 #ifdef ERTS_SMP
-#ifdef ERTS_SCHED_ONLY_POLL_SCHED_1
-	if (esdp->no != 1) {
-	    /* If we are not scheduler 1 and ERTS_SCHED_ONLY_POLL_SCHED_1 is used
-	       then we make sure to wake scheduler 1 */
-	    ErtsRunQueue *rq = ERTS_RUNQ_IX(0);
-	    wake_scheduler(rq);
-	    return 0;
-	}
-#endif
 	return try_set_sys_scheduling();
 #else
 	return 1;
@@ -2651,16 +2633,6 @@ prepare_for_sys_schedule(ErtsSchedulerDa
 #ifdef ERTS_SMP
 	while (!erts_port_task_have_outstanding_io_tasks()
 	       && try_set_sys_scheduling()) {
-#ifdef ERTS_SCHED_ONLY_POLL_SCHED_1
-	    if (esdp->no != 1) {
-		/* If we are not scheduler 1 and ERTS_SCHED_ONLY_POLL_SCHED_1 is used
-		   then we make sure to wake scheduler 1 */
-		ErtsRunQueue *rq = ERTS_RUNQ_IX(0);
-		clear_sys_scheduling();
-		wake_scheduler(rq);
-		return 0;
-	    }
-#endif
 	    if (!erts_port_task_have_outstanding_io_tasks())
 		return 1;
 	    clear_sys_scheduling();
@@ -2984,8 +2956,6 @@ aux_thread(void *unused)
 		erts_thr_progress_active(NULL, thr_prgr_active = 0);
 	    erts_thr_progress_prepare_wait(NULL);
 
-	    ERTS_SCHED_FAIR_YIELD();
-
 	    flgs = sched_spin_wait(ssi, 0);
 
 	    if (flgs & ERTS_SSI_FLG_SLEEPING) {
@@ -3053,7 +3023,7 @@ scheduler_wait(int *fcalls, ErtsSchedule
      * be waiting in erl_sys_schedule()
      */
 
-    if (ERTS_SCHEDULER_IS_DIRTY(esdp) || !prepare_for_sys_schedule(esdp, 0)) {
+    if (ERTS_SCHEDULER_IS_DIRTY(esdp) || !prepare_for_sys_schedule(0)) {
 
 	sched_waiting(esdp->no, rq);
 
@@ -3117,8 +3087,6 @@ scheduler_wait(int *fcalls, ErtsSchedule
 			erts_thr_progress_prepare_wait(esdp);
 		    }
 
-		    ERTS_SCHED_FAIR_YIELD();
-
 		    flgs = sched_spin_wait(ssi, spincount);
 		    if (flgs & ERTS_SSI_FLG_SLEEPING) {
 			ASSERT(flgs & ERTS_SSI_FLG_WAITING);
@@ -3189,13 +3157,8 @@ scheduler_wait(int *fcalls, ErtsSchedule
 #ifdef ERTS_DIRTY_SCHEDULERS
 	ASSERT(!ERTS_SCHEDULER_IS_DIRTY(esdp));
 #endif
-
-#ifdef ERTS_SCHED_ONLY_POLL_SCHED_1
-	ASSERT(esdp->no == 1);
-#endif
 	sched_waiting_sys(esdp->no, rq);
 
-
 	erts_smp_runq_unlock(rq);
 
 	ASSERT(working);
@@ -3262,7 +3225,7 @@ scheduler_wait(int *fcalls, ErtsSchedule
 		 * Got to check that we still got I/O tasks; otherwise
 		 * we have to continue checking for I/O...
 		 */
-		if (!prepare_for_sys_schedule(esdp, 0)) {
+		if (!prepare_for_sys_schedule(0)) {
 		    spincount *= ERTS_SCHED_TSE_SLEEP_SPINCOUNT_FACT;
 		    goto tse_wait;
 		}
@@ -3284,7 +3247,7 @@ scheduler_wait(int *fcalls, ErtsSchedule
 	     * Got to check that we still got I/O tasks; otherwise
 	     * we have to wait in erl_sys_schedule() after all...
 	     */
-	    if (!prepare_for_sys_schedule(esdp, 0)) {
+	    if (!prepare_for_sys_schedule(0)) {
 		/*
 		 * Not allowed to wait in erl_sys_schedule;
 		 * do tse wait instead...
@@ -5405,17 +5368,11 @@ erts_early_init_scheduling(int no_schedu
     wakeup_other.threshold = ERTS_SCHED_WAKEUP_OTHER_THRESHOLD_MEDIUM;
     wakeup_other.type = ERTS_SCHED_WAKEUP_OTHER_TYPE_DEFAULT;
 #endif
-#ifndef ERTS_SCHED_MIN_SPIN
     sched_busy_wait.sys_schedule = ERTS_SCHED_SYS_SLEEP_SPINCOUNT_MEDIUM;
     sched_busy_wait.tse = (ERTS_SCHED_SYS_SLEEP_SPINCOUNT_MEDIUM
 			   * ERTS_SCHED_TSE_SLEEP_SPINCOUNT_FACT);
     sched_busy_wait.aux_work = (ERTS_SCHED_SYS_SLEEP_SPINCOUNT_MEDIUM
 				* ERTS_SCHED_AUX_WORK_SLEEP_SPINCOUNT_FACT_MEDIUM);
-#else
-    sched_busy_wait.sys_schedule = ERTS_SCHED_SYS_SLEEP_SPINCOUNT_NONE;
-    sched_busy_wait.tse = ERTS_SCHED_SYS_SLEEP_SPINCOUNT_NONE;
-    sched_busy_wait.aux_work = ERTS_SCHED_SYS_SLEEP_SPINCOUNT_NONE;
-#endif
 }
 
 int
@@ -8301,18 +8258,12 @@ erts_start_schedulers(void)
 
 	erts_snprintf(opts.name, 16, "%lu_scheduler", actual + 1);
 
-#ifdef __OSE__
-        /* This should be done in the bind strategy */
-	opts.coreNo = (actual+1) % ose_num_cpus();
-#endif
-
 	res = ethr_thr_create(&esdp->tid, sched_thread_func, (void*)esdp, &opts);
 
 	if (res != 0) {
            break;
 	}
     }
-
     erts_no_schedulers = actual;
 
 #ifdef ERTS_DIRTY_SCHEDULERS
@@ -8341,10 +8292,6 @@ erts_start_schedulers(void)
 
     erts_snprintf(opts.name, 16, "aux");
 
-#ifdef __OSE__
-    opts.coreNo = 0;
-#endif /* __OSE__ */
-
     res = ethr_thr_create(&aux_tid, aux_thread, NULL, &opts);
     if (res != 0)
 	erts_exit(ERTS_ERROR_EXIT, "Failed to create aux thread\n");
@@ -8364,7 +8311,6 @@ erts_start_schedulers(void)
 		      actual, actual == 1 ? " was" : "s were");
 	erts_send_error_to_logger_nogl(dsbufp);
     }
-
 }
 
 #endif /* ERTS_SMP */
@@ -9568,12 +9514,10 @@ Process *schedule(Process *p, int calls)
 	    erts_aint32_t aux_work;
 	    int leader_update = erts_thr_progress_update(esdp);
 	    aux_work = erts_atomic32_read_acqb(&esdp->ssi->aux_work);
-	    if (aux_work | leader_update | ERTS_SCHED_FAIR) {
+	    if (aux_work | leader_update) {
 		erts_smp_runq_unlock(rq);
 		if (leader_update)
 		    erts_thr_progress_leader_update(esdp);
-		else if (ERTS_SCHED_FAIR)
-		  ERTS_SCHED_FAIR_YIELD();
 		if (aux_work)
 		    handle_aux_work(&esdp->aux_work_data, aux_work, 0);
 		erts_smp_runq_lock(rq);
@@ -9651,7 +9595,7 @@ Process *schedule(Process *p, int calls)
 	}
 	else if (!ERTS_SCHEDULER_IS_DIRTY(esdp) &&
 		 (fcalls > input_reductions &&
-		  prepare_for_sys_schedule(esdp, !0))) {
+		  prepare_for_sys_schedule(!0))) {
 	    ErtsMonotonicTime current_time;
 	    /*
 	     * Schedule system-level activities.
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_process.h otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_process.h
--- otp_src_18.3.4.5/erts/emulator/beam/erl_process.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_process.h	2017-02-03 21:52:59.151951737 +0200
@@ -702,13 +702,6 @@ extern ErtsAlignedSchedulerData *erts_al
 extern ErtsSchedulerData *erts_scheduler_data;
 #endif
 
-#ifdef ERTS_SCHED_FAIR
-#define ERTS_SCHED_FAIR_YIELD() ETHR_YIELD()
-#else
-#define ERTS_SCHED_FAIR 0
-#define ERTS_SCHED_FAIR_YIELD()
-#endif
-
 #if defined(ERTS_SMP) && defined(ERTS_ENABLE_LOCK_CHECK)
 int erts_smp_lc_runq_is_locked(ErtsRunQueue *);
 #endif
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/erl_trace.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_trace.c
--- otp_src_18.3.4.5/erts/emulator/beam/erl_trace.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/erl_trace.c	2017-02-03 21:52:59.151951737 +0200
@@ -3436,8 +3436,6 @@ sys_msg_dispatcher_func(void *unused)
 	    if (erts_thr_progress_update(NULL))
 		erts_thr_progress_leader_update(NULL);
 
-	    ERTS_SCHED_FAIR_YIELD();
-
 #ifdef DEBUG_PRINTOUTS
 	    print_msg_type(smqp);
 #endif
@@ -3592,9 +3590,6 @@ static void
 init_sys_msg_dispatcher(void)
 {
     erts_smp_thr_opts_t thr_opts = ERTS_SMP_THR_OPTS_DEFAULT_INITER;
-#ifdef __OSE__
-    thr_opts.coreNo   = 0;
-#endif
     thr_opts.detached = 1;
     thr_opts.name = "sys_msg_dispatcher";
     init_smq_element_alloc();
@@ -3602,7 +3597,6 @@ init_sys_msg_dispatcher(void)
     sys_message_queue_end = NULL;
     erts_smp_cnd_init(&smq_cnd);
     erts_smp_mtx_init(&smq_mtx, "sys_msg_q");
-
     erts_smp_thr_create(&sys_msg_dispatcher_tid,
 			sys_msg_dispatcher_func,
 			NULL,
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/io.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/io.c
--- otp_src_18.3.4.5/erts/emulator/beam/io.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/io.c	2017-02-03 21:52:59.155951581 +0200
@@ -53,9 +53,7 @@
 #include "erl_time.h"
 
 extern ErlDrvEntry fd_driver_entry;
-#ifndef __OSE__
 extern ErlDrvEntry vanilla_driver_entry;
-#endif
 extern ErlDrvEntry spawn_driver_entry;
 extern ErlDrvEntry *driver_tab[]; /* table of static drivers, only used during initialization */
 
@@ -2806,9 +2804,7 @@ void erts_init_io(int port_tab_size,
     erts_smp_rwmtx_rwlock(&erts_driver_list_lock);
 
     init_driver(&fd_driver, &fd_driver_entry, NULL);
-#ifndef __OSE__
     init_driver(&vanilla_driver, &vanilla_driver_entry, NULL);
-#endif
     init_driver(&spawn_driver, &spawn_driver_entry, NULL);
     erts_init_static_drivers();
     for (dp = driver_tab; *dp != NULL; dp++)
diff -Ndurp otp_src_18.3.4.5/erts/emulator/beam/sys.h otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/sys.h
--- otp_src_18.3.4.5/erts/emulator/beam/sys.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/beam/sys.h	2017-02-03 21:52:59.155951581 +0200
@@ -74,9 +74,7 @@
 
 #if defined (__WIN32__)
 #  include "erl_win_sys.h"
-#elif defined (__OSE__)
-#  include "erl_ose_sys.h"
-#else 
+#else
 #  include "erl_unix_sys.h"
 #ifndef UNIX
 #  define UNIX 1
diff -Ndurp otp_src_18.3.4.5/erts/emulator/drivers/common/efile_drv.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/common/efile_drv.c
--- otp_src_18.3.4.5/erts/emulator/drivers/common/efile_drv.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/common/efile_drv.c	2017-02-03 21:52:59.155951581 +0200
@@ -101,15 +101,9 @@
 #  include "config.h"
 #endif
 
-#ifndef __OSE__
 #include <ctype.h>
 #include <sys/types.h>
 #include <stdlib.h>
-#else
-#include "ctype.h"
-#include "sys/types.h"
-#include "stdlib.h"
-#endif
 
 /* Need (NON)BLOCKING macros for sendfile */
 #ifndef WANT_NONBLOCKING
diff -Ndurp otp_src_18.3.4.5/erts/emulator/drivers/common/inet_drv.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/common/inet_drv.c
--- otp_src_18.3.4.5/erts/emulator/drivers/common/inet_drv.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/common/inet_drv.c	2017-02-03 21:52:59.155951581 +0200
@@ -94,10 +94,6 @@ typedef unsigned long long llu_t;
 #define INT16_MAX (32767)
 #endif
 
-#ifdef __OSE__
-#include "inet.h"
-#endif
-
 #ifdef __WIN32__
 #define  STRNCASECMP strncasecmp
 
@@ -298,139 +294,7 @@ static unsigned long one_value = 1;
 #define TCP_SHUT_RD    SD_RECEIVE
 #define TCP_SHUT_RDWR  SD_BOTH
 
-#elif defined (__OSE__)
-
-/*
- * Some notes about how inet (currently only tcp) works on OSE.
- * The driver uses OSE signals to communicate with the one_inet
- * process. Because of the difference in how signals and file descriptors
- * work the whole select/deselect mechanic is very different.
- * In ose when a sock_select is done a function is called. That function
- * notes the changes that the driver want to do, but does not act on it.
- * later when the function returns the new desired state is compared
- * to the previous state and the apprioriate actions are taken. The action
- * is usually to either request more data from the stack or stop requesting
- * data.
- *
- * One thing to note is that the driver never does select/deselect. It always
- * listens for the signals. Flow of data is regulated by sending or not sending
- * signals to the ose inet process.
- *
- * The interesting functions to look at are:
- *  * inet_driver_select : called when sock_select is called
- *  * tcp_inet_ose_dispatch_signal : checks state changes and sends new signals
- *  * tcp_inet_drv_output_ose : ready output callback, reads signals and calls
- *                              dispatch_signal
- *  * tcp_inet_drv_input_ose : ready input callback.
- */
-
-#include "efs.h"
-#include "sys/socket.h"
-#include "sys/uio.h"
-#include "sfk/sys/sfk_uio.h"
-#include "netinet/in.h"
-#include "netinet/tcp.h"
-#include "netdb.h"
-#include "ose_spi/socket.sig"
-
-
-static ssize_t writev_fallback(int fd, const struct iovec *iov, int iovcnt, int max_sz);
-
-#define INVALID_SOCKET -1
-#define INVALID_EVENT  -1
-#define SOCKET_ERROR   -1
-
-#define SOCKET int
-#define HANDLE int
-#define FD_READ         ERL_DRV_READ
-#define FD_WRITE        ERL_DRV_WRITE
-#define FD_CLOSE        0
-#define FD_CONNECT      (1<<4)
-#define FD_ACCEPT       (1<<5)
-#define SOCK_FD_ERROR   (1<<6)
-
-#define sock_connect(s, addr, len)  connect((s), (addr), (len))
-#define sock_listen(s, b)           listen((s), (b))
-#define sock_bind(s, addr, len)     bind((s), (addr), (len))
-#define sock_getopt(s,t,n,v,l)      getsockopt((s),(t),(n),(v),(l))
-#define sock_setopt(s,t,n,v,l)      setsockopt((s),(t),(n),(v),(l))
-#define sock_name(s, addr, len)     getsockname((s), (addr), (len))
-#define sock_peer(s, addr, len)     getpeername((s), (addr), (len))
-#define sock_ntohs(x)               ntohs((x))
-#define sock_ntohl(x)               ntohl((x))
-#define sock_htons(x)               htons((x))
-#define sock_htonl(x)               htonl((x))
-
-#define sock_accept(s, addr, len)   accept((s), (addr), (len))
-#define sock_send(s,buf,len,flag)   inet_send((s),(buf),(len),(flag))
-#define sock_sendto(s,buf,blen,flag,addr,alen) \
-	    sendto((s),(buf),(blen),(flag),(addr),(alen))
-#define sock_sendv(s, vec, size, np, flag) \
-	    (*(np) = writev_fallback((s), (struct iovec*)(vec), (size), (*(np))))
-#define sock_sendmsg(s,msghdr,flag) sendmsg((s),(msghdr),(flag))
-
-#define sock_open(af, type, proto)  socket((af), (type), (proto))
-#define sock_close(s)               close((s))
-#define sock_dup(s)                 dup((s))
-#define sock_shutdown(s, how)       shutdown((s), (how))
-
-#define sock_hostname(buf, len)     gethostname((buf), (len))
-#define sock_getservbyname(name,proto) getservbyname((name), (proto))
-#define sock_getservbyport(port,proto) getservbyport((port), (proto))
-
-#define sock_recv(s,buf,len,flag)   recv((s),(buf),(len),(flag))
-#define sock_recvfrom(s,buf,blen,flag,addr,alen) \
-                recvfrom((s),(buf),(blen),(flag),(addr),(alen))
-#define sock_recvmsg(s,msghdr,flag) recvmsg((s),(msghdr),(flag))
-
-#define sock_errno()                errno
-#define sock_create_event(d)        ((d)->s) /* return file descriptor */
-#define sock_close_event(e)                  /* do nothing */
-
-#ifndef WANT_NONBLOCKING
-#define WANT_NONBLOCKING
-#endif
-#include "sys.h"
-
-typedef unsigned long  u_long;
-#define  IN_CLASSA(a)      ((((in_addr_t)(a)) & 0x80000000) == 0)
-#define  IN_CLASSA_NET     0xff000000
-#define  IN_CLASSA_NSHIFT  24
-#define  IN_CLASSA_HOST    (0xffffffff & ~IN_CLASSA_NET)
-#define  IN_CLASSA_MAX     128
-
-#define  IN_CLASSB(a)      ((((in_addr_t)(a)) & 0xc0000000) == 0x80000000)
-#define  IN_CLASSB_NET     0xffff0000
-#define  IN_CLASSB_NSHIFT  16
-#define  IN_CLASSB_HOST    (0xffffffff & ~IN_CLASSB_NET)
-#define  IN_CLASSB_MAX     65536
-
-#define  IN_CLASSC(a)      ((((in_addr_t)(a)) & 0xe0000000) == 0xc0000000)
-#define  IN_CLASSC_NET     0xffffff00
-#define  IN_CLASSC_NSHIFT  8
-#define  IN_CLASSC_HOST    (0xffffffff & ~IN_CLASSC_NET)
-
-#define  IN_CLASSD(a)      ((((in_addr_t)(a)) & 0xf0000000) == 0xe0000000)
-#define  IN_MULTICAST(a)      IN_CLASSD(a)
-
-#define  IN_EXPERIMENTAL(a)   ((((in_addr_t)(a)) & 0xe0000000) == 0xe0000000)
-#define  IN_BADCLASS(a)    ((((in_addr_t)(a)) & 0xf0000000) == 0xf0000000)
-
-#define sock_select(d, flags, onoff) do { \
-        ASSERT(!(d)->is_ignored); \
-        (d)->event_mask = (onoff) ? \
-                 ((d)->event_mask | (flags)) : \
-                 ((d)->event_mask & ~(flags)); \
-        DEBUGF(("(%s / %d) sock_select(%ld): flags=%02X, onoff=%d, event_mask=%02lX, s=%d\r\n", \
-		__FILE__, __LINE__, (long) (d)->port, (flags), (onoff), (unsigned long) (d)->event_mask, (d)->s)); \
-        inet_driver_select((d), (flags), (onoff)); \
-   } while(0)
-
-#define TCP_SHUT_WR    SHUT_WR
-#define TCP_SHUT_RD    SHUT_RD
-#define TCP_SHUT_RDWR  SHUT_RDWR
-
-#else /* !__OSE__ && !__WIN32__ */
+#else /* !__WIN32__ */
 
 #include <sys/time.h>
 #ifdef NETDB_H_NEEDS_IN_H
@@ -704,7 +568,7 @@ static int my_strncasecmp(const char *s1
 #define TCP_SHUT_RD    SHUT_RD
 #define TCP_SHUT_RDWR  SHUT_RDWR
 
-#endif /* !__WIN32__ && !__OSE__ */
+#endif /* !__WIN32__ */
 
 #ifdef HAVE_SOCKLEN_T
 #  define SOCKLEN_T socklen_t
@@ -1168,13 +1032,6 @@ typedef struct {
     char *netns;                /* Socket network namespace name
 				   as full file path */
 #endif
-#ifdef __OSE__
-    int select_state;           /* state to keep track of whether we
-				   should trigger another read/write
-				   request at end of ready_input/output */
-    ErlDrvEvent events[6];
-#endif
-
 } inet_descriptor;
 
 
@@ -1190,10 +1047,8 @@ static void tcp_inet_stop(ErlDrvData);
 static void tcp_inet_command(ErlDrvData, char*, ErlDrvSizeT);
 static void tcp_inet_commandv(ErlDrvData, ErlIOVec*);
 static void tcp_inet_flush(ErlDrvData drv_data);
-#ifndef __OSE__
 static void tcp_inet_drv_input(ErlDrvData, ErlDrvEvent);
 static void tcp_inet_drv_output(ErlDrvData data, ErlDrvEvent event);
-#endif
 static ErlDrvData tcp_inet_start(ErlDrvPort, char* command);
 static ErlDrvSSizeT tcp_inet_ctl(ErlDrvData, unsigned int,
 				 char*, ErlDrvSizeT, char**, ErlDrvSizeT);
@@ -1206,71 +1061,6 @@ static void tcp_inet_event(ErlDrvData, E
 static void find_dynamic_functions(void);
 #endif
 
-#ifdef __OSE__
-/* The structure of the signal used for requesting asynchronous 
- * notification from the stack. Under normal circumstances the network stack 
- * shouldn't overwrite the value set in the fd field by the sender 
- * of the request */
-struct OseAsyncSig {
-    struct FmEvent event;
-    int fd;
-};
-
-union SIGNAL {
-    SIGSELECT signo;
-    struct OseAsyncSig async;
-};
-
-static ErlDrvSSizeT tcp_inet_ctl_ose(ErlDrvData e, unsigned int cmd,
-				     char* buf, ErlDrvSizeT len,
-				     char** rbuf, ErlDrvSizeT rsize);
-static void tcp_inet_commandv_ose(ErlDrvData e, ErlIOVec* ev);
-static void tcp_inet_drv_output_ose(ErlDrvData data, ErlDrvEvent event);
-static void tcp_inet_drv_input_ose(ErlDrvData data, ErlDrvEvent event);
-static ErlDrvOseEventId inet_resolve_signal(union SIGNAL *sig);
-
-#ifdef INET_DRV_DEBUG
-
-static char *read_req = "SO_EVENT_READ_REQUEST";
-static char *read_rep = "SO_EVENT_READ_REPLY";
-static char *write_req = "SO_EVENT_WRITE_REQUEST";
-static char *write_rep = "SO_EVENT_WRITE_REPLY";
-static char *eof_req = "SO_EVENT_EOF_REQUEST";
-static char *eof_rep = "SO_EVENT_EOF_REPLY";
-static char *accept_req = "SO_EVENT_ACCEPT_REQUEST";
-static char *accept_rep = "SO_EVENT_ACCEPT_REPLY";
-static char *connect_req = "SO_EVENT_CONNECT_REQUEST";
-static char *connect_rep = "SO_EVENT_CONNECT_REPLY";
-static char *error_req = "SO_EVENT_ERROR_REQUEST";
-static char *error_rep = "SO_EVENT_ERROR_REPLY";
-static char signo_tmp[32];
-
-static char *signo_to_string(SIGSELECT signo) {
-  switch (signo) {
-  case SO_EVENT_READ_REQUEST: { return read_req; }
-  case SO_EVENT_READ_REPLY: { return read_rep; }
-  case SO_EVENT_WRITE_REQUEST: { return write_req; }
-  case SO_EVENT_WRITE_REPLY: { return write_rep; }
-  case SO_EVENT_EOF_REQUEST: { return eof_req; }
-  case SO_EVENT_EOF_REPLY: { return eof_rep; }
-  case SO_EVENT_ACCEPT_REQUEST: { return accept_req; }
-  case SO_EVENT_ACCEPT_REPLY: { return accept_rep; }
-  case SO_EVENT_CONNECT_REQUEST: { return connect_req; }
-  case SO_EVENT_CONNECT_REPLY: { return connect_rep; }
-  case SO_EVENT_ERROR_REQUEST: { return error_req; }
-  case SO_EVENT_ERROR_REPLY: { return error_rep; }
-  }
-
-  snprintf(signo_tmp,32,"0x%x",signo);
-
-  return signo_tmp;
-}
-
-#endif
-
-#endif /* __OSE__ */
-
-
 static struct erl_drv_entry tcp_inet_driver_entry =
 {
     tcp_inet_init,  /* inet_init will add this driver !! */
@@ -1280,9 +1070,6 @@ static struct erl_drv_entry tcp_inet_dri
 #ifdef __WIN32__
     tcp_inet_event,
     NULL,
-#elif defined(__OSE__)
-    tcp_inet_drv_input_ose, /*ready_input*/
-    tcp_inet_drv_output_ose, /*ready_output*/
 #else
     tcp_inet_drv_input,
     tcp_inet_drv_output,
@@ -1290,17 +1077,9 @@ static struct erl_drv_entry tcp_inet_dri
     "tcp_inet",
     NULL,
     NULL,
-#ifdef __OSE__
-    tcp_inet_ctl_ose,
-#else
     tcp_inet_ctl,
-#endif
     tcp_inet_timeout,
-#ifdef __OSE__
-    tcp_inet_commandv_ose,
-#else
     tcp_inet_commandv,
-#endif
     NULL,
     tcp_inet_flush,
     NULL,
@@ -1452,14 +1231,6 @@ static int packet_inet_output(udp_descri
 /* convert descriptor pointer to inet_descriptor pointer */
 #define INETP(d) (&(d)->inet)
 
-#ifdef __OSE__
-static void inet_driver_select(inet_descriptor* desc,
-			       int flags, int onoff);
-static void tcp_inet_ose_dispatch_signals(tcp_descriptor *desc,
-					  int prev_select_state,
-					  union SIGNAL *sig);
-#endif
-
 static int async_ref = 0;          /* async reference id generator */
 #define NEW_ASYNC_ID() ((async_ref++) & 0xffff)
 
@@ -4355,16 +4126,6 @@ static void desc_close(inet_descriptor*
 	desc->forced_events = 0;
 	desc->send_would_block = 0;
 #endif
-#ifdef __OSE__
-	if (desc->events[0]) {
-	  driver_select(desc->port,desc->events[0],FD_READ|FD_WRITE|ERL_DRV_USE,0);
-	  driver_select(desc->port,desc->events[1],FD_READ|FD_WRITE|ERL_DRV_USE,0);
-	  driver_select(desc->port,desc->events[2],FD_READ|FD_WRITE|ERL_DRV_USE,0);
-	  driver_select(desc->port,desc->events[3],FD_READ|FD_WRITE|ERL_DRV_USE,0);
-	  driver_select(desc->port,desc->events[4],FD_READ|FD_WRITE|ERL_DRV_USE,0);
-	  driver_select(desc->port,desc->events[5],FD_READ|FD_WRITE|ERL_DRV_USE,0);
-	}
-#else
 	/*
 	 * We should close the fd here, but the other driver might still
 	 * be selecting on it.
@@ -4374,7 +4135,6 @@ static void desc_close(inet_descriptor*
 			  ERL_DRV_USE, 0);
 	else
 	  inet_stop_select((ErlDrvEvent)(long)desc->event,NULL);
-#endif
 	desc->event = INVALID_EVENT; /* closed by stop_select callback */
 	desc->s = INVALID_SOCKET;
 	desc->event_mask = 0;
@@ -4416,65 +4176,6 @@ static int erl_inet_close(inet_descripto
     return 0;
 }
 
-#ifdef __OSE__
-static void inet_select_init(inet_descriptor* desc)
-{
-    desc->events[0] =
-        erl_drv_ose_event_alloc(SO_EVENT_READ_REPLY,
-                desc->s,
-                inet_resolve_signal,
-                NULL);
-    driver_select(desc->port, desc->events[0],
-            ERL_DRV_READ|ERL_DRV_USE, 1);
-
-    desc->events[1] =
-        erl_drv_ose_event_alloc(SO_EVENT_EOF_REPLY,
-                desc->s,
-                inet_resolve_signal,
-                NULL);
-    driver_select(desc->port, desc->events[1],
-            ERL_DRV_READ|ERL_DRV_USE, 1);
-
-    desc->events[2] =
-        erl_drv_ose_event_alloc(SO_EVENT_ACCEPT_REPLY,
-                desc->s,
-                inet_resolve_signal,
-                NULL);
-    driver_select(desc->port, desc->events[2],
-            ERL_DRV_READ|ERL_DRV_USE, 1);
-
-    /* trigger tcp_inet_input */
-    desc->events[3] =
-        erl_drv_ose_event_alloc(SO_EVENT_WRITE_REPLY,
-                desc->s,
-                inet_resolve_signal,
-                NULL);
-    driver_select(desc->port, desc->events[3],
-            ERL_DRV_WRITE|ERL_DRV_USE, 1);
-
-    desc->events[4] =
-        erl_drv_ose_event_alloc(SO_EVENT_CONNECT_REPLY,
-                desc->s,
-                inet_resolve_signal,
-                NULL);
-    driver_select(desc->port, desc->events[4],
-            ERL_DRV_WRITE|ERL_DRV_USE, 1);
-
-    desc->events[5] =
-        erl_drv_ose_event_alloc(SO_EVENT_ERROR_REPLY,
-                desc->s,
-                inet_resolve_signal,
-                NULL);
-    driver_select(desc->port, desc->events[5],
-            ERL_DRV_WRITE|ERL_DRV_USE, 1);
-
-    /* Issue a select on error event before any other select to be sure we are
-       prepared to receive error notifications from the stack, even in the
-       situations when select isn't issued */
-    sock_select(desc, SOCK_FD_ERROR, 1);
-}
-#endif
-
 static ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc, int domain, int type,
 				  char** rbuf, ErlDrvSizeT rsize)
 {
@@ -4557,9 +4258,6 @@ static ErlDrvSSizeT inet_ctl_open(inet_d
 #ifdef __WIN32__
     driver_select(desc->port, desc->event, ERL_DRV_READ, 1);
 #endif
-#ifdef __OSE__
-    inet_select_init(desc);
-#endif
 
     desc->state = INET_STATE_OPEN;
     desc->stype = type;
@@ -4583,13 +4281,7 @@ static ErlDrvSSizeT inet_ctl_fdopen(inet
         if (name.sa.sa_family != domain)
             return ctl_error(EINVAL, rbuf, rsize);
     }
-#ifdef __OSE__        
-    /* for fdopen duplicating the sd will allow to uniquely identify
-       the signal from OSE with erlang port */
-    desc->s = sock_dup(s);    
-#else
     desc->s = s;
-#endif
 
     if ((desc->event = sock_create_event(desc)) == INVALID_EVENT)
 	return ctl_error(sock_errno(), rbuf, rsize);
@@ -4607,12 +4299,6 @@ static ErlDrvSSizeT inet_ctl_fdopen(inet
 	sz = sizeof(name);
 	if (!IS_SOCKET_ERROR(sock_peer(s, (struct sockaddr*) &name, &sz))) {
 	    desc->state = INET_STATE_CONNECTED;
-#ifdef __OSE__
-            /* since we are dealing with different descriptors (i.e. inet and
-               socket) the select part should be initialized with the right
-               values */
-            inet_select_init(desc);
-#endif
         }
     }
 
@@ -8414,15 +8100,6 @@ static ErlDrvData inet_start(ErlDrvPort
 #ifdef HAVE_SETNS
     desc->netns = NULL;
 #endif
-#ifdef __OSE__
-    desc->select_state = 0;
-    desc->events[0] = NULL;
-    desc->events[1] = NULL;
-    desc->events[2] = NULL;
-    desc->events[3] = NULL;
-    desc->events[4] = NULL;
-    desc->events[5] = NULL;
-#endif
 
     return (ErlDrvData)desc;
 }
@@ -9149,10 +8826,6 @@ static tcp_descriptor* tcp_inet_copy(tcp
     copy_desc->inet.port = port;
     copy_desc->inet.dport = driver_mk_port(port);
 
-#ifdef __OSE__
-    inet_select_init(&copy_desc->inet);
-#endif
-
     *err = 0;
     return copy_desc;
 }
@@ -9214,23 +8887,6 @@ static void tcp_inet_stop(ErlDrvData e)
     inet_stop(INETP(desc));
 }
 
-#ifdef __OSE__
-
-static ErlDrvSSizeT tcp_inet_ctl_ose(ErlDrvData e, unsigned int cmd,
-				     char* buf, ErlDrvSizeT len,
-				     char** rbuf, ErlDrvSizeT rsize) {
-
-  tcp_descriptor* desc = (tcp_descriptor*)e;
-  int prev_select_state = INETP(desc)->select_state;
-
-  ErlDrvSSizeT res = tcp_inet_ctl(e,cmd,buf,len,rbuf,rsize);
-
-  tcp_inet_ose_dispatch_signals((tcp_descriptor*)e,prev_select_state,NULL);
-
-  return res;
-}
-#endif
-
 /* TCP requests from Erlang */
 static ErlDrvSSizeT tcp_inet_ctl(ErlDrvData e, unsigned int cmd,
 				 char* buf, ErlDrvSizeT len,
@@ -9672,17 +9328,6 @@ static void tcp_inet_command(ErlDrvData
     DEBUGF(("tcp_inet_command(%ld) }\r\n", (long)desc->inet.port)); 
 }
 
-#ifdef __OSE__
-
-static void tcp_inet_commandv_ose(ErlDrvData e, ErlIOVec* ev) {
-  int prev_select_state = INETP((tcp_descriptor*)e)->select_state;
-  tcp_inet_commandv(e, ev);
-  tcp_inet_ose_dispatch_signals((tcp_descriptor*)e,prev_select_state,NULL);
-}
-
-#endif
-
-
 static void tcp_inet_commandv(ErlDrvData e, ErlIOVec* ev)
 {
     tcp_descriptor* desc = (tcp_descriptor*)e;
@@ -9755,22 +9400,6 @@ static void inet_stop_select(ErlDrvEvent
 {
 #ifdef __WIN32__
     WSACloseEvent((HANDLE)event);
-#elif defined(__OSE__)
-    ErlDrvOseEventId id;
-    union SIGNAL *sig;
-    erl_drv_ose_event_fetch(event, NULL, &id,NULL);
-    DEBUGF(("inet_stop_select(?#?) {s=%d\n",id));
-    sock_close((int)id);
-    /* On socket close all the signals waiting to be processed as part of the
-       select should be deallocated */
-    while((sig = erl_drv_ose_get_signal(event))) {
-      DEBUGF(("inet_stop_select(?#?): Freeing signal %s\n",
-	      signo_to_string(sig->signo)));
-      free_buf(&sig);
-    }
-    erl_drv_ose_event_free(event);
-    DEBUGF(("inet_stop_select(?#?) }\n"));
-      
 #else
     sock_close((SOCKET)(long)event);
 #endif
@@ -10319,146 +9948,7 @@ static void tcp_inet_event(ErlDrvData e,
     return;
 }
 
-#elif defined(__OSE__) /* !__WIN32__ */
-/* The specific resolve signal function. It will return the socket descriptor
-   for which the select was issued */
-static ErlDrvOseEventId inet_resolve_signal(union SIGNAL *sig) {
-  DEBUGF(("%s(?#?): s=%d got signal %s, status = %d, extra = %d, sender = 0x%x\n",
-	  __FUNCTION__,sig->async.fd,signo_to_string(sig->signo),
-	  sig->async.event.status,
-	  sig->async.event.extra,sender(&sig)));
-  if (sig->signo == SO_EVENT_READ_REPLY ||
-      sig->signo == SO_EVENT_ACCEPT_REPLY ||
-      sig->signo == SO_EVENT_EOF_REPLY ||
-      sig->signo == SO_EVENT_WRITE_REPLY ||
-      sig->signo == SO_EVENT_ERROR_REPLY ||
-      sig->signo == SO_EVENT_CONNECT_REPLY ) {
-    return sig->async.fd;
-  }
-
-  return -1;
-}
-
-static void inet_driver_select(inet_descriptor* desc,
-			       int flags, int onoff) {
-    ASSERT(!desc->is_ignored);
-
-    if(onoff) {
-      desc->select_state |= flags;
-    } else {
-      desc->select_state &= ~flags;
-    }
-}
-
-static ssize_t writev_fallback(int fd, const struct iovec *iov, int iovcnt, int max_sz)
-{
-    size_t data_len = 0;
-    size_t sent = 0;
-    ssize_t n;
-    int i;
-
-    for(i = 0; i < iovcnt; i++)
-    {
-        data_len = iov[i].iov_len;
-tryagain:        
-        n = sock_send(fd, iov[i].iov_base, data_len, 0);
-        if (IS_SOCKET_ERROR(n)) {
-            /* If buffer length is greater than the amount stack is able to
-             * send out then try to send at least max_sz (this comes with
-             * SO_EVENT_WRITE_REPLY signal*/
-            if ((errno == EMSGSIZE) && (max_sz > 0) && (data_len > max_sz)) {
-                data_len = max_sz;
-                goto tryagain;
-            }
-            break;
-        }
-        sent += n;
-    }
-    return sent;
-}
-
-#define OSE_EVENT_REQ(TCP_DESC,EVENT) do {				\
-    union SIGNAL *sig = alloc(sizeof(struct OseAsyncSig), EVENT);	\
-    sig->async.fd = INETP(TCP_DESC)->s;					\
-    ose_request_event(INETP(TCP_DESC)->s, &sig, 1);			\
-    DEBUGF(("%s(%ld): s=%d sent %s\r\n",__FUNCTION__,			\
-      INETP(TCP_DESC)->port,INETP(TCP_DESC)->s,signo_to_string(EVENT))); \
-  } while(0)
-
-static void tcp_inet_ose_dispatch_signals(tcp_descriptor *desc,
-					  int prev_select_state,
-					  union SIGNAL *sig) {
-  if (sig) {
-    DEBUGF(("tcp_inet_ose_dispatch_signals(%ld) {s=%d resend\r\n",
-	    (long)INETP(desc)->port,INETP(desc)->s));
-    /* We are reacting to a signal, which means that if
-       the select_state for that signal is still activated
-       we should send a new signal */
-    switch (sig->signo) {
-    case SO_EVENT_READ_REPLY: {
-      if (INETP(desc)->select_state & FD_READ)
-	OSE_EVENT_REQ(desc,SO_EVENT_READ_REQUEST);
-      break;
-    }
-    case SO_EVENT_WRITE_REPLY: {
-      if (INETP(desc)->select_state & FD_WRITE)
-	OSE_EVENT_REQ(desc,SO_EVENT_WRITE_REQUEST);
-      break;
-    }
-    case SO_EVENT_CONNECT_REPLY: {
-      if (INETP(desc)->select_state & FD_CONNECT)
-	OSE_EVENT_REQ(desc,SO_EVENT_CONNECT_REQUEST);
-      break;
-    }
-    case SO_EVENT_ACCEPT_REPLY: {
-      if (INETP(desc)->select_state & FD_ACCEPT)
-	OSE_EVENT_REQ(desc,SO_EVENT_ACCEPT_REQUEST);
-      break;
-    }
-    case SO_EVENT_ERROR_REPLY: {
-      if (INETP(desc)->select_state & SOCK_FD_ERROR)
-	OSE_EVENT_REQ(desc,SO_EVENT_ERROR_REQUEST);
-      break;
-    }
-
-    }
-    DEBUGF(("tcp_inet_ose_dispatch_signals(%ld) }\r\n",
-	    (long)INETP(desc)->port));
-  }
-
-  if (INETP(desc)->select_state != prev_select_state) {
-    /* If the select state has changed we have to issue signals for
-       the state parts that have changed. */
-    int xor_select_state = INETP(desc)->select_state ^ prev_select_state;
-    DEBUGF(("tcp_inet_ose_dispatch_signals(%ld) {s=%d select change\r\n",
-	    (long)INETP(desc)->port,INETP(desc)->s));
-    if ((xor_select_state & FD_READ) &&
-	(INETP(desc)->select_state & FD_READ)) {
-      OSE_EVENT_REQ(desc,SO_EVENT_READ_REQUEST);
-    }
-    if ((xor_select_state & FD_WRITE) &&
-	(INETP(desc)->select_state & FD_WRITE)) {
-      OSE_EVENT_REQ(desc,SO_EVENT_WRITE_REQUEST);
-    }
-    if ((xor_select_state & FD_CONNECT) &&
-	(INETP(desc)->select_state & FD_CONNECT)) {
-      OSE_EVENT_REQ(desc,SO_EVENT_CONNECT_REQUEST);
-    }
-    if ((xor_select_state & FD_ACCEPT) &&
-	(INETP(desc)->select_state & FD_ACCEPT)) {
-      OSE_EVENT_REQ(desc,SO_EVENT_ACCEPT_REQUEST);
-    }
-    if ((xor_select_state & SOCK_FD_ERROR) &&
-	(INETP(desc)->select_state & SOCK_FD_ERROR)) {
-      OSE_EVENT_REQ(desc,SO_EVENT_ERROR_REQUEST);
-    }
-
-    DEBUGF(("tcp_inet_ose_dispatch_signals(%ld) }\r\n",
-	    (long)INETP(desc)->port));
-  }
-}
-
-#endif /* __OSE__ */
+#endif /* __WIN32__ */
 
 
 /* socket has input:
@@ -10945,49 +10435,6 @@ static void tcp_shutdown_async(tcp_descr
 	desc->tcp_add_flags |= TCP_ADDF_SHUTDOWN_WR_DONE;
 }
 
-#ifdef __OSE__
-
-static void tcp_inet_drv_output_ose(ErlDrvData data, ErlDrvEvent event)
-{
-  union SIGNAL *event_sig = erl_drv_ose_get_signal(event);
-
-  while (event_sig) {
-      int prev_select_state = INETP((tcp_descriptor*)data)->select_state;
-      int res = tcp_inet_output((tcp_descriptor*)data, (HANDLE)event_sig);
-      if (res != -1) {
-	tcp_inet_ose_dispatch_signals((tcp_descriptor*)data,
-				      prev_select_state,event_sig);
-	free_buf(&event_sig);
-	event_sig = erl_drv_ose_get_signal(event);
-      } else {
-	/* NOTE: here the event object could have been deallocated!!!!
-	   inet_stop_select is called when doing driver_select(ERL_DRV_USE,0)
-	 */
-	free_buf(&event_sig);
-	return;
-      }
-  }
-}
-
-static void tcp_inet_drv_input_ose(ErlDrvData data, ErlDrvEvent event)
-{
-  union SIGNAL *event_sig = erl_drv_ose_get_signal(event);
-
-  while (event_sig) {
-    int prev_select_state = INETP((tcp_descriptor*)data)->select_state;
-    int res = tcp_inet_input((tcp_descriptor*)data, (HANDLE)event);
-    if (res != -1) {
-      tcp_inet_ose_dispatch_signals((tcp_descriptor*)data, prev_select_state,
-				    event_sig);
-      free_buf(&event_sig);
-      event_sig = erl_drv_ose_get_signal(event);
-    } else {
-      free_buf(&event_sig);
-      return;
-    }
-  }
-}
-#else
 static void tcp_inet_drv_output(ErlDrvData data, ErlDrvEvent event)
 {
     (void)tcp_inet_output((tcp_descriptor*)data, (HANDLE)event);
@@ -10997,7 +10444,6 @@ static void tcp_inet_drv_input(ErlDrvDat
 {
     (void)tcp_inet_input((tcp_descriptor*)data, (HANDLE)event);
 }
-#endif
 
 /* socket ready for ouput:
 ** 1. INET_STATE_CONNECTING => non block connect ?
@@ -11063,13 +10509,6 @@ static int tcp_inet_output(tcp_descripto
 	    ssize_t n;
 	    SysIOVec* iov;
 
-#ifdef __OSE__
-            /* For large size buffers case the amount of data that the stack is
-               able to send out (received in the .extra field) should be passed
-               down to writev_fallback */
-            n = event ? ((union SIGNAL*)event)->async.event.extra : 0;
-#endif
-
 	    if ((iov = driver_peekq(ix, &vsize)) == NULL) {
 		sock_select(INETP(desc), FD_WRITE, 0);
 		send_empty_out_q_msgs(INETP(desc));
@@ -11097,12 +10536,6 @@ static int tcp_inet_output(tcp_descripto
 				    sizes > (max 32 bit signed int) */
 	      size_t howmuch = 0x7FFFFFFF; /* max signed 32 bit */
 	      int x;
-#ifdef __OSE__
-              /* For EWOULDBLOCK sock_sendv returns 0 so we have to be sure it
-                 wasn't the case */
-              if(sock_errno() == ERRNO_BLOCK) 
-                    goto done;
-#endif
 	      for(x = 0; x < vsize && iov[x].iov_len == 0; ++x)
 		;
 	      if (x < vsize) {
diff -Ndurp otp_src_18.3.4.5/erts/emulator/drivers/ose/ose_efile.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/ose/ose_efile.c
--- otp_src_18.3.4.5/erts/emulator/drivers/ose/ose_efile.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/ose/ose_efile.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,1125 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 1997-2012. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Purpose: Provides file and directory operations for OSE.
- */
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-#if defined(HAVE_POSIX_FALLOCATE) && !defined(__sun) && !defined(__sun__)
-#define _XOPEN_SOURCE 600
-#endif
-#if !defined(_GNU_SOURCE) && defined(HAVE_LINUX_FALLOC_H)
-#define _GNU_SOURCE
-#endif
-#include "sys.h"
-#include "erl_driver.h"
-#include "erl_efile.h"
-#if defined(DARWIN) || defined(HAVE_LINUX_FALLOC_H) || defined(HAVE_POSIX_FALLOCATE)
-#include "fcntl.h"
-#endif
-#include "ose.h"
-#include "unistd.h"
-#include "sys/stat.h"
-#include "dirent.h"
-#include "sys/time.h"
-#include "time.h"
-#include "assert.h"
-
-/* Find a definition of MAXIOV, that is used in the code later. */
-#if defined IOV_MAX
-#define MAXIOV IOV_MAX
-#elif defined UIO_MAXIOV
-#define MAXIOV UIO_MAXIOV
-#else
-#define MAXIOV 16
-#endif
-
-/*
- * Macros for testing file types.
- */
-
-#define ISDIR(st) (((st).st_mode & S_IFMT) == S_IFDIR)
-#define ISREG(st) (((st).st_mode & S_IFMT) == S_IFREG)
-#define ISDEV(st) \
-    (((st).st_mode&S_IFMT) == S_IFCHR || ((st).st_mode&S_IFMT) == S_IFBLK)
-#define ISLNK(st) (((st).st_mode & S_IFLNK) == S_IFLNK)
-#ifdef NO_UMASK
-#define FILE_MODE 0644
-#define DIR_MODE  0755
-#else
-#define FILE_MODE 0666
-#define DIR_MODE  0777
-#endif
-
-#define IS_DOT_OR_DOTDOT(s) \
-    (s[0] == '.' && (s[1] == '\0' || (s[1] == '.' && s[2] == '\0')))
-
-/*
- * Macros for handling local file descriptors
- * and mutexes.
- *
- * Handling of files like this is necessary because OSE
- * does not allow seeking after the end of a file. So
- * what we do it emulate this by keeping track of the size
- * of the file and where the file's positions is. If a
- * write happens after eof then we pad it.
- *
- * Given time this should be rewritten to get rid of the
- * mutex and use the port lock to protect the data. This
- * could be done be done by adapting the efile api for some
- * calls to allow some meta-data to be associated with the
- * open file.
- */
-
-#define L_FD_IS_VALID(fd_data) ((fd_data)->beyond_eof > 0)
-#define L_FD_INVALIDATE(fd_data) (fd_data)->beyond_eof = 0
-#define L_FD_CUR(fd_data) (fd_data)->pos
-#define L_FD_OFFS_BEYOND_EOF(fd_data, offs) \
-    (((fd_data)->size > offs) ? 0 : 1)
-
-#define L_FD_FAIL -1
-#define L_FD_SUCCESS 1
-#define L_FD_PAD_SIZE 255
-
-struct fd_meta {
-    ErlDrvMutex *meta_mtx;
-    struct fd_data *fd_data_list;
-};
-
-struct fd_data {
-    int fd;
-    struct fd_data *next;
-    struct fd_data *prev;
-    int pos;
-    int beyond_eof;
-    size_t size;
-#ifdef DEBUG
-    PROCESS owner;
-#endif
-};
-
-static int l_invalidate_local_fd(int fd);
-static int l_pad_file(struct fd_data *fd_data, off_t offset);
-static int check_error(int result, Efile_error* errInfo);
-static struct fd_data* l_new_fd(void);
-static int l_remove_local_fd(int fd);
-static struct fd_data* l_find_local_fd(int fd);
-static int l_update_local_fd(int fd, int pos, int size);
-
-static struct fd_meta* fdm = NULL;
-
-
-/***************************************************************************/
-
-static int
-l_remove_local_fd(int fd)
-{
-    struct fd_data *fd_data;
-    fd_data = l_find_local_fd(fd);
-
-    if (fd_data == NULL) {
-        return L_FD_FAIL;
-    }
-#ifdef DEBUG
-    assert(fd_data->owner == current_process());
-#endif
-    erl_drv_mutex_lock(fdm->meta_mtx);
-    /* head ? */
-    if (fd_data == fdm->fd_data_list) {
-        if (fd_data->next != NULL) {
-            /* remove link to head */
-            fd_data->next->prev = NULL;
-            /* set new head */
-            fdm->fd_data_list = fd_data->next;
-        }
-        else {
-            /* head is lonely */
-            fdm->fd_data_list = NULL;
-        }
-    }
-    else { /* not head */
-        if (fd_data->prev == NULL) {
-            erl_drv_mutex_unlock(fdm->meta_mtx);
-            return L_FD_FAIL;
-        }
-        else {
-            if (fd_data->next != NULL) {
-                fd_data->next->prev = fd_data->prev;
-                fd_data->prev->next = fd_data->next;
-            }
-            else {
-                fd_data->prev->next = NULL;
-            }
-        }
-    }
-
-    /* scramble values */
-    fd_data->beyond_eof = -1;
-    fd_data->next = NULL;
-    fd_data->prev = NULL;
-    fd_data->fd = -1;
-
-    /* unlock and clean */
-    driver_free(fd_data);
-    erl_drv_mutex_unlock(fdm->meta_mtx);
-
-    return L_FD_SUCCESS;
-}
-
-/***************************************************************************/
-
-static int
-l_invalidate_local_fd(int fd) {
-    struct fd_data *fd_data;
-
-    if ((fd_data = l_find_local_fd(fd)) == NULL) {
-        return L_FD_FAIL;
-    }
-
-    fd_data->beyond_eof = 0;
-    return L_FD_SUCCESS;
-}
-
-/****************************************************************************/
-
-static struct fd_data*
-l_find_local_fd(int fd) {
-    struct fd_data *fd_data;
-
-    fd_data = NULL;
-    erl_drv_mutex_lock(fdm->meta_mtx);
-    for (fd_data = fdm->fd_data_list; fd_data != NULL; ) {
-        if (fd_data->fd == fd) {
-#ifdef DEBUG
-            assert(fd_data->owner == current_process());
-#endif
-            break;
-        }
-        fd_data = fd_data->next;
-    }
-    erl_drv_mutex_unlock(fdm->meta_mtx);
-    return fd_data;
-}
-
-/***************************************************************************/
-
-static struct fd_data*
-l_new_fd(void) {
-    struct fd_data *fd_data;
-
-    fd_data = driver_alloc(sizeof(struct fd_data));
-    if (fd_data == NULL) {
-        return NULL;
-    }
-    erl_drv_mutex_lock(fdm->meta_mtx);
-    if (fdm->fd_data_list == NULL) {
-        fdm->fd_data_list = fd_data;
-        fdm->fd_data_list->prev = NULL;
-        fdm->fd_data_list->next = NULL;
-    }
-    else {
-        fd_data->next = fdm->fd_data_list;
-        fdm->fd_data_list = fd_data;
-        fdm->fd_data_list->prev = NULL;
-    }
-#ifdef DEBUG
-    fd_data->owner = current_process();
-#endif
-    erl_drv_mutex_unlock(fdm->meta_mtx);
-    return fd_data;
-}
-
-/***************************************************************************/
-
-static int
-l_update_local_fd(int fd, int pos, int size) {
-    struct fd_data *fd_data = NULL;
-
-    fd_data = l_find_local_fd(fd);
-    /* new fd to handle? */
-    if (fd_data == NULL) {
-        fd_data = l_new_fd();
-        if (fd_data == NULL) {
-            /* out of memory */
-            return L_FD_FAIL;
-        }
-    }
-    fd_data->size = size;
-    fd_data->pos = pos;
-    fd_data->fd = fd;
-    fd_data->beyond_eof = 1;
-
-    return L_FD_SUCCESS;
-}
-
-/***************************************************************************/
-
-static int
-l_pad_file(struct fd_data *fd_data, off_t offset) {
-    int size_dif;
-    int written = 0;
-    int ret_val = L_FD_SUCCESS;
-    char padding[L_FD_PAD_SIZE];
-
-    size_dif = (offset - fd_data->size);
-    memset(&padding, '\0', L_FD_PAD_SIZE);
-
-    while (size_dif > 0) {
-        written = write(fd_data->fd, padding,
-                (size_dif < L_FD_PAD_SIZE) ?
-                size_dif : L_FD_PAD_SIZE);
-        if (written < 0 && errno != EINTR && errno != EAGAIN) {
-            ret_val = -1;
-            break;
-        }
-        size_dif -= written;
-    }
-    L_FD_INVALIDATE(fd_data);
-    return ret_val;
-}
-
-/***************************************************************************/
-
-static int
-check_error(int result, Efile_error *errInfo) {
-    if (result < 0) {
-        errInfo->posix_errno = errInfo->os_errno = errno;
-        return 0;
-    }
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_init() {
-    fdm = driver_alloc(sizeof(struct fd_meta));
-    if (fdm == NULL) {
-        return L_FD_FAIL;
-    }
-    fdm->meta_mtx = erl_drv_mutex_create("ose_efile local fd mutex\n");
-    erl_drv_mutex_lock(fdm->meta_mtx);
-    fdm->fd_data_list = NULL;
-    erl_drv_mutex_unlock(fdm->meta_mtx);
-    return L_FD_SUCCESS;
-}
-
-/***************************************************************************/
-
-int
-efile_mkdir(Efile_error* errInfo,       /* Where to return error codes. */
-        char* name)                 /* Name of directory to create. */
-{
-#ifdef NO_MKDIR_MODE
-    return check_error(mkdir(name), errInfo);
-#else
-    int res = mkdir(name, DIR_MODE);
-    if (res < 0 && errno == EINVAL) {
-      errno = ENOENT;
-    }
-    return check_error(res, errInfo);
-#endif
-}
-
-/***************************************************************************/
-
-int
-efile_rmdir(Efile_error* errInfo,       /* Where to return error codes. */
-        char* name)                 /* Name of directory to delete. */
-{
-    if (rmdir(name) == 0) {
-        return 1;
-    }
-    if (errno == ENOTEMPTY) {
-        errno = EEXIST;
-    }
-    if (errno == EEXIST || errno == EINVAL) {
-        int saved_errno = errno;
-        struct stat file_stat;
-        struct stat cwd_stat;
-
-        if(stat(name, &file_stat) != 0) {
-            errno = ENOENT;
-            return check_error(-1, errInfo);
-        }
-        /*
-         *  The error code might be wrong if this is the current directory.
-         */
-        if (stat(name, &file_stat) == 0 && stat(".", &cwd_stat) == 0 &&
-                file_stat.st_ino == cwd_stat.st_ino &&
-                file_stat.st_dev == cwd_stat.st_dev) {
-            saved_errno = EACCES;
-        }
-        errno = saved_errno;
-    }
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_delete_file(Efile_error* errInfo, /* Where to return error codes. */
-        char* name)           /* Name of file to delete. */
-{
-    struct stat statbuf;
-
-    if (stat(name, &statbuf) >= 0) {
-        /* Do not let unlink() remove directories */
-        if (ISDIR(statbuf)) {
-            errno = EPERM;
-            return check_error(-1, errInfo);
-        }
-
-        if (unlink(name) == 0) {
-            return 1;
-        }
-
-        if (errno == EISDIR) {
-            errno = EPERM;
-            return check_error(-1, errInfo);
-        }
-    }
-    else {
-        if (errno == EINVAL) {
-            errno = ENOENT;
-            return check_error(-1, errInfo);
-        }
-    }
-    return check_error(-1, errInfo);
-}
-
-/*
- *---------------------------------------------------------------------------
- *
- *      Changes the name of an existing file or directory, from src to dst.
- *      If src and dst refer to the same file or directory, does nothing
- *      and returns success.  Otherwise if dst already exists, it will be
- *      deleted and replaced by src subject to the following conditions:
- *          If src is a directory, dst may be an empty directory.
- *          If src is a file, dst may be a file.
- *      In any other situation where dst already exists, the rename will
- *      fail.
- *
- * Results:
- *      If the directory was successfully created, returns 1.
- *      Otherwise the return value is 0 and errno is set to
- *      indicate the error.  Some possible values for errno are:
- *
- *      EACCES:     src or dst parent directory can't be read and/or written.
- *      EEXIST:     dst is a non-empty directory.
- *      EINVAL:     src is a root directory or dst is a subdirectory of src.
- *      EISDIR:     dst is a directory, but src is not.
- *      ENOENT:     src doesn't exist, or src or dst is "".
- *      ENOTDIR:    src is a directory, but dst is not.
- *      EXDEV:      src and dst are on different filesystems.
- *
- * Side effects:
- *      The implementation of rename may allow cross-filesystem renames,
- *      but the caller should be prepared to emulate it with copy and
- *      delete if errno is EXDEV.
- *
- *---------------------------------------------------------------------------
- */
-
-int
-efile_rename(Efile_error* errInfo,      /* Where to return error codes. */
-        char* src,                 /* Original name. */
-        char* dst)                 /* New name. */
-{
-
-    /* temporary fix AFM does not recognize ./<file name>
-     * in destination remove pending on adaption of AFM fix
-     */
-
-    char *dot_str;
-    if (dst != NULL) {
-        dot_str = strchr(dst, '.');
-        if (dot_str && dot_str == dst && dot_str[1] == '/') {
-            dst = dst+2;
-        }
-    }
-
-    if (rename(src, dst) == 0) {
-        return 1;
-    }
-    if (errno == ENOTEMPTY) {
-        errno = EEXIST;
-    }
-    if (errno == EINVAL) {
-        struct stat file_stat;
-
-        if (stat(dst, &file_stat)== 0) {
-            if (ISDIR(file_stat)) {
-                errno = EISDIR;
-            }
-            else if (ISREG(file_stat)) {
-                errno = ENOTDIR;
-            }
-            else {
-                errno = EINVAL;
-            }
-        }
-        else {
-            errno = EINVAL;
-        }
-    }
-
-    if (strcmp(src, "/") == 0) {
-        errno = EINVAL;
-    }
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_chdir(Efile_error* errInfo,   /* Where to return error codes. */
-        char* name)             /* Name of directory to make current. */
-{
-    return check_error(chdir(name), errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_getdcwd(Efile_error* errInfo,     /* Where to return error codes. */
-        int drive,                /* 0 - current, 1 - A, 2 - B etc. */
-        char* buffer,             /* Where to return the current
-                                     directory. */
-        size_t size)              /* Size of buffer. */
-{
-    if (drive == 0) {
-        if (getcwd(buffer, size) == NULL)
-            return check_error(-1, errInfo);
-
-        return 1;
-    }
-
-    /*
-     * Drives other than 0 is not supported on Unix.
-     */
-
-    errno = ENOTSUP;
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_readdir(Efile_error* errInfo,     /* Where to return error codes. */
-        char* name,               /* Name of directory to open. */
-        EFILE_DIR_HANDLE* p_dir_handle,   /* Pointer to directory
-                                             handle of
-                                             open directory.*/
-        char* buffer,             /* Pointer to buffer for
-                                     one filename. */
-        size_t *size)             /* in-out Size of buffer, length
-                                     of name. */
-{
-    DIR *dp;                    /* Pointer to directory structure. */
-    struct dirent* dirp;        /* Pointer to directory entry. */
-
-    /*
-     * If this is the first call, we must open the directory.
-     */
-
-    if (*p_dir_handle == NULL) {
-        dp = opendir(name);
-        if (dp == NULL)
-            return check_error(-1, errInfo);
-        *p_dir_handle = (EFILE_DIR_HANDLE) dp;
-    }
-
-    /*
-     * Retrieve the name of the next file using the directory handle.
-     */
-
-    dp = *((DIR **)((void *)p_dir_handle));
-    for (;;) {
-        dirp = readdir(dp);
-        if (dirp == NULL) {
-            closedir(dp);
-            return 0;
-        }
-        if (IS_DOT_OR_DOTDOT(dirp->d_name))
-            continue;
-        buffer[0] = '\0';
-        strncat(buffer, dirp->d_name, (*size)-1);
-        *size = strlen(dirp->d_name);
-        return 1;
-    }
-}
-
-/***************************************************************************/
-
-int
-efile_openfile(Efile_error* errInfo,    /* Where to return error codes. */
-        char* name,              /* Name of directory to open. */
-        int flags,               /* Flags to user for opening. */
-        int* pfd,                /* Where to store the file
-                                    descriptor. */
-        Sint64 *pSize)           /* Where to store the size of the
-                                    file. */
-{
-    struct stat statbuf;
-    int fd;
-    int mode;                   /* Open mode. */
-
-    if (stat(name, &statbuf) >= 0 && !ISREG(statbuf)) {
-        errno = EISDIR;
-        return check_error(-1, errInfo);
-    }
-
-    switch (flags & (EFILE_MODE_READ|EFILE_MODE_WRITE)) {
-        case EFILE_MODE_READ:
-            mode = O_RDONLY;
-            break;
-        case EFILE_MODE_WRITE:
-            if (flags & EFILE_NO_TRUNCATE)
-                mode = O_WRONLY | O_CREAT;
-            else
-                mode = O_WRONLY | O_CREAT | O_TRUNC;
-            break;
-        case EFILE_MODE_READ_WRITE:
-            mode = O_RDWR | O_CREAT;
-            break;
-        default:
-            errno = EINVAL;
-            return check_error(-1, errInfo);
-    }
-
-
-    if (flags & EFILE_MODE_APPEND) {
-        mode &= ~O_TRUNC;
-        mode |= O_APPEND;
-    }
-
-    if (flags & EFILE_MODE_EXCL) {
-        mode |= O_EXCL;
-    }
-
-    fd = open(name, mode, FILE_MODE);
-
-    if (!check_error(fd, errInfo))
-        return 0;
-
-    *pfd = fd;
-    if (pSize) {
-        *pSize = statbuf.st_size;
-    }
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_may_openfile(Efile_error* errInfo, char *name) {
-    struct stat statbuf;        /* Information about the file */
-    int result;
-
-    result = stat(name, &statbuf);
-    if (!check_error(result, errInfo))
-        return 0;
-    if (!ISREG(statbuf)) {
-        errno = EISDIR;
-        return check_error(-1, errInfo);
-    }
-    return 1;
-}
-
-/***************************************************************************/
-
-void
-efile_closefile(int fd)
-{
-    if (l_find_local_fd(fd) != NULL) {
-        l_remove_local_fd(fd);
-    }
-    close(fd);
-}
-
-/***************************************************************************/
-
-int
-efile_fdatasync(Efile_error *errInfo, /* Where to return error codes. */
-        int fd)               /* File descriptor for file to sync data. */
-{
-    return efile_fsync(errInfo, fd);
-}
-
-/***************************************************************************/
-
-int
-efile_fsync(Efile_error *errInfo, /* Where to return error codes. */
-        int fd)               /* File descriptor for file to sync. */
-{
-    return check_error(fsync(fd), errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_fileinfo(Efile_error* errInfo, Efile_info* pInfo,
-        char* name, int info_for_link)
-{
-    struct stat statbuf;        /* Information about the file */
-    int result;
-
-    result = stat(name, &statbuf);
-    if (!check_error(result, errInfo)) {
-        return 0;
-    }
-
-#if SIZEOF_OFF_T == 4
-    pInfo->size_high = 0;
-#else
-    pInfo->size_high = (Uint32)(statbuf.st_size >> 32);
-#endif
-    pInfo->size_low = (Uint32)statbuf.st_size;
-
-#ifdef NO_ACCESS
-    /* Just look at read/write access for owner. */
-
-    pInfo->access = ((statbuf.st_mode >> 6) & 07) >> 1;
-
-#else
-    pInfo->access = FA_NONE;
-    if (access(name, R_OK) == 0)
-        pInfo->access |= FA_READ;
-    if (access(name, W_OK) == 0)
-        pInfo->access |= FA_WRITE;
-
-#endif
-
-    if (ISDEV(statbuf))
-        pInfo->type = FT_DEVICE;
-    else if (ISDIR(statbuf))
-        pInfo->type = FT_DIRECTORY;
-    else if (ISREG(statbuf))
-        pInfo->type = FT_REGULAR;
-    else if (ISLNK(statbuf))
-        pInfo->type = FT_SYMLINK;
-    else
-        pInfo->type = FT_OTHER;
-
-    pInfo->accessTime   = statbuf.st_atime;
-    pInfo->modifyTime   = statbuf.st_mtime;
-    pInfo->cTime        = statbuf.st_ctime;
-
-    pInfo->mode         = statbuf.st_mode;
-    pInfo->links        = statbuf.st_nlink;
-    pInfo->major_device = statbuf.st_dev;
-    pInfo->inode        = statbuf.st_ino;
-    pInfo->uid          = statbuf.st_uid;
-    pInfo->gid          = statbuf.st_gid;
-
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_write_info(Efile_error *errInfo, Efile_info *pInfo, char *name)
-{
-    /*
-     * On some systems chown will always fail for a non-root user unless
-     * POSIX_CHOWN_RESTRICTED is not set.  Others will succeed as long as
-     * you don't try to chown a file to someone besides youself.
-     */
-    if (pInfo->mode != -1) {
-        mode_t newMode = pInfo->mode & (S_ISUID | S_ISGID |
-                S_IRWXU | S_IRWXG | S_IRWXO);
-        if (chmod(name, newMode)) {
-            newMode &= ~(S_ISUID | S_ISGID);
-            if (chmod(name, newMode)) {
-                return check_error(-1, errInfo);
-            }
-        }
-    }
-
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_write(Efile_error* errInfo,       /* Where to return error codes. */
-        int flags,                  /* Flags given when file was
-                                       opened. */
-        int fd,                     /* File descriptor to write to. */
-        char* buf,                  /* Buffer to write. */
-        size_t count)               /* Number of bytes to write. */
-{
-    ssize_t written;                    /* Bytes written in last operation. */
-    struct fd_data *fd_data;
-
-    if ((fd_data = l_find_local_fd(fd)) != NULL) {
-        if (L_FD_IS_VALID(fd_data)) {
-            /* we are beyond eof and need to pad*/
-            if (l_pad_file(fd_data, L_FD_CUR(fd_data)) < 0) {
-                return check_error(-1, errInfo);
-            }
-        }
-    }
-
-    while (count > 0)  {
-        if ((written = write(fd, buf, count)) < 0) {
-            if (errno != EINTR) {
-                return check_error(-1, errInfo);
-            }
-            else {
-                written = 0;
-            }
-        }
-        ASSERT(written <= count);
-        buf += written;
-        count -= written;
-    }
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_writev(Efile_error* errInfo,   /* Where to return error codes */
-        int flags,              /* Flags given when file was
-                                 * opened */
-        int fd,                 /* File descriptor to write to */
-        SysIOVec* iov,          /* Vector of buffer structs.
-                                 * The structs may be changed i.e.
-                                 * due to incomplete writes */
-        int iovcnt)             /* Number of structs in vector */
-{
-    struct fd_data *fd_data;
-    int cnt = 0;                     /* Buffers so far written */
-
-    ASSERT(iovcnt >= 0);
-    if ((fd_data = l_find_local_fd(fd)) != NULL) {
-        if (L_FD_IS_VALID(fd_data)) {
-            /* we are beyond eof and need to pad*/
-            if (l_pad_file(fd_data, L_FD_CUR(fd_data)) < 0) {
-                return check_error(-1, errInfo);
-            }
-        }
-    }
-    while (cnt < iovcnt) {
-        if ((! iov[cnt].iov_base) || (iov[cnt].iov_len <= 0)) {
-            /* Empty buffer - skip */
-            cnt++;
-        }
-        else { /* Non-empty buffer */
-            ssize_t w;                   /* Bytes written in this call */
-            do {
-                w = write(fd, iov[cnt].iov_base, iov[cnt].iov_len);
-            } while (w < 0 && errno == EINTR);
-
-            ASSERT(w <= iov[cnt].iov_len || w == -1);
-
-            if (w < 0) {
-                return check_error(-1, errInfo);
-            }
-            /* Move forward to next buffer to write */
-            for (; cnt < iovcnt && w > 0; cnt++) {
-                if (iov[cnt].iov_base && iov[cnt].iov_len > 0) {
-                    if (w < iov[cnt].iov_len) {
-                        /* Adjust the buffer for next write */
-                        iov[cnt].iov_len -= w;
-                        iov[cnt].iov_base += w;
-                        w = 0;
-                        break;
-                    }
-                    else {
-                        w -= iov[cnt].iov_len;
-                    }
-                }
-            }
-            ASSERT(w == 0);
-        } /* else Non-empty buffer */
-    } /* while (cnt< iovcnt) */
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_read(Efile_error* errInfo,     /* Where to return error codes. */
-        int flags,                  /* Flags given when file was opened. */
-        int fd,                     /* File descriptor to read from. */
-        char* buf,                  /* Buffer to read into. */
-        size_t count,       /* Number of bytes to read. */
-        size_t *pBytesRead)         /* Where to return number of
-                                       bytes read. */
-{
-    ssize_t n;
-    struct fd_data *fd_data;
-
-    if ((fd_data = l_find_local_fd(fd)) != NULL) {
-        if (L_FD_IS_VALID(fd_data)) {
-            *pBytesRead = 0;
-            return 1;
-        }
-    }
-    for (;;)  {
-        if ((n = read(fd, buf, count)) >= 0) {
-            break;
-        }
-        else if (errno != EINTR) {
-            return check_error(-1, errInfo);
-        }
-    }
-    if (fd_data != NULL && L_FD_IS_VALID(fd_data)) {
-        L_FD_INVALIDATE(fd_data);
-    }
-    *pBytesRead = (size_t) n;
-    return 1;
-}
-
-/* pread() and pwrite()                                                   */
-/* Some unix systems, notably Solaris has these syscalls                  */
-/* It is especially nice for i.e. the dets module to have support         */
-/* for this, even if the underlying OS dosn't support it, it is           */
-/* reasonably easy to work around by first calling seek, and then         */
-/* calling read().                                                        */
-/* This later strategy however changes the file pointer, which pread()    */
-/* does not do. We choose to ignore this and say that the location        */
-/* of the file pointer is undefined after a call to any of the p functions*/
-
-
-int
-efile_pread(Efile_error* errInfo,     /* Where to return error codes. */
-        int fd,                /* File descriptor to read from. */
-        Sint64 offset,            /* Offset in bytes from BOF. */
-        char* buf,                     /* Buffer to read into. */
-        size_t count,          /* Number of bytes to read. */
-        size_t *pBytesRead)            /* Where to return
-                                          number of bytes read. */
-{
-    int res = efile_seek(errInfo, fd, offset, EFILE_SEEK_SET, NULL);
-    if (res) {
-        return efile_read(errInfo, 0, fd, buf, count, pBytesRead);
-    } else {
-        return res;
-    }
-}
-
-
-/***************************************************************************/
-
-int
-efile_pwrite(Efile_error* errInfo,  /* Where to return error codes. */
-        int fd,                /* File descriptor to write to. */
-        char* buf,             /* Buffer to write. */
-        size_t count,          /* Number of bytes to write. */
-        Sint64 offset)         /* where to write it */
-{
-    int res = efile_seek(errInfo, fd, offset, EFILE_SEEK_SET, NULL);
-
-    if (res) {
-        return efile_write(errInfo, 0, fd, buf, count);
-    } else {
-        return res;
-    }
-}
-
-/***************************************************************************/
-
-int
-efile_seek(Efile_error* errInfo,      /* Where to return error codes. */
-        int fd,                    /* File descriptor to do the seek on. */
-        Sint64 offset,             /* Offset in bytes from the given
-                                      origin. */
-        int origin,                /* Origin of seek (SEEK_SET, SEEK_CUR,
-                                      SEEK_END). */
-        Sint64 *new_location)      /* Resulting new location in file. */
-{
-    off_t off, result;
-    off = (off_t) offset;
-
-    switch (origin) {
-        case EFILE_SEEK_SET:
-            origin = SEEK_SET;
-            break;
-        case EFILE_SEEK_CUR:
-            origin = SEEK_CUR;
-            break;
-        case EFILE_SEEK_END:
-            origin = SEEK_END;
-            break;
-        default:
-            errno = EINVAL;
-            return check_error(-1, errInfo);
-    }
-
-    if (off != offset) {
-        errno = EINVAL;
-        return check_error(-1, errInfo);
-    }
-
-    errno = 0;
-    result = lseek(fd, off, origin);
-
-    if (result >= 0) {
-        l_invalidate_local_fd(fd);
-    }
-
-    if (result < 0)
-    {
-        if (errno == ENOSYS) {
-            int size, cur_pos;
-
-            if (off < 0) {
-                errno = EINVAL;
-                return check_error(-1, errInfo);
-            }
-
-            cur_pos = lseek(fd, 0, SEEK_CUR);
-            size = lseek(fd, 0, SEEK_END);
-
-            if (origin == SEEK_SET) {
-                result = offset;
-            }
-            else if (origin == SEEK_CUR) {
-                result = offset + cur_pos;
-            }
-            else if (origin == SEEK_END) {
-                result = size + offset;
-            }
-
-            /* sanity check our result */
-            if (size > result) {
-                return check_error(-1, errInfo);
-            }
-
-            /* store the data localy */
-            l_update_local_fd(fd, result, size);
-
-            /* reset the original file position */
-            if (origin != SEEK_END) {
-                lseek(fd, cur_pos, SEEK_SET);
-            }
-        }
-        else if (errno == 0) {
-            errno = EINVAL;
-        }
-    }
-
-    if (new_location) {
-        *new_location = result;
-    }
-
-    return 1;
-}
-
-/***************************************************************************/
-
-int
-efile_truncate_file(Efile_error* errInfo, int *fd, int flags)
-{
-    off_t offset;
-    struct fd_data *fd_data;
-
-    if ((fd_data = l_find_local_fd(*fd)) != NULL && L_FD_IS_VALID(fd_data)) {
-        offset = L_FD_CUR(fd_data);
-    }
-    else {
-        offset = lseek(*fd, 0, SEEK_CUR);
-    }
-
-    return check_error(((offset >= 0) &&
-                (ftruncate(*fd, offset) == 0)) ? 1 : -1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_readlink(Efile_error* errInfo, char* name, char* buffer, size_t size)
-{
-    errno = ENOTSUP;
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_altname(Efile_error* errInfo, char* name, char* buffer, size_t size)
-{
-    errno = ENOTSUP;
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_link(Efile_error* errInfo, char* old, char* new)
-{
-    errno = ENOTSUP;
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_symlink(Efile_error* errInfo, char* old, char* new)
-{
-    errno = ENOTSUP;
-    return check_error(-1, errInfo);
-}
-
-/***************************************************************************/
-
-int
-efile_fadvise(Efile_error* errInfo, int fd, Sint64 offset,
-        Sint64 length, int advise)
-{
-    return check_error(posix_fadvise(fd, offset, length, advise), errInfo);
-}
-
-/***************************************************************************/
-
-static int
-call_posix_fallocate(int fd, Sint64 offset, Sint64 length)
-{
-    int ret;
-
-    /*
-     * On Linux and Solaris for example, posix_fallocate() returns
-     * a positive error number on error and it does not set errno.
-     * On FreeBSD however (9.0 at least), it returns -1 on error
-     * and it sets errno.
-     */
-    do {
-        ret = posix_fallocate(fd, (off_t) offset, (off_t) length);
-        if (ret > 0) {
-            errno = ret;
-            ret = -1;
-        }
-    } while (ret != 0 && errno == EINTR);
-
-    return ret;
-}
-
-/***************************************************************************/
-
-int
-efile_fallocate(Efile_error* errInfo, int fd, Sint64 offset, Sint64 length)
-{
-    return check_error(call_posix_fallocate(fd, offset, length), errInfo);
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/drivers/ose/ose_signal_drv.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/ose/ose_signal_drv.c
--- otp_src_18.3.4.5/erts/emulator/drivers/ose/ose_signal_drv.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/ose/ose_signal_drv.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,897 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2013-2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include "errno.h"
-#include "stdio.h"
-#include "string.h"
-#include "stddef.h"
-
-#include "sys.h"
-#include "erl_driver.h"
-#include "ose.h"
-
-
-#ifdef HAVE_OSE_SPI_H
-#include "ose_spi/ose_spi.h"
-#endif
-
-#define DEBUG_ATTACH   0
-#define DEBUG_HUNT     0
-#define DEBUG_SEND     0
-#define DEBUG_LISTEN   0
-
-#if 0
-#define DEBUGP(FMT,...) printf(FMT, __VA_ARGS__)
-#else
-#define DEBUGP(FMT,...)
-#endif
-
-#if DEBUG_ATTACH
-#define DEBUGP_ATTACH(...) DEBUGP( __VA_ARGS__)
-#else
-#define DEBUGP_ATTACH(...)
-#endif
-
-#if DEBUG_HUNT
-#define DEBUGP_HUNT(...) DEBUGP( __VA_ARGS__)
-#else
-#define DEBUGP_HUNT(...)
-#endif
-
-#if DEBUG_LISTEN
-#define DEBUGP_LISTEN(...) DEBUGP( __VA_ARGS__)
-#else
-#define DEBUGP_LISTEN(...)
-#endif
-
-#if DEBUG_SEND
-#define DEBUGP_SEND(...) DEBUGP( __VA_ARGS__)
-#else
-#define DEBUGP_SEND(...)
-#endif
-
-
-#define DRIVER_NAME "ose_signal_drv"
-#define GET_SPID        1
-#define GET_NAME        2
-#define HUNT          100
-#define DEHUNT        101
-#define ATTACH        102
-#define DETACH        103
-#define SEND          104
-#define SEND_W_S      105
-#define LISTEN        106
-#define OPEN          200
-
-#define REF_SEGMENT_SIZE 8
-
-struct async {
-  SIGSELECT signo;
-  ErlDrvTermData port;
-  ErlDrvTermData proc;
-  PROCESS spid;
-  PROCESS target;
-  Uint32 ref;
-};
-
-/**
- * OSE signals
- **/
-union SIGNAL {
-  SIGSELECT signo;
-  struct async async;
-};
-
-/**
- * The driver's context
- **/
-typedef struct _driver_context {
-  ErlDrvPort port;
-  PROCESS spid;
-  ErlDrvEvent perm_events[2];
-  ErlDrvEvent *events;
-  Uint32 event_cnt;
-  Uint32 ref;
-  Uint32 *outstanding_refs;
-  Uint32 outstanding_refs_max;
-  Uint32 outstanding_refs_cnt;
-} driver_context_t;
-
-/**
- * Global variables
- **/
-static ErlDrvTermData a_ok;
-static ErlDrvTermData a_error;
-static ErlDrvTermData a_enomem;
-static ErlDrvTermData a_enoent;
-static ErlDrvTermData a_badarg;
-static ErlDrvTermData a_mailbox_up;
-static ErlDrvTermData a_mailbox_down;
-static ErlDrvTermData a_ose_drv_reply;
-static ErlDrvTermData a_message;
-static PROCESS proxy_proc;
-
-
-/**
- * Serialize/unserialize unsigned 32-bit values
- **/
-static char *put_u32(unsigned int value, char *ptr) {
-  *ptr++ = (value & 0xff000000) >> 24;
-  *ptr++ = (value & 0x00ff0000) >> 16;
-  *ptr++ = (value & 0x0000ff00) >> 8;
-  *ptr++ = (value & 0xff);
-
-  return ptr;
-}
-
-static unsigned int get_u32(char *ptr) {
-  unsigned int result = 0;
-  result += (ptr[0] & 0xff) << 24;
-  result += (ptr[1] & 0xff) << 16;
-  result += (ptr[2] & 0xff) << 8;
-  result += (ptr[3] & 0xff);
-
-  return result;
-}
-
-
-/* Stolen from efile_drv.c */
-
-/* char EV_CHAR_P(ErlIOVec *ev, int p, int q) */
-#define EV_CHAR_P(ev, p, q)                   \
-    (((char *)(ev)->iov[(q)].iov_base) + (p))
-
-/* int EV_GET_CHAR(ErlIOVec *ev, char *p, int *pp, int *qp) */
-#define EV_GET_CHAR(ev, p, pp, qp) ev_get_char(ev, p ,pp, qp)
-static int
-ev_get_char(ErlIOVec *ev, char *p, int *pp, int *qp) {
-  if (*(pp)+1 <= (ev)->iov[*(qp)].iov_len) {
-    *(p) = *EV_CHAR_P(ev, *(pp), *(qp));
-    if (*(pp)+1 < (ev)->iov[*(qp)].iov_len)
-      *(pp) = *(pp)+1;
-    else {
-      (*(qp))++;
-      *pp = 0;
-    }
-    return !0;
-  }
-  return 0;
-}
-
-/* Uint32 EV_UINT32(ErlIOVec *ev, int p, int q)*/
-#define EV_UINT32(ev, p, q) \
-    ((Uint32) *(((unsigned char *)(ev)->iov[(q)].iov_base) + (p)))
-
-/* int EV_GET_UINT32(ErlIOVec *ev, Uint32 *p, int *pp, int *qp) */
-#define EV_GET_UINT32(ev, p, pp, qp) ev_get_uint32(ev,(Uint32*)(p),pp,qp)
-static int
-ev_get_uint32(ErlIOVec *ev, Uint32 *p, int *pp, int *qp) {
-  if (*(pp)+4 <= (ev)->iov[*(qp)].iov_len) {
-    *(p) = (EV_UINT32(ev, *(pp),   *(qp)) << 24)
-      | (EV_UINT32(ev, *(pp)+1, *(qp)) << 16)
-      | (EV_UINT32(ev, *(pp)+2, *(qp)) << 8)
-      | (EV_UINT32(ev, *(pp)+3, *(qp)));
-    if (*(pp)+4 < (ev)->iov[*(qp)].iov_len)
-      *(pp) = *(pp)+4;
-    else {
-      (*(qp))++;
-      *pp = 0;
-    }
-    return !0;
-  }
-  return 0;
-}
-
-/**
- * Convinience macros
- **/
-#define send_response(port,output) erl_drv_send_term(driver_mk_port(port),\
-    driver_caller(port), output, sizeof(output) / sizeof(output[0]));
-
-void iov_memcpy(void *dest,ErlIOVec *ev,int ind,int off);
-void iov_memcpy(void *dest,ErlIOVec *ev,int ind,int off) {
-  int i;
-  memcpy(dest,ev->iov[ind].iov_base+off,ev->iov[ind].iov_len-off);
-  for (i = ind+1; i < ev->vsize; i++)
-    memcpy(dest,ev->iov[i].iov_base,ev->iov[i].iov_len);
-}
-
-/**
- * Reference handling
- **/
-
-static int add_reference(driver_context_t *ctxt, Uint32 ref) {
-
-  /*
-   * Premature optimizations may be evil, but they sure are fun.
-   */
-
-  if (ctxt->outstanding_refs == NULL) {
-    /* First ref to be ignored */
-    ctxt->outstanding_refs = driver_alloc(REF_SEGMENT_SIZE*sizeof(Uint32));
-    if (!ctxt->outstanding_refs)
-      return 1;
-
-    memset(ctxt->outstanding_refs,0,REF_SEGMENT_SIZE*sizeof(Uint32));
-    ctxt->outstanding_refs_max += REF_SEGMENT_SIZE;
-    ctxt->outstanding_refs[ctxt->outstanding_refs_cnt++] = ref;
-  } else if (ctxt->outstanding_refs_cnt == ctxt->outstanding_refs_max) {
-    /* Expand ref array */
-    Uint32 *new_array;
-    ctxt->outstanding_refs_max += REF_SEGMENT_SIZE;
-    new_array = driver_realloc(ctxt->outstanding_refs,
-			       ctxt->outstanding_refs_max*sizeof(Uint32));
-
-    if (!new_array) {
-      ctxt->outstanding_refs_max -= REF_SEGMENT_SIZE;
-      return 1;
-    }
-
-    ctxt->outstanding_refs = new_array;
-
-    memset(ctxt->outstanding_refs+ctxt->outstanding_refs_cnt,0,
-	   REF_SEGMENT_SIZE*sizeof(Uint32));
-    ctxt->outstanding_refs[ctxt->outstanding_refs_cnt++] = ref;
-
-  } else {
-    /* Find an empty slot:
-     *   First we try current index,
-     *   then we scan for a slot.
-     */
-    if (!ctxt->outstanding_refs[ctxt->outstanding_refs_cnt]) {
-      ctxt->outstanding_refs[ctxt->outstanding_refs_cnt++] = ref;
-    } else {
-      int i;
-      ASSERT(ctxt->outstanding_refs_cnt < ctxt->outstanding_refs_max);
-      for (i = 0; i < ctxt->outstanding_refs_max; i++)
-	if (!ctxt->outstanding_refs[i])
-	  break;
-      ASSERT(ctxt->outstanding_refs[i] == 0);
-      ctxt->outstanding_refs[i] = ref;
-      ctxt->outstanding_refs_cnt++;
-    }
-  }
-  return 0;
-}
-
-/* Return 0 if removed, 1 if does not exist, */
-static int remove_reference(driver_context_t *ctxt, Uint32 ref) {
-  int i,j;
-
-  if (ctxt->outstanding_refs_max == 0 && ctxt->outstanding_refs_cnt == 0) {
-    ASSERT(ctxt->outstanding_refs == NULL);
-    return 1;
-  }
-
-  for (i = 0; i < ctxt->outstanding_refs_max; i++) {
-    if (ctxt->outstanding_refs[i] == ref) {
-      ctxt->outstanding_refs[i] = 0;
-      ctxt->outstanding_refs_cnt--;
-      i = -1;
-      break;
-    }
-  }
-
-  if (i != -1)
-    return 1;
-
-  if (ctxt->outstanding_refs_cnt == 0) {
-    driver_free(ctxt->outstanding_refs);
-    ctxt->outstanding_refs = NULL;
-    ctxt->outstanding_refs_max = 0;
-  } else if (ctxt->outstanding_refs_cnt == (ctxt->outstanding_refs_max - REF_SEGMENT_SIZE)) {
-    Uint32 *new_array;
-    for (i = 0, j = 0; i < ctxt->outstanding_refs_cnt; i++) {
-      if (ctxt->outstanding_refs[i] == 0) {
-	for (j = i+1; j < ctxt->outstanding_refs_max; j++)
-	  if (ctxt->outstanding_refs[j]) {
-	    ctxt->outstanding_refs[i] = ctxt->outstanding_refs[j];
-	    ctxt->outstanding_refs[j] = 0;
-	    break;
-	  }
-      }
-    }
-    ctxt->outstanding_refs_max -= REF_SEGMENT_SIZE;
-    new_array = driver_realloc(ctxt->outstanding_refs,
-			       ctxt->outstanding_refs_max*sizeof(Uint32));
-    if (!new_array) {
-      ctxt->outstanding_refs_max += REF_SEGMENT_SIZE;
-      return 2;
-    }
-
-    ctxt->outstanding_refs = new_array;
-
-  }
-
-  return 0;
-}
-
-/**
- * The OSE proxy process. This only handles ERTS_SIGNAL_OSE_DRV_ATTACH.
- * The process is needed because signals triggered by attach ignore
- * redir tables.
- *
- * We have one global proxy process to save memory. An attempt to make each
- * port phantom into a proxy was made, but that used way to much memory.
- */
-static OS_PROCESS(driver_proxy_process) {
-  SIGSELECT sigs[] = {1,ERTS_SIGNAL_OSE_DRV_ATTACH};
-  PROCESS master = 0;
-
-  while (1) {
-    union SIGNAL *sig = receive(sigs);
-
-    if (sig->signo == ERTS_SIGNAL_OSE_DRV_ATTACH) {
-
-      /* The first message is used to determine who to send messages to. */
-      if (master == 0)
-	master = sender(&sig);
-
-      if (sig->async.target == 0) {
-	PROCESS from = sender(&sig);
-	restore(sig);
-	DEBUGP_ATTACH("0x%x: got attach 0x%x, sending to 0x%x\n",
-		      current_process(),from,master);
-	sig->async.target = from;
-	send(&sig,master);
-      } else {
-	PROCESS target = sig->async.target;
-	restore(sig);
-	sig->async.target = 0;
-	DEBUGP_ATTACH("0x%x: doing attach on 0x%x\n",current_process(),target);
-	attach(&sig,target);
-      }
-    }
-  }
-}
-
-
-/**
- * Init routine for the driver
- **/
-static int drv_init(void) {
-
-  a_ok = driver_mk_atom("ok");
-  a_error = driver_mk_atom("error");
-  a_enomem = driver_mk_atom("enomem");
-  a_enoent = driver_mk_atom("enoent");
-  a_badarg = driver_mk_atom("badarg");
-  a_mailbox_up = driver_mk_atom("mailbox_up");
-  a_mailbox_down = driver_mk_atom("mailbox_down");
-  a_ose_drv_reply = driver_mk_atom("ose_drv_reply");
-  a_message = driver_mk_atom("message");
-
-  proxy_proc = create_process(get_ptype(current_process()),
-			      "ose_signal_driver_proxy",
-			      driver_proxy_process, 10000,
-			      get_pri(current_process()),
-			      0, 0, NULL, 0, 0);
-
-#ifdef DEBUG
-  efs_clone(proxy_proc);
-#endif
-  start(proxy_proc);
-
-  return 0;
-}
-
-/* Signal resolution callback */
-static ErlDrvOseEventId resolve_signal(union SIGNAL* osig) {
-  union SIGNAL *sig = osig;
-  if (sig->signo == ERTS_SIGNAL_OSE_DRV_HUNT ||
-      sig->signo == ERTS_SIGNAL_OSE_DRV_ATTACH) {
-    return sig->async.spid;
-  }
-  DEBUGP("%p: Got signal %d sent to %p from 0x%p\n",
-	 current_process(),sig->signo,addressee(&sig),sender(&sig));
-  return addressee(&sig);
-}
-
-
-/**
- * Start routine for the driver
- **/
-static ErlDrvData drv_start(ErlDrvPort port, char *command)
-{
-  driver_context_t *ctxt = driver_alloc(sizeof(driver_context_t));
-
-  ctxt->perm_events[0] = NULL;
-  ctxt->perm_events[1] = NULL;
-
-  ctxt->spid = 0;
-  ctxt->port = port;
-  ctxt->event_cnt = 0;
-  ctxt->events = NULL;
-  ctxt->ref = 0;
-  ctxt->outstanding_refs = NULL;
-  ctxt->outstanding_refs_max = 0;
-  ctxt->outstanding_refs_cnt = 0;
-
-
-  /* Set the communication protocol to Erlang to be binary */
-  set_port_control_flags(port, PORT_CONTROL_FLAG_BINARY);
-
-  /* Everything ok */
-  return (ErlDrvData)ctxt;
-}
-
-/**
- * Stop routine for the driver
- **/
-static void drv_stop(ErlDrvData driver_data)
-{
-  driver_context_t *ctxt = (driver_context_t *)driver_data;
-  int i;
-
-  /* HUNT + ATTACH */
-  if (ctxt->perm_events[0])
-    driver_select(ctxt->port, ctxt->perm_events[0],
-		  ERL_DRV_USE|ERL_DRV_READ, 0);
-  if (ctxt->perm_events[1])
-    driver_select(ctxt->port, ctxt->perm_events[1],
-		  ERL_DRV_USE|ERL_DRV_READ, 0);
-
-  for (i = 0; i < ctxt->event_cnt; i++) {
-    driver_select(ctxt->port, ctxt->events[i], ERL_DRV_USE|ERL_DRV_READ, 0);
-  }
-
-  if (ctxt->spid != 0)
-    kill_proc(ctxt->spid);
-  DEBUGP("0x%x: stopped\n",ctxt->spid);
-  if (ctxt->events)
-    driver_free(ctxt->events);
-  if (ctxt->outstanding_refs)
-    driver_free(ctxt->outstanding_refs);
-
-  driver_free(ctxt);
-}
-
-/**
- * Output from Erlang
- **/
-static void outputv(ErlDrvData driver_data, ErlIOVec *ev)
-{
-  driver_context_t *ctxt = (driver_context_t *)driver_data;
-  int p = 0, q = 1;
-  char cmd;
-
-  if (! EV_GET_CHAR(ev,&cmd,&p,&q)) {
-    ErlDrvTermData output[] = {
-      ERL_DRV_ATOM, a_ose_drv_reply,
-      ERL_DRV_PORT, driver_mk_port(ctxt->port),
-      ERL_DRV_ATOM, a_badarg,
-      ERL_DRV_TUPLE, 3};
-    send_response(ctxt->port, output);
-    return;
-  }
-
-  /* Command is in the buffer's first byte */
-  switch(cmd) {
-
-  case OPEN: {
-    char *name = driver_alloc(ev->size - 1+1);
-    struct OS_redir_entry redir[2];
-
-    redir[0].sig = 1;
-    redir[0].pid = current_process();
-
-    iov_memcpy(name,ev,q,p);
-    name[ev->size-1] = '\0';
-
-    ctxt->spid = create_process(OS_PHANTOM, name, NULL, 0,
-				0, 0, 0, redir, 0, 0);
-
-    DEBUGP("0x%x: open\n",ctxt->spid);
-
-    ctxt->perm_events[1] =
-      erl_drv_ose_event_alloc(ERTS_SIGNAL_OSE_DRV_ATTACH,(int)ctxt->spid,
-			      resolve_signal, NULL);
-    driver_select(ctxt->port,ctxt->perm_events[1],ERL_DRV_READ|ERL_DRV_USE,1);
-
-    ctxt->perm_events[0] =
-      erl_drv_ose_event_alloc(ERTS_SIGNAL_OSE_DRV_HUNT,(int)ctxt->spid,
-			      resolve_signal, NULL);
-    driver_select(ctxt->port,ctxt->perm_events[0],ERL_DRV_READ|ERL_DRV_USE,1);
-
-    start(ctxt->spid);
-
-    {
-      ErlDrvTermData output[] = {
-	ERL_DRV_ATOM, a_ose_drv_reply,
-	ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	ERL_DRV_ATOM, a_ok,
-	ERL_DRV_TUPLE, 3};
-
-      send_response(ctxt->port, output);
-    }
-
-    break;
-
-  }
-
-  case ATTACH:
-  case HUNT:
-    {
-      union SIGNAL *sig = alloc(sizeof(union SIGNAL),
-				cmd == HUNT ? ERTS_SIGNAL_OSE_DRV_HUNT:ERTS_SIGNAL_OSE_DRV_ATTACH);
-
-      sig->async.port = driver_mk_port(ctxt->port);
-      sig->async.proc = driver_caller(ctxt->port);
-      sig->async.spid = ctxt->spid;
-      sig->async.ref = ++ctxt->ref;
-
-      if (add_reference(ctxt,ctxt->ref)) {
-	ErlDrvTermData output[] = {
-	  ERL_DRV_ATOM, a_ose_drv_reply,
-	  ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	  ERL_DRV_ATOM, a_enomem,
-	  ERL_DRV_TUPLE, 3};
-	send_response(ctxt->port, output);
-	free_buf(&sig);
-      } else {
-	ErlDrvTermData output[] = {
-	  ERL_DRV_ATOM, a_ose_drv_reply,
-	  ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	  ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	  ERL_DRV_INT, (ErlDrvUInt)ctxt->ref,
-	  ERL_DRV_TUPLE, 2,
-	  ERL_DRV_TUPLE, 3};
-	send_response(ctxt->port, output);
-
-	if (cmd == HUNT) {
-	  char *huntname = driver_alloc(sizeof(char)*((ev->size-1)+1));
-
-	  iov_memcpy(huntname,ev,q,p);
-	  huntname[ev->size-1] = '\0';
-
-	  DEBUGP_HUNT("0x%x: hunt %s -> %u (%u,%u)\n",
-		      ctxt->spid,huntname,ctxt->ref,
-		      ctxt->outstanding_refs_cnt,
-		      ctxt->outstanding_refs_max);
-
-	  hunt(huntname, 0, NULL, &sig);
-
-	  driver_free(huntname);
-	} else {
-	  EV_GET_UINT32(ev,&sig->async.target,&p,&q);
-	  DEBUGP_ATTACH("0x%x: attach %u -> %u (%u,%u)\n",
-			ctxt->spid,sig->async.target,
-			ctxt->ref,
-			ctxt->outstanding_refs_cnt,
-			ctxt->outstanding_refs_max);
-
-	  send(&sig,proxy_proc);
-	}
-
-      }
-
-      break;
-    }
-
-  case DETACH:
-  case DEHUNT:
-    {
-
-        Uint32 ref;
-
-	EV_GET_UINT32(ev,&ref,&p,&q);
-	if (cmd == DETACH) {
-	  DEBUGP_ATTACH("0x%x: detach %u (%u,%u)\n",ctxt->spid,ref,
-			ctxt->outstanding_refs_cnt,
-			ctxt->outstanding_refs_max);
-	} else {
-	  DEBUGP_HUNT("0x%x: dehunt %u (%u,%u)\n",ctxt->spid,ref,
-		      ctxt->outstanding_refs_cnt,
-		      ctxt->outstanding_refs_max);
-	}
-
-	if (remove_reference(ctxt,ref)) {
-	  ErlDrvTermData output[] = {
-	    ERL_DRV_ATOM, a_ose_drv_reply,
-	    ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	    ERL_DRV_ATOM, a_error,
-	    ERL_DRV_ATOM, a_enoent,
-	    ERL_DRV_TUPLE, 2,
-	    ERL_DRV_TUPLE, 3};
-
-	  send_response(ctxt->port, output);
-	} else {
-	  ErlDrvTermData output[] = {
-	    ERL_DRV_ATOM, a_ose_drv_reply,
-	    ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	    ERL_DRV_ATOM, a_ok,
-	    ERL_DRV_TUPLE, 3};
-
-	  send_response(ctxt->port, output);
-	}
-
-      break;
-    }
-
-  case SEND:
-  case SEND_W_S:
-    {
-      PROCESS spid;
-      PROCESS sender;
-      SIGSELECT signo;
-      OSBUFSIZE size = ev->size-9;
-      union SIGNAL *sig;
-
-      EV_GET_UINT32(ev,&spid,&p,&q);
-
-      if (cmd == SEND_W_S) {
-	EV_GET_UINT32(ev,&sender,&p,&q);
-	size -= 4;
-      } else {
-	sender = ctxt->spid;
-      }
-
-      EV_GET_UINT32(ev,&signo,&p,&q);
-
-      sig = alloc(size + sizeof(SIGSELECT),signo);
-
-      if (cmd == SEND_W_S) {
-	DEBUGP_SEND("0x%x: send_w_s(%u,%u,%u)\n",ctxt->spid,spid,signo,sender);
-      } else {
-	DEBUGP_SEND("0x%x: send(%u,%u)\n",ctxt->spid,spid,signo);
-      }
-
-      iov_memcpy(((char *)&sig->signo) + sizeof(SIGSELECT),ev,q,p);
-
-      send_w_s(&sig, sender, spid);
-
-      break;
-    }
-
-    case LISTEN:
-    {
-      int i,j,event_cnt = (ev->size - 1)/4;
-      ErlDrvEvent *events = NULL;
-      SIGSELECT signo,tmp_signo;
-
-      if (event_cnt == 0) {
-	for (i = 0; i < ctxt->event_cnt; i++)
-	  driver_select(ctxt->port,ctxt->events[i],ERL_DRV_READ|ERL_DRV_USE,0);
-	if (ctxt->events)
-	  driver_free(ctxt->events);
-      } else {
-	events = driver_alloc(sizeof(ErlDrvEvent)*event_cnt);
-	EV_GET_UINT32(ev,&signo,&p,&q);
-	for (i = 0, j = 0; i < event_cnt || j < ctxt->event_cnt; ) {
-
-	  if (ctxt->events)
-	    erl_drv_ose_event_fetch(ctxt->events[j],&tmp_signo,NULL,NULL);
-
-	  if (signo == tmp_signo) {
-	    events[i++] = ctxt->events[j++];
-	    EV_GET_UINT32(ev,&signo,&p,&q);
-	  } else if (signo < tmp_signo || !ctxt->events) {
-	    /* New signal to select on */
-	    events[i] = erl_drv_ose_event_alloc(signo,(int)ctxt->spid,
-						resolve_signal, NULL);
-	    driver_select(ctxt->port,events[i++],ERL_DRV_READ|ERL_DRV_USE,1);
-	    EV_GET_UINT32(ev,&signo,&p,&q);
-	  } else {
-	    /* Remove old signal to select on */
-	    driver_select(ctxt->port,ctxt->events[j++],ERL_DRV_READ|ERL_DRV_USE,0);
-	  }
-	}
-	if (ctxt->events)
-	  driver_free(ctxt->events);
-      }
-      ctxt->events = events;
-      ctxt->event_cnt = event_cnt;
-
-      {
-	ErlDrvTermData output[] = {
-	  ERL_DRV_ATOM, a_ose_drv_reply,
-	  ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	  ERL_DRV_ATOM, a_ok,
-	  ERL_DRV_TUPLE, 3};
-	send_response(ctxt->port, output);
-      }
-      break;
-    }
-
-    default:
-    {
-      DEBUGP("Warning: 'ose_signal_drv' unknown command '%d'\n", cmd);
-      break;
-    }
-  }
-}
-
-/**
- * Handler for when OSE signal arrives
- **/
-static void ready_input(ErlDrvData driver_data, ErlDrvEvent event)
-{
-  driver_context_t *ctxt = (driver_context_t *)driver_data;
-  union SIGNAL *sig = erl_drv_ose_get_signal(event);
-
-  while (sig != NULL) {
-
-    switch(sig->signo)
-      {
-	/* Remote process is available */
-      case ERTS_SIGNAL_OSE_DRV_HUNT:
-	{
-	  const PROCESS spid = sender(&sig);
-
-	  if (remove_reference(ctxt,sig->async.ref)) {
-	    DEBUGP_HUNT("0x%x: Got hunt from 0x%x -> %u (CANCELLED) (%u,%u)\n",
-			ctxt->spid,spid,sig->async.ref,
-			ctxt->outstanding_refs_cnt,
-			ctxt->outstanding_refs_max);
-	    /* Already removed by dehunt */
-	  } else {
-	    ErlDrvTermData reply[] = {
-	      ERL_DRV_ATOM, a_mailbox_up,
-	      ERL_DRV_PORT, sig->async.port,
-	      ERL_DRV_PORT, sig->async.port,
-	      ERL_DRV_UINT, (ErlDrvUInt)sig->async.ref,
-	      ERL_DRV_TUPLE, 2,
-	      ERL_DRV_UINT, (ErlDrvUInt)spid,
-	      ERL_DRV_TUPLE, 4};
-	    DEBUGP_HUNT("0x%x: Got hunt from 0x%x -> %u (%u,%u)\n",
-			ctxt->spid,spid,sig->async.ref,
-			ctxt->outstanding_refs_cnt,
-			ctxt->outstanding_refs_max);
-	    erl_drv_send_term(sig->async.port, sig->async.proc, reply,
-			      sizeof(reply) / sizeof(reply[0]));
-	  }
-	  break;
-	}
-
-	/* Remote process is down */
-      case ERTS_SIGNAL_OSE_DRV_ATTACH:
-	{
-	  PROCESS spid = sig->async.target;
-
-	  if (remove_reference(ctxt,sig->async.ref)) {
-	    DEBUGP_ATTACH("0x%x: Got attach from 0x%x -> %u (CANCELLED) (%u,%u)\n",
-			  ctxt->spid,spid,sig->async.ref,
-			  ctxt->outstanding_refs_cnt,
-			  ctxt->outstanding_refs_max);
-	    /* Already removed by detach */
-	  } else {
-	    ErlDrvTermData reply[] = {
-	      ERL_DRV_ATOM, a_mailbox_down,
-	      ERL_DRV_PORT, sig->async.port,
-	      ERL_DRV_PORT, sig->async.port,
-	      ERL_DRV_UINT, sig->async.ref,
-	      ERL_DRV_TUPLE, 2,
-	      ERL_DRV_UINT, (ErlDrvUInt)spid,
-	      ERL_DRV_TUPLE, 4};
-	     DEBUGP_ATTACH("0x%x: Got attach from 0x%x -> %u (%u,%u)\n",
-			   ctxt->spid,spid,sig->async.ref,
-			   ctxt->outstanding_refs_cnt,
-			   ctxt->outstanding_refs_max);
-	    erl_drv_send_term(sig->async.port, sig->async.proc, reply,
-			      sizeof(reply) / sizeof(reply[0]));
-	  }
-	  break;
-	}
-
-	/* Received user defined signal */
-      default:
-	{
-	  const PROCESS spid = sender(&sig);
-	  const OSBUFSIZE size = sigsize(&sig) - sizeof(SIGSELECT);
-	  const char *sig_data = ((char *)&sig->signo) + sizeof(SIGSELECT);
-
-	  ErlDrvTermData reply[] = {
-	    ERL_DRV_ATOM, a_message,
-	    ERL_DRV_PORT, driver_mk_port(ctxt->port),
-	    ERL_DRV_UINT, (ErlDrvUInt)spid,
-	    ERL_DRV_UINT, (ErlDrvUInt)ctxt->spid,
-	    ERL_DRV_UINT, (ErlDrvUInt)sig->signo,
-	    ERL_DRV_BUF2BINARY, (ErlDrvTermData)sig_data, (ErlDrvUInt)size,
-	    ERL_DRV_TUPLE, 4,
-	    ERL_DRV_TUPLE, 3};
-
-	  DEBUGP_SEND("0x%x: Got 0x%u\r\n", spid, sig->signo);
-
-	  erl_drv_output_term(driver_mk_port(ctxt->port), reply,
-			      sizeof(reply) / sizeof(reply[0]));
-	  break;
-	}
-      }
-
-    free_buf(&sig);
-    sig = erl_drv_ose_get_signal(event);
-  }
-}
-
-/**
- * Handler for 'port_control'
- **/
-static ErlDrvSSizeT control(ErlDrvData driver_data, unsigned int cmd,
-                            char *buf, ErlDrvSizeT len,
-                            char **rbuf, ErlDrvSizeT rlen)
-{
-  driver_context_t *ctxt = (driver_context_t *)driver_data;
-
-  switch(cmd)
-  {
-    case GET_SPID:
-    {
-      const PROCESS spid = ctxt->spid;
-      put_u32(spid, *rbuf);
-      return sizeof(PROCESS);
-    }
-
-#ifdef HAVE_OSE_SPI_H
-    case GET_NAME:
-    {
-      const PROCESS spid = get_u32(buf);
-      char *name = (char*)get_pid_info(spid,OSE_PI_NAME);
-      int n;
-      if (!name) {
-	*rbuf = NULL;
-	return 0;
-      }
-
-      if (rlen < (n = strlen(name))) {
-	ErlDrvBinary *bin = driver_alloc_binary(n);
-	strncpy(bin->orig_bytes,name,n);
-	*rbuf = (char*)bin;
-      } else
-	strncpy(*rbuf,name,n);
-      free_buf((union SIGNAL**)&name);
-
-      return n;
-    }
-#endif
-    default:
-    {
-      /* Unknown command */
-      return (ErlDrvSSizeT)ERL_DRV_ERROR_GENERAL;
-      break;
-    }
-  }
-}
-
-static void stop_select(ErlDrvEvent event, void *reserved)
-{
-  erl_drv_ose_event_free(event);
-}
-
-/**
- * Setup the driver entry for the Erlang runtime
- **/
-ErlDrvEntry ose_signal_driver_entry = {
-  .init                         = drv_init,
-  .start                        = drv_start,
-  .stop                         = drv_stop,
-  .outputv                      = outputv,
-  .ready_input                  = ready_input,
-  .driver_name                  = DRIVER_NAME,
-  .control                      = control,
-  .extended_marker              = ERL_DRV_EXTENDED_MARKER,
-  .major_version                = ERL_DRV_EXTENDED_MAJOR_VERSION,
-  .minor_version                = ERL_DRV_EXTENDED_MINOR_VERSION,
-  .driver_flags                 = ERL_DRV_FLAG_USE_PORT_LOCKING,
-  .stop_select                  = stop_select
-};
-
diff -Ndurp otp_src_18.3.4.5/erts/emulator/drivers/ose/ttsl_drv.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/ose/ttsl_drv.c
--- otp_src_18.3.4.5/erts/emulator/drivers/ose/ttsl_drv.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/drivers/ose/ttsl_drv.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,69 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 1996-2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Stub tty driver because group/user depend on this.
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include "erl_driver.h"
-
-static int ttysl_init(void);
-static ErlDrvData ttysl_start(ErlDrvPort, char*);
-
-/* Define the driver table entry. */
-struct erl_drv_entry ttsl_driver_entry = {
-    ttysl_init,
-    ttysl_start,
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    "tty_sl",
-    NULL,
-    NULL,
-    NULL,
-    NULL, /* timeout */
-    NULL, /* outputv */
-    NULL, /* ready_async */
-    NULL, /* flush */
-    NULL, /* call */
-    NULL, /* event */
-    ERL_DRV_EXTENDED_MARKER,
-    ERL_DRV_EXTENDED_MAJOR_VERSION,
-    ERL_DRV_EXTENDED_MINOR_VERSION,
-    0, /* ERL_DRV_FLAGs */
-    NULL,
-    NULL, /* process_exit */
-    NULL
-};
-
-
-static int ttysl_init(void)
-{
-    return 0;
-}
-
-static ErlDrvData ttysl_start(ErlDrvPort port, char* buf)
-{
-    return ERL_DRV_ERROR_GENERAL;
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/Makefile.in otp_src_18.3.4.5-remove-OSE-port/erts/emulator/Makefile.in
--- otp_src_18.3.4.5/erts/emulator/Makefile.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/Makefile.in	2017-02-03 21:52:59.159951425 +0200
@@ -23,10 +23,6 @@ include ../vsn.mk
 include $(ERL_TOP)/make/$(TARGET)/otp.mk
 -include $(TARGET)/gen_git_version.mk
 
-ifeq ($(findstring ose,$(TARGET)),ose)
-include $(ERL_TOP)/make/$(TARGET)/ose_lm.mk
-endif
-
 ENABLE_ALLOC_TYPE_VARS = @ENABLE_ALLOC_TYPE_VARS@
 HIPE_ENABLED=@HIPE_ENABLED@
 DTRACE_ENABLED=@DTRACE_ENABLED@
@@ -245,9 +241,7 @@ HCC     = @HCC@
 LD      = @LD@
 DEXPORT = @DEXPORT@
 RANLIB  = @RANLIB@
-ifneq ($(findstring ose,$(TARGET)),ose)
 STRIP   = strip
-endif
 PERL    = @PERL@
 RM	= @RM@
 MKDIR	= @MKDIR@
@@ -684,14 +678,6 @@ $(OBJDIR)/%.o: $(TTF_DIR)/%.c
 $(OBJDIR)/%.o: sys/$(ERLANG_OSTYPE)/%.c
 	$(V_CC) $(CFLAGS) $(INCLUDES) -c $< -o $@
 
-ifeq ($(findstring ose,$(TARGET)),ose)
-$(OBJDIR)/ose_confd.o: $(OSE_CONFD)
-	$(V_CC) $(CFLAGS) $(INCLUDES) -c $< -o $@
-
-$(OBJDIR)/crt0_lm.o: $(CRT0_LM)
-	$(V_CC) $(CFLAGS) $(INCLUDES) -c $< -o $@
-endif
-
 $(OBJDIR)/%.o: sys/common/%.c
 	$(V_CC) $(subst -O2, $(GEN_OPT_FLGS), $(CFLAGS)) $(INCLUDES) -c $< -o $@
 
@@ -810,29 +796,6 @@ OS_OBJS = \
 	$(OBJDIR)/dosmap.o
 
 else
-ifeq ($(findstring ose,$(TARGET)),ose)
-OS_OBJS = \
-	$(OBJDIR)/sys.o \
-	$(OBJDIR)/driver_tab.o \
-	$(OBJDIR)/ose_efile.o \
-	$(OBJDIR)/gzio.o \
-	$(OBJDIR)/elib_memmove.o
-
-OS_OBJS += $(OBJDIR)/ose_confd.o \
-	$(OBJDIR)/crt0_lm.o
-
-OS_OBJS += $(OBJDIR)/sys_float.o \
-					 $(OBJDIR)/sys_time.o
-
-DRV_OBJS = \
-	$(OBJDIR)/efile_drv.o \
-	$(OBJDIR)/ose_signal_drv.o \
-	$(OBJDIR)/inet_drv.o \
-	$(OBJDIR)/zlib_drv.o \
-	$(OBJDIR)/ram_file_drv.o \
-	$(OBJDIR)/ttsl_drv.o
-
-else
 OS_OBJS = \
 	$(OBJDIR)/sys.o \
 	$(OBJDIR)/driver_tab.o \
@@ -849,7 +812,6 @@ DRV_OBJS = \
 	$(OBJDIR)/ram_file_drv.o \
 	$(OBJDIR)/ttsl_drv.o
 endif
-endif
 
 ifneq ($(STATIC_NIFS),no)
 STATIC_NIF_LIBS = $(STATIC_NIFS)
@@ -1022,19 +984,12 @@ $(BINDIR)/$(EMULATOR_EXECUTABLE): $(INIT
 	$(STATIC_DRIVER_LIBS) $(LIBS)
 
 else
-ifeq ($(findstring ose,$(TARGET)),ose)
-$(BINDIR)/$(EMULATOR_EXECUTABLE): $(INIT_OBJS) $(OBJS) $(DEPLIBS) $(LCF)
-	$(call build-ose-load-module, $@, $(INIT_OBJS) $(OBJS), $(STATIC_NIF_LIBS) \
-	$(STATIC_DRIVER_LIBS) $(LIBS), $(BEAM_LMCONF))
-
-else
 $(BINDIR)/$(EMULATOR_EXECUTABLE): $(INIT_OBJS) $(OBJS) $(DEPLIBS)
 	$(ld_verbose)$(PURIFY) $(LD) -o $(BINDIR)/$(EMULATOR_EXECUTABLE) \
 	$(HIPEBEAMLDFLAGS) $(LDFLAGS) $(DEXPORT) $(INIT_OBJS) $(OBJS) \
 	$(STATIC_NIF_LIBS) $(STATIC_DRIVER_LIBS) $(LIBS)
 
 endif
-endif
 
 # ----------------------------------------------------------------------
 # Dependencies
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/common/erl_check_io.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/common/erl_check_io.c
--- otp_src_18.3.4.5/erts/emulator/sys/common/erl_check_io.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/common/erl_check_io.c	2017-02-03 21:52:59.159951425 +0200
@@ -1337,11 +1337,7 @@ print_select_op(erts_dsprintf_buf_t *dsb
 {
     Port *pp = erts_drvport2port(ix);
     erts_dsprintf(dsbufp,
-#ifdef __OSE__
-		  "driver_select(%p, %d,%s%s%s%s | %d, %d) "
-#else
 		  "driver_select(%p, %d,%s%s%s%s, %d) "
-#endif
 		  "by ",
 		  ix,
 		  (int) GET_FD(fd),
@@ -1861,25 +1857,6 @@ stale_drv_select(Eterm id, ErtsDrvEventS
 
 #ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
 
-#ifdef __OSE__
-static SafeHashValue drv_ev_state_hash(void *des)
-{
-    ErtsSysFdType fd = ((ErtsDrvEventState *) des)->fd;
-    /* We use hash on signo ^ id in order for steal to happen when the
-       same signo + fd is selected on by two different ports */
-    SafeHashValue val = (SafeHashValue)(fd->signo ^ fd->id);
-    return val ^ (val >> 8);
-}
-
-static int drv_ev_state_cmp(void *des1, void *des2)
-{
-    ErtsSysFdType fd1 = ((ErtsDrvEventState *) des1)->fd;
-    ErtsSysFdType fd2 = ((ErtsDrvEventState *) des2)->fd;
-    if (fd1->signo == fd2->signo && fd1->id == fd2->id)
-      return 0;
-    return 1;
-}
-#else /* !__OSE__ && !ERTS_SYS_CONTINOUS_FD_NUMBERS i.e. probably windows */
 static SafeHashValue drv_ev_state_hash(void *des)
 {
     SafeHashValue val = (SafeHashValue) ((ErtsDrvEventState *) des)->fd;
@@ -1891,7 +1868,6 @@ static int drv_ev_state_cmp(void *des1,
     return ( ((ErtsDrvEventState *) des1)->fd == ((ErtsDrvEventState *) des2)->fd
 	    ? 0 : 1);
 }
-#endif
 
 static void *drv_ev_state_alloc(void *des_tmpl)
 {
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/common/erl_poll.h otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/common/erl_poll.h
--- otp_src_18.3.4.5/erts/emulator/sys/common/erl_poll.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/common/erl_poll.h	2017-02-03 21:52:59.159951425 +0200
@@ -93,7 +93,7 @@
 #  if defined(ERTS_USE_POLL)
 #    undef ERTS_POLL_USE_POLL
 #    define ERTS_POLL_USE_POLL 1
-#  elif !defined(__WIN32__) && !defined(__OSE__)
+#  elif !defined(__WIN32__)
 #    undef ERTS_POLL_USE_SELECT
 #    define ERTS_POLL_USE_SELECT 1
 #  endif
@@ -104,31 +104,13 @@
 typedef Uint32 ErtsPollEvents;
 #undef ERTS_POLL_EV_E2N
 
-#if defined(__WIN32__) || defined(__OSE__)	/* --- win32 or ose -------- */
+#if defined(__WIN32__)	/* --- win32  --------------------------------------- */
 
 #define ERTS_POLL_EV_IN   1
 #define ERTS_POLL_EV_OUT  2
 #define ERTS_POLL_EV_ERR  4
 #define ERTS_POLL_EV_NVAL 8
 
-#ifdef __OSE__
-
-typedef struct ErtsPollOseMsgList_ {
-  struct ErtsPollOseMsgList_ *next;
-  union SIGNAL *data;
-} ErtsPollOseMsgList;
-
-struct erts_sys_fd_type {
-    SIGSELECT signo;
-    ErlDrvOseEventId id;
-    ErtsPollOseMsgList *msgs;
-    ErlDrvOseEventId (*resolve_signal)(union SIGNAL *sig);
-    ethr_mutex mtx;
-    void *extra;
-};
-
-#endif
-
 #elif ERTS_POLL_USE_EPOLL	/* --- epoll ------------------------------- */
 
 #include <sys/epoll.h>
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/beam.lmconf otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/beam.lmconf
--- otp_src_18.3.4.5/erts/emulator/sys/ose/beam.lmconf	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/beam.lmconf	1970-01-01 03:00:00.000000000 +0300
@@ -1,26 +0,0 @@
-OSE_LM_STACK_SIZES=256,512,1024,2048,4096,8192,16384,65536
-OSE_LM_SIGNAL_SIZES=31,63,127,255,1023,4095,16383,65535
-OSE_LM_POOL_SIZE=0x200000
-OSE_LM_MAIN_NAME=main
-OSE_LM_MAIN_STACK_SIZE=0xF000
-OSE_LM_MAIN_PRIORITY=20
-## Has to be of a type that allows MAM
-OSE_LM_PROGRAM_TYPE=APP_RAM
-OSE_LM_DATA_INIT=YES
-OSE_LM_BSS_INIT=YES
-OSE_LM_EXEC_MODEL=SHARED
-HEAP_MAX_SIZE=1000000000
-HEAP_SMALL_BUF_INIT_SIZE=20971520
-HEAP_LARGE_BUF_THRESHOLD=16000000
-HEAP_LOCK_TYPE=2
-
-ERTS_DEFAULT_PRIO=24
-ERTS_SCHEDULER_PRIO=24
-ERTS_ASYNC_PRIO=22
-ERTS_AUX_PRIO=24
-ERTS_SYS_MSG_DISPATCHER_PRIO=21
-
-# Setting the environment variable EFS_RESOLVE_TMO on the block to 0.
-# This will eliminiate delays when trying to open files on not mounted
-# volumes.
-EFS_RESOLVE_TMO=0
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/driver_int.h otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/driver_int.h
--- otp_src_18.3.4.5/erts/emulator/sys/ose/driver_int.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/driver_int.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,42 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 1997-2009. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * System dependant driver declarations
- */
-
-#ifndef __DRIVER_INT_H__
-#define __DRIVER_INT_H__
-
-#ifdef HAVE_SYS_UIO_H
-#include <sys/types.h>
-#include <sys/uio.h>
-
-typedef struct iovec SysIOVec;
-
-#else
-
-typedef struct {
-    char* iov_base;
-    int   iov_len;
-} SysIOVec;
-
-#endif
-
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/erl_main.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_main.c
--- otp_src_18.3.4.5/erts/emulator/sys/ose/erl_main.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_main.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,54 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2000-2009. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-#include <stdlib.h>
-
-#include "sys.h"
-#include "erl_vm.h"
-#include "global.h"
-#include "ose.h"
-
-int
-main(int argc, char **argv) {
-
-  (void)stdin;(void)stdout;(void)stderr;
-
-  /* When starting using pm_create -c ARGV="-- -root ..", argv[0] is the first
-     part of ARGV and not the name of the executable. So we shuffle some
-     pointers here to make erl_start happy. */
-  if (argv[0][0] == '-') {
-    int i;
-    char **tmp_argv = malloc(sizeof(char*)*(argc+1));
-    for (i = 0; i < argc; i++)
-      tmp_argv[i+1] = argv[i];
-    tmp_argv[0] = "beam";
-    erl_start(argc+1,tmp_argv);
-    free(tmp_argv);
-  } else {
-   erl_start(argc,argv);
-  }
-
-   stop(current_process());
-
-   return 0;
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/erl_ose_sys_ddll.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_ose_sys_ddll.c
--- otp_src_18.3.4.5/erts/emulator/sys/ose/erl_ose_sys_ddll.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_ose_sys_ddll.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,127 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2006-2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-/*
- * Interface functions to the dynamic linker using dl* functions.
- * (No support in OSE, we use static linkage instead)
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include "sys.h"
-#include "erl_vm.h"
-#include "global.h"
-
-
-void erl_sys_ddll_init(void) {
-}
-
-/*
- * Open a shared object
- */
-int erts_sys_ddll_open(const char *full_name, void **handle, ErtsSysDdllError* err)
-{
-   return ERL_DE_ERROR_NO_DDLL_FUNCTIONALITY;
-}
-
-int erts_sys_ddll_open_noext(char *dlname, void **handle, ErtsSysDdllError* err)
-{
-   return ERL_DE_ERROR_NO_DDLL_FUNCTIONALITY;
-}
-
-/*
- * Find a symbol in the shared object
- */
-int erts_sys_ddll_sym2(void *handle, const char *func_name, void **function,
-		       ErtsSysDdllError* err)
-{
-   return ERL_DE_ERROR_NO_DDLL_FUNCTIONALITY;
-}
-
-/* XXX:PaN These two will be changed with new driver interface! */
-
-/*
- * Load the driver init function, might appear under different names depending on object arch...
- */
-
-int erts_sys_ddll_load_driver_init(void *handle, void **function)
-{
-    void *fn;
-    int res;
-    if ((res = erts_sys_ddll_sym2(handle, "driver_init", &fn, NULL)) != ERL_DE_NO_ERROR) {
-	res = erts_sys_ddll_sym2(handle, "_driver_init", &fn, NULL);
-    }
-    if (res == ERL_DE_NO_ERROR) {
-	*function = fn;
-    }
-    return res;
-}
-
-int erts_sys_ddll_load_nif_init(void *handle, void **function, ErtsSysDdllError* err)
-{
-    void *fn;
-    int res;
-    if ((res = erts_sys_ddll_sym2(handle, "nif_init", &fn, err)) != ERL_DE_NO_ERROR) {
-	res = erts_sys_ddll_sym2(handle, "_nif_init", &fn, err);
-    }
-    if (res == ERL_DE_NO_ERROR) {
-	*function = fn;
-    }
-    return res;
-}
-
-/*
- * Call the driver_init function, whatever it's really called, simple on unix...
-*/
-void *erts_sys_ddll_call_init(void *function) {
-    void *(*initfn)(void) = function;
-    return (*initfn)();
-}
-void *erts_sys_ddll_call_nif_init(void *function) {
-    return erts_sys_ddll_call_init(function);
-}
-
-
-
-/*
- * Close a chared object
- */
-int erts_sys_ddll_close2(void *handle, ErtsSysDdllError* err)
-{
-   return ERL_DE_ERROR_NO_DDLL_FUNCTIONALITY;
-}
-
-
-/*
- * Return string that describes the (current) error
- */
-char *erts_sys_ddll_error(int code)
-{
-    return "Unspecified error";
-}
-
-void erts_sys_ddll_free_error(ErtsSysDdllError* err)
-{
-    if (err->str != NULL) {
-	erts_free(ERTS_ALC_T_DDLL_TMP_BUF, err->str);
-    }
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/erl_ose_sys.h otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_ose_sys.h
--- otp_src_18.3.4.5/erts/emulator/sys/ose/erl_ose_sys.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_ose_sys.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,356 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 1997-2011. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- *
- * This file handles differences between different Unix systems.
- * This should be the only place with conditional compilation
- * depending on the type of OS.
- */
-
-#ifndef _ERL_OSE_SYS_H
-#define _ERL_OSE_SYS_H
-
-#include "ose.h"
-#undef NIL
-#include "ramlog.h"
-#include "erts.sig"
-
-#include "fcntl.h"
-#include "math.h"
-#include "stdio.h"
-#include "stdlib.h"
-#include "string.h"
-#include "sys/param.h"
-#include "sys/time.h"
-#include "time.h"
-#include "dirent.h"
-#include "ethread.h"
-
-/* FIXME: configuration options */
-#define ERTS_SCHED_MIN_SPIN 1
-#define ERTS_SCHED_ONLY_POLL_SCHED_1 1
-#define ERTS_SCHED_FAIR 1
-#define NO_SYSCONF 1
-#define OPEN_MAX FOPEN_MAX
-
-#define MAP_ANON MAP_ANONYMOUS
-
-#ifndef HAVE_MMAP
-#   define HAVE_MMAP 0
-#endif
-
-#if HAVE_MMAP
-#   include "sys/mman.h"
-#endif
-
-/*
- * Min number of async threads
- */
-#define ERTS_MIN_NO_OF_ASYNC_THREADS 1
-
-/*
- * Our own type of "FD's"
- */
-#define ERTS_SYS_FD_TYPE struct erts_sys_fd_type*
-#define NO_FSTAT_ON_SYS_FD_TYPE 1 /* They are signals, not files */
-
-#include "sys/stat.h"
-
-/* FIXME mremap is not defined in OSE - POSIX issue */
-extern void *mremap (void *__addr, size_t __old_len, size_t __new_len,
-                        int __flags, ...);
-
-/* FIXME: mremap constants */
-#define MREMAP_MAYMOVE  1
-#define MREMAP_FIXED    2
-
-typedef void *GETENV_STATE;
-
-/*
-** For the erl_timer_sup module.
-*/
-#define HAVE_GETHRTIME
-
-typedef long long SysHrTime;
-extern SysHrTime sys_gethrtime(void);
-
-void sys_init_hrtime(void);
-
-typedef time_t erts_time_t;
-
-typedef struct timeval SysTimeval;
-
-#define sys_gettimeofday(Arg) ((void) gettimeofday((Arg), NULL))
-
-typedef struct {
-    clock_t tms_utime;
-    clock_t tms_stime;
-    clock_t tms_cutime;
-    clock_t tms_cstime;
-} SysTimes;
-
-extern int erts_ticks_per_sec;
-
-#define SYS_CLK_TCK (erts_ticks_per_sec)
-
-extern clock_t sys_times(SysTimes *buffer);
-
-/* No use in having other resolutions than 1 Ms. */
-#define SYS_CLOCK_RESOLUTION 1
-
-#define erts_isfinite finite
-
-#ifdef NO_FPE_SIGNALS
-
-#define erts_get_current_fp_exception() NULL
-#ifdef ERTS_SMP
-#define erts_thread_init_fp_exception() do{}while(0)
-#endif
-#  define __ERTS_FP_CHECK_INIT(fpexnp) do {} while (0)
-#  define __ERTS_FP_ERROR(fpexnp, f, Action) if (!finite(f)) { Action; } else {}
-#  define __ERTS_FP_ERROR_THOROUGH(fpexnp, f, Action) __ERTS_FP_ERROR(fpexnp, f, Action)
-#  define __ERTS_SAVE_FP_EXCEPTION(fpexnp)
-#  define __ERTS_RESTORE_FP_EXCEPTION(fpexnp)
-
-#define erts_sys_block_fpe() 0
-#define erts_sys_unblock_fpe(x) do{}while(0)
-
-#else /* !NO_FPE_SIGNALS */
-
-extern volatile unsigned long *erts_get_current_fp_exception(void);
-#ifdef ERTS_SMP
-extern void erts_thread_init_fp_exception(void);
-#endif
-#  if (defined(__i386__) || defined(__x86_64__)) && defined(__GNUC__)
-#    define erts_fwait(fpexnp,f) \
-	__asm__ __volatile__("fwait" : "=m"(*(fpexnp)) : "m"(f))
-#  elif (defined(__powerpc__) || defined(__ppc__)) && defined(__GNUC__)
-#    define erts_fwait(fpexnp,f) \
-	__asm__ __volatile__("" : "=m"(*(fpexnp)) : "fm"(f))
-#  elif defined(__sparc__) && defined(__linux__) && defined(__GNUC__)
-#    define erts_fwait(fpexnp,f) \
-	__asm__ __volatile__("" : "=m"(*(fpexnp)) : "em"(f))
-#  else
-#    define erts_fwait(fpexnp,f) \
-	__asm__ __volatile__("" : "=m"(*(fpexnp)) : "g"(f))
-#  endif
-#  if (defined(__i386__) || defined(__x86_64__)) && defined(__GNUC__)
-     extern void erts_restore_fpu(void);
-#  else
-#    define erts_restore_fpu() /*empty*/
-#  endif
-#  if (!defined(__GNUC__) || \
-       (__GNUC__ < 2) || \
-       (__GNUC__ == 2 && __GNUC_MINOR < 96)) && \
-      !defined(__builtin_expect)
-#    define __builtin_expect(x, expected_value) (x)
-#  endif
-static __inline__ int erts_check_fpe(volatile unsigned long *fp_exception, double f)
-{
-    erts_fwait(fp_exception, f);
-    if (__builtin_expect(*fp_exception == 0, 1))
-       return 0;
-    *fp_exception = 0;
-    erts_restore_fpu();
-    return 1;
-}
-#  undef erts_fwait
-#  undef erts_restore_fpu
-extern void erts_fp_check_init_error(volatile unsigned long *fp_exception);
-static __inline__ void __ERTS_FP_CHECK_INIT(volatile unsigned long *fp_exception)
-{
-    if (__builtin_expect(*fp_exception == 0, 1))
-	return;
-    erts_fp_check_init_error(fp_exception);
-}
-#  define __ERTS_FP_ERROR(fpexnp, f, Action) do { if (erts_check_fpe((fpexnp),(f))) { Action; } } while (0)
-#  define __ERTS_SAVE_FP_EXCEPTION(fpexnp) unsigned long old_erl_fp_exception = *(fpexnp)
-#  define __ERTS_RESTORE_FP_EXCEPTION(fpexnp) \
-              do { *(fpexnp) = old_erl_fp_exception; } while (0)
-   /* This is for library calls where we don't trust the external
-      code to always throw floating-point exceptions on errors. */
-static __inline__ int erts_check_fpe_thorough(volatile unsigned long *fp_exception, double f)
-{
-    return erts_check_fpe(fp_exception, f) || !finite(f);
-}
-#  define __ERTS_FP_ERROR_THOROUGH(fpexnp, f, Action) \
-  do { if (erts_check_fpe_thorough((fpexnp),(f))) { Action; } } while (0)
-
-int erts_sys_block_fpe(void);
-void erts_sys_unblock_fpe(int);
-
-#endif /* !NO_FPE_SIGNALS */
-
-#define ERTS_FP_CHECK_INIT(p)		__ERTS_FP_CHECK_INIT(&(p)->fp_exception)
-#define ERTS_FP_ERROR(p, f, A)		__ERTS_FP_ERROR(&(p)->fp_exception, f, A)
-#define ERTS_FP_ERROR_THOROUGH(p, f, A)	__ERTS_FP_ERROR_THOROUGH(&(p)->fp_exception, f, A)
-
-/* FIXME: force HAVE_GETPAGESIZE and stub getpagesize */
-#ifndef HAVE_GETPAGESIZE
-#define HAVE_GETPAGESIZE 1
-#endif
-
-extern int getpagesize(void);
-
-#ifndef HZ
-#define HZ 60
-#endif
-
-/* OSE5 doesn't provide limits.h so a number of macros should be
- * added manually */
-
-#ifndef CHAR_BIT
-#define CHAR_BIT 8
-#endif
-
-/* Minimum and maximum values a `signed int' can hold.  */
-#ifndef INT_MAX
-#define INT_MAX	2147483647
-#endif
-
-#ifndef INT_MIN
-#define INT_MIN	(-INT_MAX - 1)
-#endif
-
-#ifndef UINT_MAX
-#  define UINT_MAX   4294967295U
-#endif
-
-/*
-static void erts_ose_sys_send(union SIGNAL **signal,PROCESS dst,
-			      char* file,int line) {
-  SIGSELECT **ziggy = (SIGSELECT**)signal;
-  printf("%s:%d 0x%x Send signal 0x%x(0x%x) to 0x%x\r\n",
-	 file,line,current_process(),ziggy[0][0],*ziggy,dst);
-  send(signal,dst);
-}
-#define send(signal,dst) erts_ose_sys_send(signal,dst,__FILE__,__LINE__)
-
-static void erts_ose_sys_send_w_sender(union SIGNAL **signal,
-				       PROCESS sender,PROCESS dst,
-				       char* file,int line) {
-  SIGSELECT **ziggy = (SIGSELECT**)signal;
-  printf("%s:%d 0x%x Send signal 0x%x(0x%x) to 0x%x as 0x%x\r\n",
-	 file,line,current_process(),ziggy[0][0],*ziggy,dst,sender);
-  send_w_sender(signal,sender,dst);
-}
-#define send_w_sender(signal,sender,dst) \
-  erts_ose_sys_send_w_sender(signal,sender,dst,__FILE__,__LINE__)
-
-
-static union SIGNAL *erts_ose_sys_receive(SIGSELECT *sigsel,
-					  char *file,
-					  int line) {
-  SIGSELECT *sig;
-  int i;
-
-  printf("%s:%d 0x%x receive({%d,",file,line,current_process(),sigsel[0]);
-  for (i = 1; i < sigsel[0]; i++)
-    printf("0x%x, ",sigsel[i]);
-  if (sigsel[0] != 0)
-    printf("0x%x",sigsel[i]);
-  printf("})\n");
-  sig = (SIGSELECT*)receive(sigsel);
-  printf("%s:%d 0x%x got 0x%x from 0x%x\n",file,line,current_process(),
-	 *sig,sender((union SIGNAL**)(&sig)));
-  return (union SIGNAL*)sig;
-}
-#define receive(SIGSEL) erts_ose_sys_receive(SIGSEL,__FILE__,__LINE__)
-
-static union SIGNAL *erts_ose_sys_receive_w_tmo(OSTIME tmo,SIGSELECT *sigsel,
-						char *file,int line) {
-  SIGSELECT *sig;
-  int i;
-  if (tmo == 0) {
-    sig = (SIGSELECT*)receive_w_tmo(tmo,sigsel);
-    if (sig != NULL) {
-      printf("%s:%d 0x%x receive_w_tmo(0,{%d,",file,line,current_process(),
-	     sigsel[0]);
-      for (i = 1; i < sigsel[0]; i++)
-	printf("0x%x, ",sigsel[i]);
-      if (sigsel[0] != 0)
-	printf("0x%x",sigsel[i]);
-      printf("})\n");
-      printf("%s:%d 0x%x got 0x%x from 0x%x\n",file,line,current_process(),
-	     *sig,sender((union SIGNAL**)(&sig)));
-    }
-  } else {
-    printf("%s:%d 0x%x receive_w_tmo(%u,{%d,",file,line,current_process(),tmo,
-	   sigsel[0]);
-      for (i = 1; i < sigsel[0]; i++)
-	printf("0x%x, ",sigsel[i]);
-      if (sigsel[0] != 0)
-	printf("0x%x",sigsel[i]);
-      printf("})\n");
-      sig = (SIGSELECT*)receive_w_tmo(tmo,sigsel);
-      printf("%s:%d 0x%x got ",file,line,current_process());
-      if (sig == NULL)
-	printf("TIMEOUT\n");
-      else
-	printf("0x%x from 0x%x\n",*sig,sender((union SIGNAL**)(&sig)));
-  }
-
-  return (union SIGNAL*)sig;
-}
-
-#define receive_w_tmo(tmo,sigsel) erts_ose_sys_receive_w_tmo(tmo,sigsel, \
-							     __FILE__,__LINE__)
-
-static union SIGNAL *erts_ose_sys_receive_fsem(OSTIME tmo,SIGSELECT *sigsel,
-					       OSFSEMVAL fsem,
-					       char *file,int line) {
-  SIGSELECT *sig;
-  int i;
-  if (tmo == 0) {
-    sig = (SIGSELECT*)receive_fsem(tmo,sigsel,fsem);
-    if (sig != NULL && sig != OS_RCV_FSEM) {
-      printf("%s:%d 0x%x receive_fsem(0,{%d,",file,line,current_process(),
-	     sigsel[0]);
-      for (i = 1; i < sigsel[0]; i++)
-	printf("0x%x, ",sigsel[i]);
-      if (sigsel[0] != 0)
-	printf("0x%x",sigsel[i]);
-      printf("},%d)\n",fsem);
-      printf("%s:%d 0x%x got 0x%x from 0x%x\n",file,line,current_process(),
-	     *sig,sender((union SIGNAL**)(&sig)));
-    }
-  } else {
-    printf("%s:%d 0x%x receive_fsem(%u,{%d,",file,line,current_process(),tmo,
-	   sigsel[0]);
-      for (i = 1; i < sigsel[0]; i++)
-	printf("0x%x, ",sigsel[i]);
-      if (sigsel[0] != 0)
-	printf("0x%x",sigsel[i]);
-      printf("},%d)\n",fsem);
-      sig = (SIGSELECT*)receive_fsem(tmo,sigsel,fsem);
-      printf("%s:%d 0x%x got ",file,line,current_process());
-      if (sig == NULL)
-	printf("TIMEOUT\n");
-      else if (sig == OS_RCV_FSEM)
-	printf("FSEM\n");
-      else
-	printf("0x%x from 0x%x\n",*sig,sender((union SIGNAL**)(&sig)));
-  }
-
-  return (union SIGNAL*)sig;
-}
-
-#define receive_fsem(tmo,sigsel,fsem) \
-  erts_ose_sys_receive_fsem(tmo,sigsel,fsem,__FILE__,__LINE__)
-*/
-#endif  /* _ERL_OSE_SYS_H */
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/erl_poll.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_poll.c
--- otp_src_18.3.4.5/erts/emulator/sys/ose/erl_poll.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erl_poll.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,818 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2006-2012. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-/*
- * Description:	Poll interface suitable for ERTS on OSE with or without
- *              SMP support.
- *
- *		The interface is currently implemented using:
- *                - receive + receive_fsem
- *
- * Author: 	Lukas Larsson
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include "erl_thr_progress.h"
-#include "erl_driver.h"
-#include "erl_alloc.h"
-#include "erl_poll.h"
-
-#define NOFILE    4096
-
-/*
- * Some debug macros
- */
-
-/* #define HARDDEBUG
-#define HARDTRACE*/
-#ifdef HARDDEBUG
-#ifdef HARDTRACE
-#define HARDTRACEF(X, ...) { fprintf(stderr, X, __VA_ARGS__); fprintf(stderr,"\r\n"); }
-#else
-#define HARDTRACEF(...)
-#endif
-
-#else
-#define HARDTRACEF(X,...)
-#define HARDDEBUGF(...)
-#endif
-
-#if 0
-#define ERTS_POLL_DEBUG_PRINT
-#endif
-
-#if defined(DEBUG) && 0
-#define HARD_DEBUG
-#endif
-
-#  define SEL_ALLOC	erts_alloc
-#  define SEL_REALLOC	realloc_wrap
-#  define SEL_FREE	erts_free
-
-#ifdef ERTS_SMP
-
-#define ERTS_POLLSET_LOCK(PS) \
-  erts_smp_mtx_lock(&(PS)->mtx)
-#define ERTS_POLLSET_UNLOCK(PS) \
-  erts_smp_mtx_unlock(&(PS)->mtx)
-
-#else
-
-#define ERTS_POLLSET_LOCK(PS)
-#define ERTS_POLLSET_UNLOCK(PS)
-
-#endif
-
-/*
- * --- Data types ------------------------------------------------------------
- */
-
-union SIGNAL {
-    SIGSELECT sig_no;
-};
-
-typedef struct erts_sigsel_item_ ErtsSigSelItem;
-
-struct erts_sigsel_item_ {
-    ErtsSigSelItem *next;
-    ErtsSysFdType fd;
-    ErtsPollEvents events;
-};
-
-typedef struct erts_sigsel_info_ ErtsSigSelInfo;
-
-struct erts_sigsel_info_ {
-    ErtsSigSelInfo *next;
-    SIGSELECT signo;
-    ErlDrvOseEventId (*decode)(union SIGNAL* sig);
-    ErtsSigSelItem *fds;
-};
-
-struct ErtsPollSet_ {
-    SIGSELECT *sigs;
-    ErtsSigSelInfo *info;
-    Uint sig_count;
-    Uint item_count;
-    PROCESS interrupt;
-    erts_atomic32_t wakeup_state;
-    erts_atomic64_t timeout_time;
-#ifdef ERTS_SMP
-    erts_smp_mtx_t mtx;
-#endif
-};
-
-static int max_fds = -1;
-
-static ERTS_INLINE void
-init_timeout_time(ErtsPollSet ps)
-{
-    erts_atomic64_init_nob(&ps->timeout_time,
-			   (erts_aint64_t) ERTS_MONOTONIC_TIME_MAX);
-}
-
-static ERTS_INLINE void
-set_timeout_time(ErtsPollSet ps, ErtsMonotonicTime time)
-{
-    erts_atomic64_set_relb(&ps->timeout_time,
-			   (erts_aint64_t) time);
-}
-
-static ERTS_INLINE ErtsMonotonicTime
-get_timeout_time(ErtsPollSet ps)
-{
-    return (ErtsMonotonicTime) erts_atomic64_read_acqb(&ps->timeout_time);
-}
-
-#define ERTS_POLL_NOT_WOKEN		((erts_aint32_t) (1 << 0))
-#define ERTS_POLL_WOKEN_INTR		((erts_aint32_t) (1 << 1))
-#define ERTS_POLL_WOKEN_TIMEDOUT	((erts_aint32_t) (1 << 2))
-#define ERTS_POLL_WOKEN_IO_READY	((erts_aint32_t) (1 << 3))
-#define ERTS_POLL_SLEEPING	        ((erts_aint32_t) (1 << 4))
-
-/* signal list prototypes */
-static ErtsSigSelInfo *get_sigsel_info(ErtsPollSet ps, SIGSELECT signo);
-static ErtsSigSelItem *get_sigsel_item(ErtsPollSet ps, ErtsSysFdType fd);
-static ErtsSigSelInfo *add_sigsel_info(ErtsPollSet ps, ErtsSysFdType fd,
-				       ErlDrvOseEventId (*decode)(union SIGNAL* sig));
-static ErtsSigSelItem *add_sigsel_item(ErtsPollSet ps, ErtsSysFdType fd,
-				       ErlDrvOseEventId (*decode)(union SIGNAL* sig));
-static int del_sigsel_info(ErtsPollSet ps, ErtsSigSelInfo *info);
-static int del_sigsel_item(ErtsPollSet ps, ErtsSigSelItem *item);
-static int update_sigsel(ErtsPollSet ps);
-
-static ErtsSigSelInfo *
-get_sigsel_info(ErtsPollSet ps, SIGSELECT signo) {
-    ErtsSigSelInfo *curr = ps->info;
-    while (curr != NULL) {
-	if (curr->signo == signo)
-	    return curr;
-	curr = curr->next;
-    }
-    return NULL;
-}
-
-static ErtsSigSelItem *
-get_sigsel_item(ErtsPollSet ps, ErtsSysFdType fd) {
-    ErtsSigSelInfo *info = get_sigsel_info(ps,fd->signo);
-    ErtsSigSelItem *curr;
-
-    if (info == NULL)
-	return NULL;
-
-    curr = info->fds;
-
-    while (curr != NULL) {
-	if (curr->fd->id == fd->id) {
-	    ASSERT(curr->fd->signo == fd->signo);
-	    return curr;
-	}
-	curr = curr->next;
-    }
-    return NULL;
-}
-
-static ErtsSigSelInfo *
-add_sigsel_info(ErtsPollSet ps, ErtsSysFdType fd,
-		ErlDrvOseEventId (*decode)(union SIGNAL* sig)) {
-    ErtsSigSelInfo *info = SEL_ALLOC(ERTS_ALC_T_POLLSET,
-		       sizeof(ErtsSigSelInfo));
-    info->next = ps->info;
-    info->fds = NULL;
-    info->signo = fd->signo;
-    info->decode = decode;
-    ps->info = info;
-    ps->sig_count++;
-    return info;
-}
-
-static ErtsSigSelItem *
-add_sigsel_item(ErtsPollSet ps, ErtsSysFdType fd,
-		ErlDrvOseEventId (*decode)(union SIGNAL* sig)) {
-    ErtsSigSelInfo *info = get_sigsel_info(ps,fd->signo);
-    ErtsSigSelItem *item = SEL_ALLOC(ERTS_ALC_T_POLLSET,
-			   sizeof(ErtsSigSelItem));
-    if (info == NULL)
-	info = add_sigsel_info(ps, fd, decode);
-    if (info->decode != decode) {
-	erts_dsprintf_buf_t *dsbufp = erts_create_logger_dsbuf();
-	erts_dsprintf(dsbufp, "erts_poll_control() inconsistency: multiple resolve_signal functions for same signal (%d)\n",
-	    fd->signo);
-	erts_send_error_to_logger_nogl(dsbufp);
-    }
-    ASSERT(info->decode == decode);
-    item->next = info->fds;
-    item->fd = fd;
-    item->events = 0;
-    info->fds = item;
-    ps->item_count++;
-    return item;
-}
-
-static int del_sigsel_info(ErtsPollSet ps, ErtsSigSelInfo *info) {
-    ErtsSigSelInfo *curr, *prev;
-
-    if (ps->info == info) {
-	ps->info = ps->info->next;
-    } else {
-	curr = ps->info->next;
-	prev = ps->info;
-
-	while (curr != info) {
-	    if (curr == NULL)
-		return 1;
-	    prev = curr;
-	    curr = curr->next;
-	}
-	prev->next = curr->next;
-    }
-
-    ps->sig_count--;
-    SEL_FREE(ERTS_ALC_T_POLLSET, info);
-    return 0;
-}
-
-static int del_sigsel_item(ErtsPollSet ps, ErtsSigSelItem *item) {
-    ErtsSigSelInfo *info = get_sigsel_info(ps,item->fd->signo);
-    ErtsSigSelItem *curr, *prev;
-
-    ps->item_count--;
-    ASSERT(ps->item_count >= 0);
-
-    if (info->fds == item) {
-	info->fds = info->fds->next;
-	SEL_FREE(ERTS_ALC_T_POLLSET,item);
-	if (info->fds == NULL)
-	    return del_sigsel_info(ps,info);
-	return 0;
-    }
-
-    curr = info->fds->next;
-    prev = info->fds;
-
-    while (curr != item) {
-	if (curr == NULL) {
-	    /* We did not find an item to delete so we have to
-	     * increment item count again.
-	     */
-	    ps->item_count++;
-	    return 1;
-	}
-	prev = curr;
-	curr = curr->next;
-    }
-    prev->next = curr->next;
-    SEL_FREE(ERTS_ALC_T_POLLSET,item);
-    return 0;
-}
-
-#ifdef ERTS_SMP
-
-static void update_redir_tables(ErtsPollSet ps) {
-  struct OS_redir_entry *redir_table;
-  PROCESS sched_1 = ERTS_SCHEDULER_IX(0)->tid.id;
-  int i;
-  redir_table = SEL_ALLOC(ERTS_ALC_T_POLLSET,
-			  sizeof(struct OS_redir_entry)*(ps->sig_count+1));
-
-  redir_table[0].sig = ps->sig_count+1;
-  redir_table[0].pid = 0;
-
-  for (i = 1; i < ps->sig_count+1; i++) {
-    redir_table[i].sig = ps->sigs[i];
-    redir_table[i].pid = sched_1;
-  }
-
-  for (i = 1; i < erts_no_schedulers; i++) {
-    ErtsSchedulerData *esdp = ERTS_SCHEDULER_IX(i);
-    set_redirection(esdp->tid.id,redir_table);
-  }
-
-  SEL_FREE(ERTS_ALC_T_POLLSET,redir_table);
-}
-
-#endif
-
-static int update_sigsel(ErtsPollSet ps) {
-    ErtsSigSelInfo *info = ps->info;
-
-    int i;
-
-    if (ps->sigs != NULL)
-	SEL_FREE(ERTS_ALC_T_POLLSET,ps->sigs);
-
-    if (ps->sig_count == 0) {
-	/* If there are no signals we place a non-valid signal to make sure that
-	 * we do not trigger on a any unrelated signals which are sent to the
-	 * process.
-	 */
-	ps->sigs = SEL_ALLOC(ERTS_ALC_T_POLLSET,sizeof(SIGSELECT)*(2));
-	ps->sigs[0] = 1;
-	ps->sigs[1] = ERTS_SIGNAL_INVALID;
-	return 0;
-    }
-
-    ps->sigs = SEL_ALLOC(ERTS_ALC_T_POLLSET,sizeof(SIGSELECT)*(ps->sig_count+1));
-    ps->sigs[0] = ps->sig_count;
-
-    for (i = 1; info != NULL; i++, info = info->next)
-	ps->sigs[i] = info->signo;
-
-#ifdef ERTS_SMP
-    update_redir_tables(ps);
-#endif
-
-    return 0;
-}
-
-static ERTS_INLINE void
-wake_poller(ErtsPollSet ps)
-{
-  erts_aint32_t wakeup_state;
-
-  ERTS_THR_MEMORY_BARRIER;
-  wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
-  while (wakeup_state != ERTS_POLL_WOKEN_IO_READY
-	 && wakeup_state != ERTS_POLL_WOKEN_INTR) {
-    erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-						  ERTS_POLL_WOKEN_INTR,
-						  wakeup_state);
-    if (act == wakeup_state) {
-      wakeup_state = act;
-      break;
-    }
-    wakeup_state = act;
-  }
-  if (wakeup_state == ERTS_POLL_SLEEPING) {
-    /*
-     * Since we don't know the internals of signal_fsem() we issue
-     * a memory barrier as a safety precaution ensuring that
-     * the store we just made to wakeup_state wont be reordered
-     * with loads in signal_fsem().
-     */
-    ERTS_THR_MEMORY_BARRIER;
-    signal_fsem(ps->interrupt);
-  }
-}
-
-static ERTS_INLINE void
-reset_interrupt(ErtsPollSet ps)
-{
-    /* We need to keep io-ready if set */
-    erts_aint32_t wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
-    while (wakeup_state != ERTS_POLL_NOT_WOKEN &&
-	   wakeup_state != ERTS_POLL_SLEEPING) {
-	erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-						      ERTS_POLL_NOT_WOKEN,
-						      wakeup_state);
-	if (wakeup_state == act)
-	    break;
-	wakeup_state = act;
-    }
-    ERTS_THR_MEMORY_BARRIER;
-}
-
-static ERTS_INLINE void
-set_interrupt(ErtsPollSet ps)
-{
-    wake_poller(ps);
-}
-
-void erts_poll_interrupt(ErtsPollSet ps,int set) {
-    HARDTRACEF("erts_poll_interrupt called!\n");
-
-    if (!set)
-	reset_interrupt(ps);
-    else
-	set_interrupt(ps);
-
-}
-
-void erts_poll_interrupt_timed(ErtsPollSet ps,
-			       int set,
-			       ErtsTimeoutTime timeout_time) {
-    HARDTRACEF("erts_poll_interrupt_timed called!\n");
-
-    if (!set)
-	reset_interrupt(ps);
-    else if (get_timeout_time(ps) > timeout_time)
-        set_interrupt(ps);
-}
-
-ErtsPollEvents erts_poll_control(ErtsPollSet ps, ErtsSysFdType fd,
-	ErtsPollEvents pe, int on, int* do_wake) {
-    ErtsSigSelItem *curr;
-    ErtsPollEvents new_events;
-    int old_sig_count;
-
-    HARDTRACEF(
-	    "%ux: In erts_poll_control, fd = %d, pe = %d, on = %d, *do_wake = %d, curr = 0x%xu",
-	    ps, fd, pe, on, do_wake, curr);
-
-    ERTS_POLLSET_LOCK(ps);
-
-    if (on && (pe & ERTS_POLL_EV_IN) && (pe & ERTS_POLL_EV_OUT)) {
-      /* Check to make sure both in and out are not used at the same time */
-      new_events = ERTS_POLL_EV_NVAL;
-      goto done;
-    }
-
-    curr = get_sigsel_item(ps, fd);
-    old_sig_count = ps->sig_count;
-
-    if (curr == NULL && on) {
-	curr = add_sigsel_item(ps, fd, fd->resolve_signal);
-    } else if (curr == NULL && !on) {
-        new_events = ERTS_POLL_EV_NVAL;
-	goto done;
-    }
-
-    new_events = curr->events;
-
-    if (pe == 0) {
-	*do_wake = 0;
-	goto done;
-    }
-
-    if (on) {
-	new_events |= pe;
-	curr->events = new_events;
-    } else {
-	new_events &= ~pe;
-	curr->events = new_events;
-	if (new_events == 0 && del_sigsel_item(ps, curr)) {
-	    new_events = ERTS_POLL_EV_NVAL;
-	    goto done;
-	}
-    }
-
-    if (ps->sig_count != old_sig_count) {
-      if (update_sigsel(ps))
-	new_events = ERTS_POLL_EV_NVAL;
-    }
-done:
-    ERTS_POLLSET_UNLOCK(ps);
-    HARDTRACEF("%ux: Out erts_poll_control", ps);
-    return new_events;
-}
-
-int erts_poll_wait(ErtsPollSet ps,
-		   ErtsPollResFd pr[],
-		   int *len,
-		   ErtsMonotonicTime timeout_time)
-{
-    int res = ETIMEDOUT, no_fds, currid = 0;
-    OSTIME timeout;
-    union SIGNAL *sig;
-    ErtsMonotonicTime current_time, diff_time, timeout;
-    // HARDTRACEF("%ux: In erts_poll_wait",ps);
-    if (ps->interrupt == (PROCESS)0)
-      ps->interrupt = current_process();
-
-    ASSERT(current_process() == ps->interrupt);
-    ASSERT(get_fsem(current_process()) == 0);
-    ASSERT(erts_atomic32_read_nob(&ps->wakeup_state) &
-	   (ERTS_POLL_NOT_WOKEN | ERTS_POLL_WOKEN_INTR));
-    /* Max no of spots avable in pr */
-    no_fds = *len;
-
-    *len = 0;
-
-    /* erts_printf("Entering erts_poll_wait(), timeout_time=%bps\n",
-		   timeout_time); */
-
-    if (timeout_time == ERTS_POLL_NO_TIMEOUT) {
-    no_timeout:
-	timeout = (OSTIME) 0;
-	save_timeout_time = ERTS_MONOTONIC_TIME_MIN;
-    }
-    else {
-	ErtsMonotonicTime current_time, diff_time;
-	current_time = erts_get_monotonic_time(NULL);
-	diff_time = timeout_time - current_time;
-	if (diff_time <= 0)
-	    goto no_timeout;
-	diff_time = (ERTS_MONOTONIC_TO_MSEC(diff_time - 1) + 1);
-	if (diff_time > INT_MAX)
-	    diff_time = INT_MAX;
-	timeout = (OSTIME) diff_time;
-	save_timeout_time = current_time;
-	save_timeout_time += ERTS_MSEC_TO_MONOTONIC(diff_time);
-    }
-
-    set_timeout_time(ps, save_timeout_time);
-
-    while (currid < no_fds) {
-      if (timeout > 0) {
-	erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-						      ERTS_POLL_SLEEPING,
-						      ERTS_POLL_NOT_WOKEN);
-	if (act == ERTS_POLL_NOT_WOKEN) {
-#ifdef ERTS_SMP
-	  erts_thr_progress_prepare_wait(NULL);
-#endif
-	  sig = receive_fsem(timeout, ps->sigs, 1);
-#ifdef ERTS_SMP
-	  erts_thr_progress_finalize_wait(NULL);
-#endif
-	} else {
-	  ASSERT(act == ERTS_POLL_WOKEN_INTR);
-	  sig = OS_RCV_FSEM;
-	}
-      } else
-	  sig = receive_w_tmo(0, ps->sigs);
-
-	if (sig == NULL) {
-	  if (timeout > 0) {
-	    erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-							  ERTS_POLL_WOKEN_TIMEDOUT,
-							  ERTS_POLL_SLEEPING);
-	    if (act == ERTS_POLL_WOKEN_INTR)
-	      /* Restore fsem as it was signaled but we got a timeout */
-	      wait_fsem(1);
-	    } else
-	    erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-				      ERTS_POLL_WOKEN_TIMEDOUT,
-				      ERTS_POLL_NOT_WOKEN);
-	    break;
-	} else if (sig == OS_RCV_FSEM) {
-	  ASSERT(erts_atomic32_read_nob(&ps->wakeup_state) == ERTS_POLL_WOKEN_INTR);
-	  break;
-	}
-       {
-          ErtsSigSelInfo *info = get_sigsel_info(ps, sig->sig_no);
-          struct erts_sys_fd_type fd = { sig->sig_no, info->decode(sig) };
-          ErtsSigSelItem *item = get_sigsel_item(ps, &fd);
-
-	  ASSERT(sig);
-          if (currid == 0 && timeout > 0) {
-	    erts_aint32_t act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-							  ERTS_POLL_WOKEN_IO_READY,
-							  ERTS_POLL_SLEEPING);
-	    if (act == ERTS_POLL_WOKEN_INTR) {
-	      /* Restore fsem as it was signaled but we got a msg */
-	      wait_fsem(1);
-	      act = erts_atomic32_cmpxchg_nob(&ps->wakeup_state,
-					      ERTS_POLL_WOKEN_IO_READY,
-					      ERTS_POLL_WOKEN_INTR);
-	    }
-	  } else if (currid == 0) {
-	    erts_atomic32_set_nob(&ps->wakeup_state,
-				  ERTS_POLL_WOKEN_IO_READY);
-	  }
-
-	  if (item == NULL) {
-	    erts_dsprintf_buf_t *dsbufp = erts_create_logger_dsbuf();
-	    erts_dsprintf(
-                dsbufp,
-                "erts_poll_wait() failed: found unkown signal id %d (signo %u) "
-		"(curr_proc 0x%x)\n",
-                fd.id, fd.signo, current_process());
-             erts_send_error_to_logger_nogl(dsbufp);
-	     timeout = 0;
-             /* Under normal circumstances the signal is deallocated by the
-              * driver that issued the select operation. But in this case
-              * there's no driver waiting for such signal so we have to
-              * deallocate it here */
-             if (sig)
-                 free_buf(&sig);
-	  } else {
-	    int i;
-	    struct erts_sys_fd_type *fd = NULL;
-	    ErtsPollOseMsgList *tl,*new;
-
-	    /* Check if this fd has already been triggered by a previous signal */
-	    for (i = 0; i < currid;i++) {
-	      if (pr[i].fd == item->fd) {
-		fd = pr[i].fd;
-		pr[i].events |= item->events;
-		break;
-	      }
-	    }
-
-	    /* First time this fd is triggered */
-	    if (fd == NULL) {
-	      pr[currid].fd = item->fd;
-	      pr[currid].events = item->events;
-	      fd = item->fd;
-	      timeout = 0;
-	      currid++;
-	    }
-
-	    /* Insert new signal in approriate list */
-	    new = erts_alloc(ERTS_ALC_T_FD_SIG_LIST,sizeof(ErtsPollOseMsgList));
-	    new->next = NULL;
-	    new->data = sig;
-
-	    ethr_mutex_lock(&fd->mtx);
-	    tl = fd->msgs;
-
-	    if (tl == NULL) {
-	      fd->msgs = new;
-	    } else {
-	      while (tl->next != NULL)
-		tl = tl->next;
-	      tl->next = new;
-	    }
-	    ethr_mutex_unlock(&fd->mtx);
-          }
-
-       }
-    }
-
-    {
-       erts_aint32_t wakeup_state = erts_atomic32_read_nob(&ps->wakeup_state);
-
-       switch (wakeup_state) {
-          case ERTS_POLL_WOKEN_IO_READY:
-             res = 0;
-             break;
-          case ERTS_POLL_WOKEN_INTR:
-             res = EINTR;
-             break;
-          case ERTS_POLL_WOKEN_TIMEDOUT:
-             res = ETIMEDOUT;
-             break;
-          case ERTS_POLL_NOT_WOKEN:
-             /* This happens when we get an invalid signal only */
-             res = EINVAL;
-             break;
-          default:
-             res = 0;
-             erts_exit(ERTS_ABORT_EXIT,
-                      "%s:%d: Internal error: Invalid wakeup_state=%d\n",
-                      __FILE__, __LINE__, (int) wakeup_state);
-       }
-    }
-
-    erts_atomic32_set_nob(&ps->wakeup_state, ERTS_POLL_NOT_WOKEN);
-    set_timeout_time(ps, ERTS_MONOTONIC_TIME_MAX);
-
-    *len = currid;
-
-    // HARDTRACEF("%ux: Out erts_poll_wait",ps);
-    return res;
-}
-
-int erts_poll_max_fds(void)
-{
-
-    HARDTRACEF("In/Out erts_poll_max_fds -> %d",max_fds);
-    return max_fds;
-}
-
-void erts_poll_info(ErtsPollSet ps,
-		    ErtsPollInfo *pip)
-{
-    Uint size = 0;
-    Uint num_events = 0;
-
-    size += sizeof(struct ErtsPollSet_);
-    size += sizeof(ErtsSigSelInfo)*ps->sig_count;
-    size += sizeof(ErtsSigSelItem)*ps->item_count;
-    size += sizeof(SIGSELECT)*(ps->sig_count+1);
-
-    pip->primary = "receive_fsem";
-
-    pip->fallback = NULL;
-
-    pip->kernel_poll = NULL;
-
-    pip->memory_size = size;
-
-    pip->poll_set_size = num_events;
-
-    pip->fallback_poll_set_size = 0;
-
-    pip->lazy_updates = 0;
-
-    pip->pending_updates = 0;
-
-    pip->batch_updates = 0;
-
-    pip->concurrent_updates = 0;
-
-
-    pip->max_fds = erts_poll_max_fds();
-    HARDTRACEF("%ux: Out erts_poll_info",ps);
-
-}
-
-ErtsPollSet erts_poll_create_pollset(void)
-{
-    ErtsPollSet ps = SEL_ALLOC(ERTS_ALC_T_POLLSET,
-			       sizeof(struct ErtsPollSet_));
-
-    ps->sigs       = NULL;
-    ps->sig_count  = 0;
-    ps->item_count = 0;
-    ps->info       = NULL;
-    ps->interrupt  = (PROCESS)0;
-    erts_atomic32_init_nob(&ps->wakeup_state, ERTS_POLL_NOT_WOKEN);
-    init_timeout_time(ps);
-#ifdef ERTS_SMP
-    erts_smp_mtx_init(&ps->mtx, "pollset");
-#endif
-    update_sigsel(ps);
-    HARDTRACEF("%ux: Out erts_poll_create_pollset",ps);
-    return ps;
-}
-
-void erts_poll_destroy_pollset(ErtsPollSet ps)
-{
-    ErtsSigSelInfo *info;
-    for (info = ps->info; ps->info != NULL; info = ps->info, ps->info = ps->info->next) {
-	ErtsSigSelItem *item;
-	for (item = info->fds; info->fds != NULL; item = info->fds, info->fds = info->fds->next)
-	    SEL_FREE(ERTS_ALC_T_POLLSET, item);
-	SEL_FREE(ERTS_ALC_T_POLLSET, info);
-    }
-
-    SEL_FREE(ERTS_ALC_T_POLLSET,ps->sigs);
-
-#ifdef ERTS_SMP
-    erts_smp_mtx_destroy(&ps->mtx);
-#endif
-
-    SEL_FREE(ERTS_ALC_T_POLLSET,ps);
-}
-
-void  erts_poll_init(void)
-{
-    HARDTRACEF("In %s", __FUNCTION__);
-    max_fds = 256;
-
-    HARDTRACEF("Out %s", __FUNCTION__);
-}
-
-
-/* OSE driver functions */
-
-union SIGNAL *erl_drv_ose_get_signal(ErlDrvEvent drv_ev) {
-    struct erts_sys_fd_type *ev = (struct erts_sys_fd_type *)drv_ev;
-    ethr_mutex_lock(&ev->mtx);
-    if (ev->msgs == NULL) {
-      ethr_mutex_unlock(&ev->mtx);
-      return NULL;
-    } else {
-      ErtsPollOseMsgList *msg = ev->msgs;
-      union SIGNAL *sig = (union SIGNAL*)msg->data;
-      ASSERT(msg->data);
-      ev->msgs = msg->next;
-      ethr_mutex_unlock(&ev->mtx);
-      erts_free(ERTS_ALC_T_FD_SIG_LIST,msg);
-      restore(sig);
-      return sig;
-    }
-}
-
-ErlDrvEvent
-erl_drv_ose_event_alloc(SIGSELECT signo, ErlDrvOseEventId id,
-			ErlDrvOseEventId (*resolve_signal)(union SIGNAL *sig), void *extra) {
-  struct erts_sys_fd_type *ev = erts_alloc(ERTS_ALC_T_DRV_EV,
-					   sizeof(struct erts_sys_fd_type));
-  ev->signo = signo;
-  ev->extra = extra;
-  ev->id = id;
-  ev->msgs = NULL;
-  ev->resolve_signal = resolve_signal;
-  ethr_mutex_init(&ev->mtx);
-  return (ErlDrvEvent)ev;
-}
-
-void erl_drv_ose_event_free(ErlDrvEvent drv_ev) {
-  struct erts_sys_fd_type *ev = (struct erts_sys_fd_type *)drv_ev;
-  ASSERT(ev->msgs == NULL);
-  ethr_mutex_destroy(&ev->mtx);
-  erts_free(ERTS_ALC_T_DRV_EV,ev);
-}
-
-void erl_drv_ose_event_fetch(ErlDrvEvent drv_ev, SIGSELECT *signo,
-                             ErlDrvOseEventId *id, void **extra) {
-  struct erts_sys_fd_type *ev = (struct erts_sys_fd_type *)drv_ev;
-  if (signo)
-    *signo = ev->signo;
-  if (extra)
-    *extra = ev->extra;
-  if (id)
-    *id = ev->id;
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/erts.sig otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erts.sig
--- otp_src_18.3.4.5/erts/emulator/sys/ose/erts.sig	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/erts.sig	1970-01-01 03:00:00.000000000 +0300
@@ -1,17 +0,0 @@
-#ifndef ERTS_OSE_SIGNALS
-#define ERTS_OSE_SIGNALS
-
-#ifndef ERTS_OSE_SIGNAL_BASE
-#define ERTS_OSE_SIGNAL_BASE 0x01900280
-#endif
-
-#define ERTS_SIGNAL_INVALID        ERTS_OSE_SIGNAL_BASE
-#define ERTS_SIGNAL_FD_DRV_CONFIG  ERTS_OSE_SIGNAL_BASE+1
-#define ERTS_SIGNAL_FD_DRV_ASYNC   ERTS_OSE_SIGNAL_BASE+2
-#define ERTS_SIGNAL_OSE_DRV_ATTACH ERTS_OSE_SIGNAL_BASE+3
-#define ERTS_SIGNAL_OSE_DRV_HUNT   ERTS_OSE_SIGNAL_BASE+4
-
-#define ERTS_SIGNAL_RUN_ERL_SETUP  ERTS_OSE_SIGNAL_BASE+100
-#define ERTS_SIGNAL_RUN_ERL_DAEMON ERTS_OSE_SIGNAL_BASE+101
-
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/gcc_4.4.3_lm_ppc.lcf otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/gcc_4.4.3_lm_ppc.lcf
--- otp_src_18.3.4.5/erts/emulator/sys/ose/gcc_4.4.3_lm_ppc.lcf	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/gcc_4.4.3_lm_ppc.lcf	1970-01-01 03:00:00.000000000 +0300
@@ -1,182 +0,0 @@
-/*******************************************************************************
- * Copyright (C) 2013-2014 by Enea Software AB,
- * All rights reserved.
- *
- * Redistribution and use in source and binary forms, with or without
- * modification, are permitted provided that the following conditions are met:
- *
- * 1. Redistributions of source code must retain the above copyright notice,
- *    this list of conditions and the following disclaimer.
- *
- * 2. Redistributions in binary form must reproduce the above copyright notice,
- *    this list of conditions and the following disclaimer in the documentation
- *    and/or other materials provided with the distribution.
- *
- * 3. Neither the name of the copyright holder nor the names of its contributors
- *    may be used to endorse or promote products derived from this software
- *    without specific prior written permission.
- *
- * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
- * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
- * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
- * ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
- * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
- * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
- * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
- * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
- * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
- * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
- * POSSIBILITY OF SUCH DAMAGE.
- ******************************************************************************/
-
-OUTPUT_FORMAT("elf32-powerpc", "elf32-powerpc", "elf32-powerpc")
-OUTPUT_ARCH("powerpc")
-ENTRY("crt0_lm")
-MEMORY
-{
- rom : ORIGIN = 0x01000000, LENGTH = 0x01000000
- ram : ORIGIN = 0x02000000, LENGTH = 0x01000000
-}
-PHDRS
-{
-  ph_conf PT_LOAD ;
- ph_rom PT_LOAD ;
- ph_ram PT_LOAD ;
-}
-SECTIONS
-{
- .text :
- {
-  *(.text_first)
-  *(.text)
-  *(.text.*)
-  *(.stub)
-  *(oscode)
-  *(.init*)
-  *(.fini*)
-  *(.gnu.warning)
-  *(.gnu.linkonce.t.*)
-  *(.glue_7t)
-  *(.glue_7)
- } > rom :ph_rom = 0
- .ose_sfk_biosentry :
- {
-  *(.ose_sfk_biosentry)
-        } > rom :ph_rom
- .ctors :
- {
-  __CTOR_LIST__ = .;
-  *(.ctors)
-  *(SORT(.ctors.*))
-  __CTOR_END__ = .;
- } > rom :ph_rom
- .dtors :
- {
-  __DTOR_LIST__ = .;
-  *(.dtors)
-  *(SORT(.dtors.*))
-  __DTOR_END__ = .;
- } > rom :ph_rom
- OSESYMS :
- {
-  *(.osesyms)
- } > rom :ph_rom
- .rodata :
- {
-  *(.rodata)
-  *(.rodata.*)
-  *(.gnu.linkonce.r.*)
- } > rom :ph_rom
- .eh_frame_hdr :
- {
-  *(.eh_frame_hdr)
- } > rom :ph_rom
- .eh_frame :
- {
-  __EH_FRAME_BEGIN__ = .;
-  *(.eh_frame)
-  LONG(0)
-  __EH_FRAME_END__ = .;
- } > rom :ph_rom
- .gcc_except_table :
- {
-  *(.gcc_except_table .gcc_except_table.*)
- } > rom :ph_rom
- .sdata2 :
- {
-  PROVIDE (_SDA2_BASE_ = .);
-  *(.sdata2)
-  *(.sdata2.*)
-  *(.gnu.linkonce.s2.*)
- } > rom :ph_rom
- .sbss2 :
- {
-  *(.sbss2)
-  *(.sbss2.*)
-  *(.gnu.linkonce.sb2.*)
- } > rom :ph_rom
- LMCONF :
- {
-  obj/?*?/ose_confd.o(.rodata)
-  *(LMCONF)
- } > rom :ph_conf
- .data :
- {
-  LONG(0xDEADBABE)
-  *(.data)
-  *(.data.*)
-  *(.gnu.linkonce.d.*)
-  SORT(CONSTRUCTORS)
-  . = ALIGN(0x10);
- } > ram :ph_ram = 0
-        .sdata2 :
-   {
-         _SDA2_BASE_ = .;
-             *(.sdata2 .sdata2.* .gnu.linkonce.s2.*)
-   }> ram :ph_ram
- .sdata :
- {
-         PROVIDE (_SDA_BASE_ = .);
-  *(.sdata)
-  *(.sdata.*)
-  *(.gnu.linkonce.s.*)
- } > ram :ph_ram
- .sbss :
- {
-  *(.sbss)
-  *(.sbss.*)
-  *(.scommon)
-  *(.gnu.linkonce.sb.*)
- } > ram :ph_ram
- .bss (NOLOAD) :
- {
-  *(.bss)
-  *(.bss.*)
-  *(COMMON)
-  *(.gnu.linkonce.b.*)
-  *(.osvars)
- } > ram :ph_ram
- .ignore (NOLOAD) :
- {
-  *(.rel.dyn)
- } > ram :ph_ram
- .debug 0 : { *(.debug) }
- .line 0 : { *(.line) }
- .debug_srcinfo 0 : { *(.debug_srcinfo) }
- .debug_sfnames 0 : { *(.debug_sfnames) }
- .debug_aranges 0 : { *(.debug_aranges) }
- .debug_pubnames 0 : { *(.debug_pubnames) }
- .debug_info 0 : { *(.debug_info) *(.gnu.linkonce.wi.*) }
- .debug_abbrev 0 : { *(.debug_abbrev) }
- .debug_line 0 : { *(.debug_line) }
- .debug_frame 0 : { *(.debug_frame) }
- .debug_str 0 : { *(.debug_str) }
- .debug_loc 0 : { *(.debug_loc) }
- .debug_macinfo 0 : { *(.debug_macinfo) }
- .debug_weaknames 0 : { *(.debug_weaknames) }
- .debug_funcnames 0 : { *(.debug_funcnames) }
- .debug_typenames 0 : { *(.debug_typenames) }
- .debug_varnames 0 : { *(.debug_varnames) }
-}
-__OSESYMS_START = ADDR(OSESYMS);
-__OSESYMS_END = ADDR(OSESYMS) + SIZEOF(OSESYMS);
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/gcc_4.6.3_lm_ppc.lcf otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/gcc_4.6.3_lm_ppc.lcf
--- otp_src_18.3.4.5/erts/emulator/sys/ose/gcc_4.6.3_lm_ppc.lcf	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/gcc_4.6.3_lm_ppc.lcf	1970-01-01 03:00:00.000000000 +0300
@@ -1,242 +0,0 @@
-/*******************************************************************************
- * Copyright (C) 2013-2014 by Enea Software AB,
- * All rights reserved.
- *
- * Redistribution and use in source and binary forms, with or without
- * modification, are permitted provided that the following conditions are met:
- *
- * 1. Redistributions of source code must retain the above copyright notice,
- *    this list of conditions and the following disclaimer.
- *
- * 2. Redistributions in binary form must reproduce the above copyright notice,
- *    this list of conditions and the following disclaimer in the documentation
- *    and/or other materials provided with the distribution.
- *
- * 3. Neither the name of the copyright holder nor the names of its contributors
- *    may be used to endorse or promote products derived from this software
- *    without specific prior written permission.
- *
- * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
- * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
- * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
- * ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
- * LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
- * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
- * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
- * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
- * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
- * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
- * POSSIBILITY OF SUCH DAMAGE.
- ******************************************************************************/
-
-OUTPUT_FORMAT("elf32-powerpc", "elf32-powerpc", "elf32-powerpc")
-OUTPUT_ARCH("powerpc")
-
-ENTRY("crt0_lm")
-
-/* Note:
- * You may have to increase the length of the "rom" memory region and the
- * origin and length of the "ram" memory region below depending on the size
- * of the code and data in your load module.
- */
-
-MEMORY
-{
-	conf : ORIGIN = 0x00100000, LENGTH = 0x00030000
-	rom  : ORIGIN = 0x01000000, LENGTH = 0x01000000
-	ram  : ORIGIN = 0x03000000, LENGTH = 0x01000000
-}
-
-PHDRS
-{
-	ph_conf PT_LOAD ;
-	ph_rom PT_LOAD ;
-	ph_ram PT_LOAD ;
-}
-
-SECTIONS
-{
-/*---------------------------------------------------------------------------
- *		Load module configuration area
- *-------------------------------------------------------------------------*/
-
-	/* Load module configuration section. */
-	LMCONF :
-	{
-		obj/?*?/ose_confd.o(.rodata)
-		*(LMCONF)
-	} > conf :ph_conf
-
-/*---------------------------------------------------------------------------
- *		Read-only area
- *-------------------------------------------------------------------------*/
-
-	/* Code section. */
-	.text :
-	{
-		*(.text)
-		*(.text.*)
-		*(.stub)
-		*(oscode)
-		*(.init*)
-		*(.fini*)
-		*(.gnu.warning)
-		*(.gnu.linkonce.t.*)
-	} > rom :ph_rom = 0
-
-	/* OSE symbols section. */
-	OSESYMS :
-	{
-		*(.osesyms)
-	} > rom :ph_rom
-
-	/* Read-only data section. */
-	.rodata :
-	{
-		*(.rodata)
-		*(.rodata.*)
-		*(.gnu.linkonce.r.*)
-	} > rom :ph_rom
-
-	/* C++ exception handling section. */
-	.eh_frame :
-	{
-		__EH_FRAME_BEGIN__ = .;
-		*(.eh_frame)
-		LONG(0)
-		__EH_FRAME_END__ = .;
-	} > rom :ph_rom
-
-	/* C++ exception handling section. */
-	.gcc_except_table :
-	{
-		*(.gcc_except_table .gcc_except_table.*)
-	} > rom :ph_rom
-
-	/* PowerPC EABI initialized read-only data section. */
-	.sdata2 :
-	{
-		PROVIDE (_SDA2_BASE_ = .);
-		*(.sdata2)
-		*(.sdata2.*)
-		*(.gnu.linkonce.s2.*)
-	} > rom :ph_rom
-
-	/* PowerPC EABI uninitialized read-only data section. */
-	.sbss2 :
-	{
-		*(.sbss2)
-		*(.sbss2.*)
-		*(.gnu.linkonce.sb2.*)
-	} > rom :ph_rom
-
-/*---------------------------------------------------------------------------
- *		Read-write area
- *-------------------------------------------------------------------------*/
-
-	/*-------------------------------------------------------------------
-	 * Initialized data (copied by PM)
-	 *-----------------------------------------------------------------*/
-
-	/* Data section. */
-	.data :
-	{
-		*(.data)
-		*(.data.*)
-		*(.gnu.linkonce.d.*)
-		SORT(CONSTRUCTORS)
-	} > ram :ph_ram
-
-	/* C++ constructor section. */
-	.ctors :
-	{
-		__CTOR_LIST__ = .;
-		*(.ctors)
-		*(SORT(.ctors.*))
-		__CTOR_END__ = .;
-	} > ram :ph_ram
-
-	/* C++ destructor section. */
-	.dtors :
-	{
-		__DTOR_LIST__ = .;
-		*(.dtors)
-		*(SORT(.dtors.*))
-		__DTOR_END__ = .;
-	} > ram :ph_ram
-
-
-	/* Small data section. */
-	.sdata ALIGN(0x10) :
-	{
-		PROVIDE (_SDA_BASE_ = .);
-		*(.sdata)
-		*(.sdata.*)
-		*(.gnu.linkonce.s.*)
-	} > ram :ph_ram
-
-	/*-------------------------------------------------------------------
-	 * Uninitialized data (cleared by PM)
-	 *-----------------------------------------------------------------*/
-
-	/* Small bss section. */
-	.sbss :
-	{
-		*(.sbss)
-		*(.sbss.*)
-		*(.scommon)
-		*(.gnu.linkonce.sb.*)
-	} > ram :ph_ram
-
-	/* Bss section. */
-	.bss :
-	{
-		*(.bss)
-		*(.bss.*)
-		*(COMMON)
-		*(.gnu.linkonce.b.*)
-	} > ram :ph_ram
-
-/*---------------------------------------------------------------------------
- *		Debug information
- *-------------------------------------------------------------------------*/
-
-	/*
-	 * Stabs debug sections.
-	 */
-
-	.stab            0 : { *(.stab) }
-	.stabstr         0 : { *(.stabstr) }
-	.stab.excl       0 : { *(.stab.excl) }
-	.stab.exclstr    0 : { *(.stab.exclstr) }
-	.stab.index      0 : { *(.stab.index) }
-	.stab.indexstr   0 : { *(.stab.indexstr) }
-	.comment         0 : { *(.comment) }
-
-	/*
-	 * DWARF debug sections.
-	 */
-
-	/* DWARF 1 */
-	.debug           0 : { *(.debug) }
-	.line            0 : { *(.line) }
-	/* GNU DWARF 1 extensions */
-	.debug_srcinfo   0 : { *(.debug_srcinfo) }
-	.debug_sfnames   0 : { *(.debug_sfnames) }
-	/* DWARF 1.1 and DWARF 2 */
-	.debug_aranges   0 : { *(.debug_aranges) }
-	.debug_pubnames  0 : { *(.debug_pubnames) }
-	/* DWARF 2 */
-	.debug_info      0 : { *(.debug_info) *(.gnu.linkonce.wi.*) }
-	.debug_abbrev    0 : { *(.debug_abbrev) }
-	.debug_line      0 : { *(.debug_line) }
-	.debug_frame     0 : { *(.debug_frame) }
-	.debug_str       0 : { *(.debug_str) }
-	.debug_loc       0 : { *(.debug_loc) }
-	.debug_macinfo   0 : { *(.debug_macinfo) }
-	/* SGI/MIPS DWARF 2 extensions */
-	.debug_weaknames 0 : { *(.debug_weaknames) }
-	.debug_funcnames 0 : { *(.debug_funcnames) }
-	.debug_typenames 0 : { *(.debug_typenames) }
-	.debug_varnames  0 : { *(.debug_varnames) }
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/sys.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/sys.c
--- otp_src_18.3.4.5/erts/emulator/sys/ose/sys.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/sys.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,1847 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 1996-2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-#include "sys/time.h"
-#include "time.h"
-#include "sys/uio.h"
-#include "termios.h"
-#include "ctype.h"
-#include "termios.h"
-
-#ifdef HAVE_FCNTL_H
-#include "fcntl.h"
-#endif
-
-#ifdef HAVE_SYS_IOCTL_H
-#include "sys/ioctl.h"
-#endif
-
-#define ERTS_WANT_BREAK_HANDLING
-#define WANT_NONBLOCKING
-#include "sys.h"
-#include "erl_thr_progress.h"
-
-#ifdef USE_THREADS
-#include "erl_threads.h"
-#endif
-
-#include "erl_mseg.h"
-
-#include "unistd.h"
-#include "efs.h"
-#include "erl_printf.h"
-#include "aio.h"
-#include "pm.h"
-#include "fcntl.h"
-
-/* Set the define to 1 to get some logging */
-#if 0
-#include "ramlog.h"
-#define LOG(output) ramlog_printf output
-#else
-#define LOG(output)
-#endif
-
-extern char **environ;
-static erts_smp_rwmtx_t environ_rwmtx;
-static PROCESS sig_proxy_pid = 0;
-
-#define MAX_VSIZE 16		/* Max number of entries allowed in an I/O
-				 * vector sock_sendv().
-				 */
-/*
- * Don't need global.h, but bif_table.h (included by bif.h),
- * won't compile otherwise
- */
-#include "global.h"
-#include "bif.h"
-
-#include "erl_sys_driver.h"
-#include "erl_check_io.h"
-#include "erl_cpu_topology.h"
-
-/* The priority for reader/writer processes */
-#define FD_PROC_PRI get_pri(current_process())
-
-typedef struct ErtsSysReportExit_ ErtsSysReportExit;
-struct ErtsSysReportExit_ {
-    ErtsSysReportExit  *next;
-    Eterm              port;
-    int                pid;
-    int                ifd;
-    int                ofd;
-    ErlDrvEvent        attach_event;
-    ErlDrvEvent        input_event;
-    ErlDrvEvent        output_event;
-};
-
-/* This data is shared by these drivers - initialized by spawn_init() */
-static struct driver_data {
-   ErlDrvPort          port_num;
-   int                 ofd;
-   int                 ifd;
-   int                 packet_bytes;
-   ErtsSysReportExit   *report_exit;
-   int                 pid;
-   int                 alive;
-   int                 status;
-   ErlDrvEvent         input_event;
-   ErlDrvEvent         output_event;
-   struct aiocb        aiocb;
-   FmHandle            handle;
-   char                *install_handle;
-} *driver_data;			/* indexed by fd */
-
-struct async {
-  SIGSELECT            signo;
-  ErlDrvTermData       port;
-  ErlDrvTermData       proc;
-  PROCESS              spid;
-  PROCESS              target;
-  Uint32               ref;
-};
-
-static ErtsSysReportExit *report_exit_list;
-static ERTS_INLINE void report_exit_status(ErtsSysReportExit *rep, int status);
-
-extern int  driver_interrupt(int, int);
-extern void do_break(void);
-
-extern void erl_sys_args(int*, char**);
-
-/* The following two defs should probably be moved somewhere else */
-
-extern void erts_sys_init_float(void);
-
-extern void erl_crash_dump(char* file, int line, char* fmt, ...);
-
-#define DIR_SEPARATOR_CHAR    '/'
-
-#if defined(DEBUG)
-#define ERL_BUILD_TYPE_MARKER ".debug"
-#else /* opt */
-#define ERL_BUILD_TYPE_MARKER
-#endif
-
-#define CHILD_SETUP_PROG_NAME	"child_setup" ERL_BUILD_TYPE_MARKER
-
-#ifdef DEBUG
-static int debug_log = 0;
-#endif
-
-#ifdef ERTS_SMP
-static erts_smp_atomic32_t have_prepared_crash_dump;
-#define ERTS_PREPARED_CRASH_DUMP \
-  ((int) erts_smp_atomic32_xchg_nob(&have_prepared_crash_dump, 1))
-#else
-static volatile int have_prepared_crash_dump;
-#define ERTS_PREPARED_CRASH_DUMP \
-  (have_prepared_crash_dump++)
-#endif
-
-static erts_smp_atomic_t sys_misc_mem_sz;
-
-#if defined(ERTS_SMP)
-erts_mtx_t chld_stat_mtx;
-#endif
-
-#if defined(ERTS_SMP) /* ------------------------------------------------- */
-#define CHLD_STAT_LOCK		erts_mtx_lock(&chld_stat_mtx)
-#define CHLD_STAT_UNLOCK	erts_mtx_unlock(&chld_stat_mtx)
-
-#else /* ------------------------------------------------------------------- */
-#define CHLD_STAT_LOCK
-#define CHLD_STAT_UNLOCK
-static volatile int children_died;
-#endif
-
-#define SET_AIO(REQ,FD,SIZE,BUFF)                                       \
-   memset(&(REQ),0,sizeof(REQ));                                        \
-   (REQ).aio_fildes = FD;                                               \
-   (REQ).aio_offset = FM_POSITION_CURRENT;                              \
-   (REQ).aio_nbytes = SIZE;                                             \
-   (REQ).aio_buf = BUFF;                                                \
-   (REQ).aio_sigevent.sigev_notify = SIGEV_NONE
-
-/* the first sizeof(struct aiocb *) bytes of the write buffer
- * will contain the pointer to the aiocb struct, this needs
- * to be freed between asynchronous writes.
- * A write of 0 bytes is ignored. */
-#define WRITE_AIO(FD,SIZE,BUFF) do {                                    \
-   if (SIZE > 0) {                                                      \
-      struct aiocb *write_req = driver_alloc(sizeof(struct aiocb));     \
-      char *write_buff = driver_alloc((sizeof(char)*SIZE)+1+            \
-            (sizeof(struct aiocb *)));                                  \
-      *(struct aiocb **)write_buff = (struct aiocb *)write_req;         \
-      write_buff += sizeof(struct aiocb *);                             \
-      memcpy(write_buff,BUFF,SIZE+1);                                   \
-      SET_AIO(*write_req,FD,SIZE,write_buff);                           \
-      if (aio_write(write_req))						\
-	ramlog_printf("%s:%d: write failed with %d\n",			\
-		      __FILE__,__LINE__,errno);				\
-   }                                                                    \
-} while(0)
-
-/* free the write_buffer and write_req
- * created in the WRITE_AIO() request macro */
-#define FREE_AIO(ptr) do {                                              \
-   struct aiocb *aiocb_ptr;                                             \
-   char *buffer_ptr;                                                    \
-   aiocb_ptr = *(struct aiocb **)((ptr)-sizeof(struct aiocb *));        \
-   buffer_ptr = (((char*)ptr)-sizeof(struct aiocb *));			\
-   driver_free(aiocb_ptr);                                              \
-   driver_free(buffer_ptr);                                             \
-} while(0)
-
-#define DISPATCH_AIO(sig) do {                                          \
-   if (aio_dispatch(sig))						\
-     ramlog_printf("%s:%d: dispatch failed with %d\n",			\
-		   __FILE__,__LINE__,errno);				\
-   } while(0)
-
-#define AIO_PIPE_SIZE 1024
-
-/* debug print macros */
-#define DEBUG_RES 0
-
-#ifdef DEBUG_RES
-#define DEBUG_CHECK_RES(actual, expected) \
-   do { \
-      if (actual != expected ) { \
-         ramlog_printf("Result check failed" \
-                       " got: 0x%08x expected:0x%08x\nat: %s:%d\n", \
-               actual, expected, __FILE__, __LINE__); \
-         abort();  /* This might perhaps be too harsh? */ \
-      } \
-   } while(0)
-#else
-#define DEBUG_CHECK_RES
-#endif
-
-static struct fd_data {
-    char  pbuf[4];   /* hold partial packet bytes */
-    int   psz;       /* size of pbuf */
-    char  *buf;
-    char  *cpos;
-    int   sz;
-    int   remain;  /* for input on fd */
-} *fd_data;			/* indexed by fd */
-
-/********************* General functions ****************************/
-
-/* This is used by both the drivers and general I/O, must be set early */
-static int max_files = -1;
-
-/*
- * a few variables used by the break handler
- */
-#ifdef ERTS_SMP
-erts_smp_atomic32_t erts_break_requested;
-#define ERTS_SET_BREAK_REQUESTED \
-  erts_smp_atomic32_set_nob(&erts_break_requested, (erts_aint32_t) 1)
-#define ERTS_UNSET_BREAK_REQUESTED \
-  erts_smp_atomic32_set_nob(&erts_break_requested, (erts_aint32_t) 0)
-#else
-volatile int erts_break_requested = 0;
-#define ERTS_SET_BREAK_REQUESTED (erts_break_requested = 1)
-#define ERTS_UNSET_BREAK_REQUESTED (erts_break_requested = 0)
-#endif
-/* set early so the break handler has access to initial mode */
-static struct termios initial_tty_mode;
-static int replace_intr = 0;
-/* assume yes initially, ttsl_init will clear it */
-int using_oldshell = 1;
-static PROCESS get_signal_proxy_pid(void);
-
-static void
-init_check_io(void)
-{
-    erts_init_check_io();
-    max_files = erts_check_io_max_files();
-}
-
-#ifdef ERTS_POLL_NEED_ASYNC_INTERRUPT_SUPPORT
-#define ERTS_CHK_IO_AS_INTR()	erts_check_io_async_sig_interrupt()
-#else
-#define ERTS_CHK_IO_AS_INTR()	erts_check_io_interrupt(1)
-#endif
-#define ERTS_CHK_IO_INTR	erts_check_io_interrupt
-#define ERTS_CHK_IO_INTR_TMD	erts_check_io_interrupt_timed
-#define ERTS_CHK_IO		erts_check_io
-#define ERTS_CHK_IO_SZ		erts_check_io_size
-
-
-void
-erts_sys_schedule_interrupt(int set)
-{
-    ERTS_CHK_IO_INTR(set);
-}
-
-#ifdef ERTS_SMP
-void
-erts_sys_schedule_interrupt_timed(int set, ErtsMonotonicTime timeout_time)
-{
-    ERTS_CHK_IO_INTR_TMD(set, timeout_time);
-}
-#endif
-
-Uint
-erts_sys_misc_mem_sz(void)
-{
-    Uint res = ERTS_CHK_IO_SZ();
-    res += erts_smp_atomic_read_mb(&sys_misc_mem_sz);
-    return res;
-}
-
-/*
- * reset the terminal to the original settings on exit
- */
-void sys_tty_reset(int exit_code)
-{
-  if (using_oldshell && !replace_intr) {
-    SET_BLOCKING(0);
-  }
-  else if (isatty(0)) {
-    tcsetattr(0,TCSANOW,&initial_tty_mode);
-  }
-}
-
-#ifdef USE_THREADS
-
-typedef struct {
-    int sched_bind_data;
-} erts_thr_create_data_t;
-
-/*
- * thr_create_prepare() is called in parent thread before thread creation.
- * Returned value is passed as argument to thr_create_cleanup().
- */
-static void *
-thr_create_prepare(void)
-{
-    erts_thr_create_data_t *tcdp;
-
-    tcdp = erts_alloc(ERTS_ALC_T_TMP, sizeof(erts_thr_create_data_t));
-
-    tcdp->sched_bind_data = erts_sched_bind_atthrcreate_prepare();
-
-    return (void *) tcdp;
-}
-
-
-/* thr_create_cleanup() is called in parent thread after thread creation. */
-static void
-thr_create_cleanup(void *vtcdp)
-{
-    erts_thr_create_data_t *tcdp = (erts_thr_create_data_t *) vtcdp;
-
-    erts_sched_bind_atthrcreate_parent(tcdp->sched_bind_data);
-
-    erts_free(ERTS_ALC_T_TMP, tcdp);
-}
-
-static void
-thr_create_prepare_child(void *vtcdp)
-{
-    erts_thr_create_data_t *tcdp = (erts_thr_create_data_t *) vtcdp;
-
-#ifdef ERTS_ENABLE_LOCK_COUNT
-    erts_lcnt_thread_setup();
-#endif
-
-    erts_sched_bind_atthrcreate_child(tcdp->sched_bind_data);
-}
-
-#endif /* #ifdef USE_THREADS */
-
-/* The two functions below are stolen from win_con.c
-   They have to use malloc/free/realloc directly becasue
-   we want to do able to do erts_printf very early on.
- */
-#define VPRINTF_BUF_INC_SIZE 128
-static erts_dsprintf_buf_t *
-grow_vprintf_buf(erts_dsprintf_buf_t *dsbufp, size_t need)
-{
-    char *buf;
-    size_t size;
-
-    ASSERT(dsbufp);
-
-    if (!dsbufp->str) {
-	size = (((need + VPRINTF_BUF_INC_SIZE - 1)
-		 / VPRINTF_BUF_INC_SIZE)
-		* VPRINTF_BUF_INC_SIZE);
-	buf = (char *) malloc(size * sizeof(char));
-    }
-    else {
-	size_t free_size = dsbufp->size - dsbufp->str_len;
-
-	if (need <= free_size)
-	    return dsbufp;
-
-	size = need - free_size + VPRINTF_BUF_INC_SIZE;
-	size = (((size + VPRINTF_BUF_INC_SIZE - 1)
-		 / VPRINTF_BUF_INC_SIZE)
-		* VPRINTF_BUF_INC_SIZE);
-	size += dsbufp->size;
-        buf = (char *) realloc((void *) dsbufp->str,
-			       size * sizeof(char));
-    }
-    if (!buf)
-	return NULL;
-    if (buf != dsbufp->str)
-	dsbufp->str = buf;
-    dsbufp->size = size;
-    return dsbufp;
-}
-
-static int erts_sys_ramlog_printf(char *format, va_list arg_list)
-{
-    int res,i;
-    erts_dsprintf_buf_t dsbuf = ERTS_DSPRINTF_BUF_INITER(grow_vprintf_buf);
-    res = erts_vdsprintf(&dsbuf, format, arg_list);
-    if (res >= 0) {
-      for (i = 0; i < dsbuf.str_len; i+= 50)
-	/* We print 50 characters at a time because otherwise
-	   the ramlog looks broken */
-        ramlog_printf("%.*s",dsbuf.str_len-50 < 0?dsbuf.str_len:50,dsbuf.str+i);
-    }
-    if (dsbuf.str)
-      free((void *) dsbuf.str);
-    return res;
-}
-
-void
-erts_sys_pre_init(void)
-{
-    erts_printf_add_cr_to_stdout = 1;
-    erts_printf_add_cr_to_stderr = 1;
-#ifdef USE_THREADS
-    {
-    erts_thr_init_data_t eid = ERTS_THR_INIT_DATA_DEF_INITER;
-
-    eid.thread_create_child_func = thr_create_prepare_child;
-    /* Before creation in parent */
-    eid.thread_create_prepare_func = thr_create_prepare;
-    /* After creation in parent */
-    eid.thread_create_parent_func = thr_create_cleanup,
-
-    erts_thr_init(&eid);
-
-    report_exit_list = NULL;
-
-#ifdef ERTS_ENABLE_LOCK_COUNT
-    erts_lcnt_init();
-#endif
-
-#if defined(ERTS_SMP)
-    erts_mtx_init(&chld_stat_mtx, "child_status");
-#endif
-    }
-#ifdef ERTS_SMP
-    erts_smp_atomic32_init_nob(&erts_break_requested, 0);
-    erts_smp_atomic32_init_nob(&have_prepared_crash_dump, 0);
-#else
-    erts_break_requested = 0;
-    have_prepared_crash_dump = 0;
-#endif
-#if !defined(ERTS_SMP)
-    children_died = 0;
-#endif
-#endif /* USE_THREADS */
-
-    erts_printf_stdout_func = erts_sys_ramlog_printf;
-
-    erts_smp_atomic_init_nob(&sys_misc_mem_sz, 0);
-}
-
-void
-erl_sys_init(void)
-{
-
-#ifdef USE_SETLINEBUF
-    setlinebuf(stdout);
-#else
-    setvbuf(stdout, (char *)NULL, _IOLBF, BUFSIZ);
-#endif
-
-    erts_sys_init_float();
-
-    /* we save this so the break handler can set and reset it properly */
-    /* also so that we can reset on exit (break handler or not) */
-    if (isatty(0)) {
-	tcgetattr(0,&initial_tty_mode);
-    }
-    tzset(); /* Required at least for NetBSD with localtime_r() */
-}
-
-static ERTS_INLINE int
-prepare_crash_dump(int secs)
-{
-#define NUFBUF (3)
-    int i, max;
-    char env[21]; /* enough to hold any 64-bit integer */
-    size_t envsz;
-    /*DeclareTmpHeapNoproc(heap,NUFBUF);*/
-    /*Eterm *hp = heap;*/
-    /*Eterm list = NIL;*/
-    int has_heart = 0;
-
-    UseTmpHeapNoproc(NUFBUF);
-
-    if (ERTS_PREPARED_CRASH_DUMP)
-	return 0; /* We have already been called */
-
-
-    /* Positive secs means an alarm must be set
-     * 0 or negative means no alarm
-     *
-     * Set alarm before we try to write to a port
-     * we don't want to hang on a port write with
-     * no alarm.
-     *
-     */
-
-#if 0 /*ose TBD!!!*/
-    if (secs >= 0) {
-	alarm((unsigned int)secs);
-    }
-#endif
-
-    /* Make sure we unregister at epmd (unknown fd) and get at least
-       one free filedescriptor (for erl_crash.dump) */
-
-    max = max_files;
-    if (max < 1024)
-	max = 1024;
-    for (i = 3; i < max; i++) {
-	close(i);
-    }
-
-    envsz = sizeof(env);
-    i = erts_sys_getenv__("ERL_CRASH_DUMP_NICE", env, &envsz);
-    if (i >= 0) {
-	int nice_val;
-	nice_val = i != 0 ? 0 : atoi(env);
-	if (nice_val > 39) {
-	    nice_val = 39;
-	}
-	set_pri(nice_val);
-    }
-
-    UnUseTmpHeapNoproc(NUFBUF);
-#undef NUFBUF
-    return has_heart;
-}
-
-int erts_sys_prepare_crash_dump(int secs)
-{
-    return prepare_crash_dump(secs);
-}
-
-static ERTS_INLINE void
-break_requested(void)
-{
-  /*
-   * just set a flag - checked for and handled by
-   * scheduler threads erts_check_io() (not signal handler).
-   */
-#ifdef DEBUG
-  fprintf(stderr,"break!\n");
-#endif
-  if (ERTS_BREAK_REQUESTED)
-      erts_exit(ERTS_INTR_EXIT, "");
-
-  ERTS_SET_BREAK_REQUESTED;
-  ERTS_CHK_IO_AS_INTR(); /* Make sure we don't sleep in poll */
-}
-
-/* Disable break */
-void erts_set_ignore_break(void) {
-
-}
-
-/* Don't use ctrl-c for break handler but let it be
-   used by the shell instead (see user_drv.erl) */
-void erts_replace_intr(void) {
-  struct termios mode;
-
-  if (isatty(0)) {
-    tcgetattr(0, &mode);
-
-    /* here's an example of how to replace ctrl-c with ctrl-u */
-    /* mode.c_cc[VKILL] = 0;
-       mode.c_cc[VINTR] = CKILL; */
-
-    mode.c_cc[VINTR] = 0;	/* disable ctrl-c */
-    tcsetattr(0, TCSANOW, &mode);
-    replace_intr = 1;
-  }
-}
-
-void init_break_handler(void)
-{
-
-}
-
-int sys_max_files(void)
-{
-   return(max_files);
-}
-
-
-/************************** OS info *******************************/
-
-/* Used by erlang:info/1. */
-/* (This code was formerly in drv.XXX/XXX_os_drv.c) */
-
-char os_type[] = "ose";
-
-void
-os_flavor(char* namebuf,	/* Where to return the name. */
-	  unsigned size)	/* Size of name buffer. */
-{
-#if 0
-    struct utsname uts;		/* Information about the system. */
-    char* s;
-
-    (void) uname(&uts);
-    for (s = uts.sysname; *s; s++) {
-	if (isupper((int) *s)) {
-	    *s = tolower((int) *s);
-	}
-    }
-    strcpy(namebuf, uts.sysname);
-#else
-    strncpy(namebuf, "release", size);
-#endif
-}
-
-void
-os_version(pMajor, pMinor, pBuild)
-int* pMajor;			/* Pointer to major version. */
-int* pMinor;			/* Pointer to minor version. */
-int* pBuild;			/* Pointer to build number. */
-{
-    *pMajor = 5;
-    *pMinor = 7;
-    *pBuild = 0;
-}
-
-void init_getenv_state(GETENV_STATE *state)
-{
-   erts_smp_rwmtx_rlock(&environ_rwmtx);
-   *state = NULL;
-}
-
-char **environ; /*ose - needs replacement*/
-
-char *getenv_string(GETENV_STATE *state0)
-{
-   char **state = (char **) *state0;
-   char *cp;
-
-   ERTS_SMP_LC_ASSERT(erts_smp_lc_rwmtx_is_rlocked(&environ_rwmtx));
-
-   if (state == NULL)
-      state = environ;
-
-   cp = *state++;
-   *state0 = (GETENV_STATE) state;
-
-   return cp;
-}
-
-void fini_getenv_state(GETENV_STATE *state)
-{
-   *state = NULL;
-   erts_smp_rwmtx_runlock(&environ_rwmtx);
-}
-
-
-/************************** Port I/O *******************************/
-
-/* I. Common stuff */
-
-union SIGNAL {
-    SIGSELECT sig_no;
-    struct FmReadPtr fm_read_reply;
-    struct FmWritePtr fm_write_reply;
-    struct async async;
-};
-
-/* II. The spawn/fd drivers */
-
-/*
- * Decreasing the size of it below 16384 is not allowed.
- */
-#define ERTS_SYS_READ_BUF_SZ (64*1024)
-
-/* Driver interfaces */
-static ErlDrvData spawn_start(ErlDrvPort, char*, SysDriverOpts*);
-static ErlDrvData fd_start(ErlDrvPort, char*, SysDriverOpts*);
-static ErlDrvSSizeT fd_control(ErlDrvData, unsigned int, char *, ErlDrvSizeT,
-			       char **, ErlDrvSizeT);
-static int spawn_init(void);
-static void fd_stop(ErlDrvData);
-static void erl_stop(ErlDrvData);
-static void ready_input(ErlDrvData, ErlDrvEvent);
-static void ready_output(ErlDrvData, ErlDrvEvent);
-static void output(ErlDrvData, char*, ErlDrvSizeT);
-static void stop_select(ErlDrvEvent, void*);
-
-static PROCESS
-get_signal_proxy_pid(void) {
-   union SIGNAL *sig;
-   SIGSELECT any_sig[] = {1,ERTS_SIGNAL_OSE_DRV_ATTACH};
-
-   if (!sig_proxy_pid) {
-      sig = alloc(sizeof(union SIGNAL), ERTS_SIGNAL_OSE_DRV_ATTACH);
-      hunt("ose_signal_driver_proxy", 0, NULL, &sig);
-      sig = receive(any_sig);
-      sig_proxy_pid = sender(&sig);
-      free_buf(&sig);
-   }
-   ASSERT(sig_proxy_pid);
-   return sig_proxy_pid;
-}
-
-static ErlDrvOseEventId
-resolve_signal(union SIGNAL* sig) {
-   switch(sig->sig_no) {
-
-      case FM_READ_PTR_REPLY:
-            return (ErlDrvOseEventId)sig->fm_read_reply.handle;
-
-       case FM_WRITE_PTR_REPLY:
-            return (ErlDrvOseEventId)sig->fm_write_reply.handle;
-
-       case ERTS_SIGNAL_OSE_DRV_ATTACH:
-            return (ErlDrvOseEventId)sig->async.target;
-
-       default:
-            break;
-    }
-    return (ErlDrvOseEventId)-1;
-}
-
-struct erl_drv_entry spawn_driver_entry = {
-    spawn_init,
-    spawn_start,
-    NULL, /* erl_stop, */
-    output,
-    ready_input,
-    ready_output,
-    "spawn",
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    NULL,
-    ERL_DRV_EXTENDED_MARKER,
-    ERL_DRV_EXTENDED_MAJOR_VERSION,
-    ERL_DRV_EXTENDED_MINOR_VERSION,
-    ERL_DRV_FLAG_USE_PORT_LOCKING,
-    NULL, NULL,
-    stop_select
-};
-struct erl_drv_entry fd_driver_entry = {
-    NULL,
-    fd_start,
-    fd_stop,
-    output,
-    ready_input,
-    ready_output,
-    "fd",
-    NULL,
-    NULL,
-    fd_control,
-    NULL,
-    NULL,
-    NULL, /* ready_async */
-    NULL, /* flush */
-    NULL, /* call */
-    NULL, /* event */
-    ERL_DRV_EXTENDED_MARKER,
-    ERL_DRV_EXTENDED_MAJOR_VERSION,
-    ERL_DRV_EXTENDED_MINOR_VERSION,
-    0, /* ERL_DRV_FLAGs */
-    NULL, /* handle2 */
-    NULL, /* process_exit */
-    stop_select
-};
-
-static void
-set_spawn_fd(int local_fd, int remote_fd, PROCESS remote_pid) {
-   PROCESS vm_pid;
-   FmHandle handle;
-   char env_val[55];
-   char env_name[10];
-   EfsStatus efs_res;
-
-   /* get pid of pipevm and handle of chosen fd */
-   efs_res = efs_examine_fd(local_fd, FLIB_FD_VMPID, &vm_pid, 0);
-   DEBUG_CHECK_RES(efs_res, EFS_SUCCESS);
-
-   /* setup the file descriptor to buffer per line */
-   efs_res = efs_config_fd(local_fd, FLIB_FD_BUFMODE, FM_BUFF_LINE,
-                    FLIB_FD_BUFSIZE, 80, 0);
-   DEBUG_CHECK_RES(efs_res, EFS_SUCCESS);
-
-   /* duplicate handle  and set spawn pid owner */
-   efs_res = efs_dup_to(local_fd, remote_pid, &handle);
-   DEBUG_CHECK_RES(efs_res, EFS_SUCCESS);
-
-   sprintf(env_name, "FD%d", remote_fd);
-
-   /* Syntax of the environment variable:
-    * "FD#" "<pid of pipevm>,<handle>,<buffer mode>,<buff size>,<omode>" */
-   sprintf(env_val, "0x%lx,0x%lx,%lu,%lu,0x%x",
-                    vm_pid, handle,
-                    FM_BUFF_LINE, 80,
-                    O_APPEND);
-
-   set_env(remote_pid, env_name, env_val);
-}
-
-static ErlDrvData
-set_driver_data(ErlDrvPort port_num,
-			   int ifd,
-			   int ofd,
-			   int packet_bytes,
-			   int read_write,
-			   int exit_status,
-			   PROCESS pid)
-{
-    Port *prt;
-    ErtsSysReportExit *report_exit;
-
-    prt = erts_drvport2port(port_num);
-    if (prt != ERTS_INVALID_ERL_DRV_PORT) {
-       prt->os_pid = pid;
-    }
-
-    /* READ */
-    if (read_write & DO_READ) {
-       EfsStatus res = efs_examine_fd(ifd, FLIB_FD_HANDLE,
-				      &driver_data[ifd].handle, 0);
-       if (res != EFS_SUCCESS)
-	 ramlog_printf("%s:%d: efs_examine_fd(%d) failed with %d\n",
-		       __FILE__,__LINE__,ifd,errno);
-       driver_data[ifd].ifd = ifd;
-       driver_data[ifd].packet_bytes = packet_bytes;
-       driver_data[ifd].port_num = port_num;
-       driver_data[ifd].pid = pid;
-
-       /* async read struct */
-       memset(&driver_data[ifd].aiocb, 0, sizeof(struct aiocb));
-       driver_data[ifd].aiocb.aio_buf = driver_alloc(AIO_PIPE_SIZE);
-       driver_data[ifd].aiocb.aio_fildes = ifd;
-       driver_data[ifd].aiocb.aio_nbytes = (packet_bytes?packet_bytes:AIO_PIPE_SIZE);
-       driver_data[ifd].alive = 1;
-       driver_data[ifd].status = 0;
-       driver_data[ifd].input_event =
-          erl_drv_ose_event_alloc(FM_READ_PTR_REPLY,
-                driver_data[ifd].handle, resolve_signal,
-                &driver_data[ifd].ifd);
-
-       /* READ & WRITE */
-       if (read_write & DO_WRITE) {
-          driver_data[ifd].ofd = ofd;
-          efs_examine_fd(ofd, FLIB_FD_HANDLE, &driver_data[ofd].handle, 0);
-
-          driver_data[ifd].output_event =
-             erl_drv_ose_event_alloc(FM_WRITE_PTR_REPLY,
-                   driver_data[ofd].handle, resolve_signal,
-                   &driver_data[ofd].ofd);
-          driver_data[ofd].pid = pid;
-          if (ifd != ofd) {
-             driver_data[ofd] = driver_data[ifd];
-             driver_data[ofd].aiocb.aio_buf = NULL;
-           }
-       }
-       else { /* READ ONLY */
-          driver_data[ifd].ofd = -1;
-       }
-
-       /* enable input event */
-       (void) driver_select(port_num, driver_data[ifd].input_event,
-			     (ERL_DRV_READ | ERL_DRV_USE), 1);
-
-       if (aio_read(&driver_data[ifd].aiocb))
-	 ramlog_printf("%s:%d: aio_read(%d) failed with %d\n",
-		       __FILE__,__LINE__,ifd,errno);
-    }
-    else { /* WRITE ONLY */
-       efs_examine_fd(ofd, FLIB_FD_HANDLE, &driver_data[ofd].handle, 0);
-       driver_data[ofd].packet_bytes = packet_bytes;
-       driver_data[ofd].port_num = port_num;
-       driver_data[ofd].ofd = ofd;
-       driver_data[ofd].pid = pid;
-       driver_data[ofd].alive = 1;
-       driver_data[ofd].status = 0;
-       driver_data[ofd].output_event =
-          erl_drv_ose_event_alloc(FM_WRITE_PTR_REPLY, driver_data[ofd].handle,
-				    resolve_signal, &driver_data[ofd].ofd);
-       driver_data[ofd].input_event = driver_data[ofd].output_event;
-    }
-
-    /* this is used for spawned load modules, and is needed
-     * to properly uninstall them */
-    if (exit_status) {
-       struct PmProgramInfo *info;
-       int install_handle_size;
-       union SIGNAL *sig;
-       PmStatus pm_status;
-       report_exit = erts_alloc(ERTS_ALC_T_PRT_REP_EXIT,
-				 sizeof(ErtsSysReportExit));
-       report_exit->next = report_exit_list;
-       report_exit->port = erts_drvport2id(port_num);
-       report_exit->pid = pid;
-       report_exit->ifd = (read_write & DO_READ) ? ifd : -1;
-       report_exit->ofd = (read_write & DO_WRITE) ? ofd : -1;
-       report_exit_list = report_exit;
-       report_exit->attach_event =
-          erl_drv_ose_event_alloc(ERTS_SIGNAL_OSE_DRV_ATTACH, pid,
-				resolve_signal, &driver_data[ifd].ifd);
-
-       /* setup ifd and ofd report exit */
-       driver_data[ifd].report_exit = report_exit;
-       driver_data[ofd].report_exit = report_exit;
-
-       pm_status = ose_pm_program_info(pid, &info);
-       DEBUG_CHECK_RES(pm_status, PM_SUCCESS);
-
-       install_handle_size = strlen(info->install_handle)+1;
-       driver_data[ifd].install_handle = driver_alloc(install_handle_size);
-       strcpy(driver_data[ifd].install_handle,
-             info->install_handle);
-
-       free_buf((union SIGNAL **)&info);
-
-       sig = alloc(sizeof(struct async), ERTS_SIGNAL_OSE_DRV_ATTACH);
-       sig->async.target = pid;
-       send(&sig, get_signal_proxy_pid());
-
-       /* this event will trigger when we receive an attach signal
-        * from the recently dead load module */
-       (void)driver_select(port_num,report_exit->attach_event, DO_READ, 1);
-    }
-    else {
-       report_exit = NULL;
-    }
-
-    /* the return value is the pointer to the driver_data struct we created
-     * in this function, it will be used in the drivers input
-     * and output functions */
-    return (ErlDrvData)((!(read_write & DO_READ) && read_write & DO_WRITE)
-          ? &driver_data[ofd]
-          : &driver_data[ifd]);
-}
-
-static int spawn_init()
-{
-    int i;
-
-    driver_data = (struct driver_data *)
-      erts_alloc(ERTS_ALC_T_DRV_TAB, max_files * sizeof(struct driver_data));
-    erts_smp_atomic_add_nob(&sys_misc_mem_sz,
-			    max_files * sizeof(struct driver_data));
-
-    for (i = 0; i < max_files; i++)
-        driver_data[i].pid = -1;
-
-   return 1;
-}
-
-static void
-init_fd_data(int fd, ErlDrvPort port_num)
-{
-    fd_data[fd].buf = NULL;
-    fd_data[fd].cpos = NULL;
-    fd_data[fd].remain = 0;
-    fd_data[fd].sz = 0;
-    fd_data[fd].psz = 0;
-}
-
-/* FIXME write a decent text on pipes on ose */
-static ErlDrvData
-spawn_start(ErlDrvPort port_num, char* name, SysDriverOpts* opts)
-{
-    int ifd[2];
-    int ofd[2];
-    static uint32_t ticker = 1;
-    PmStatus pm_status;
-    OSDOMAIN domain = PM_NEW_DOMAIN;
-    PROCESS progpid, mainbid, mainpid;
-    char *handle = NULL;
-    struct PmProgramInfo *info;
-    char *args = NULL;
-    char *tmp_handle;
-    ErlDrvData res = (ErlDrvData)-1;
-    int handle_size;
-    char *ptr;
-
-   
-    args = driver_alloc(strlen(name)+1);
-    strcpy(args, name);
-    /* We need to handle name in three parts 
-     * - install handle (must be unique)
-     * - install binary (needed for ose_pm_install_load_module())
-     * - full path (as argument to the spawned applications env.var
-     */
-
-    /* full path including arguments */
-    args = driver_alloc(strlen(name)+1);
-    strcpy(args, name);
-
-    /* handle path */
-    tmp_handle = strrchr(name, '/');
-    if (tmp_handle == NULL) {
-       tmp_handle = name;
-    }
-    else {
-       tmp_handle++;
-    }
-
-    /* handle args */
-    ptr = strchr(tmp_handle, ' ');
-    if (ptr != NULL) {
-       *ptr = '\0';
-       handle_size = ptr - tmp_handle;
-    }
-    else {
-       handle_size = strlen(name)+1;
-    }
-
-    /* make room for ticker */
-    handle_size += (ticker<10)?3:((ticker<100)?4:5);
-    handle = driver_alloc(handle_size);
-    
-    do {
-       snprintf(handle, handle_size, "%s_%d", tmp_handle, ticker);
-       pm_status = ose_pm_install_load_module(0, "ELF", name, handle,
-                                              0, 0, NULL);
-       ticker++;
-    } while (pm_status == PM_EINSTALL_HANDLE_ALREADY_INSTALLED);
-
-    if (pm_status != PM_SUCCESS) {
-       errno = ENOSYS; /* FIXME add comment */
-       return ERL_DRV_ERROR_ERRNO; 
-    }
-
-    /* Create Program */
-    pm_status = ose_pm_create_program(&domain, handle, 0, 0,
-                                      NULL, &progpid, &mainbid);
-    DEBUG_CHECK_RES(pm_status, PM_SUCCESS);
-
-    /* Get the mainpid from the newly created program */
-    pm_status = ose_pm_program_info(progpid, &info);
-    DEBUG_CHECK_RES(pm_status, PM_SUCCESS);
-
-    mainpid = info->main_process;
-    free_buf ((union SIGNAL **)&info);
-
-    /* pipevm needs to be started
-     * pipe will return 0 if success, -1 if not,
-     * errno will be set */
-    if (pipe(ifd) != 0 || pipe(ofd) != 0) {
-       DEBUG_CHECK_RES(0, -1);
-       ASSERT(0);
-    }
-
-    /* setup driver data */
-    res = set_driver_data(port_num, ofd[0], ifd[1], opts->packet_bytes,
-              opts->read_write, 1 /* opts->exit_status */, progpid);
-
-    /* init the fd_data array for read/write */
-    init_fd_data(ofd[0], port_num);
-    init_fd_data(ifd[1], port_num);
-
-    /* setup additional configurations
-     * for the spawned applications environment */
-    if (args != NULL) {
-       set_env(progpid, "ARGV", args);
-    }
-    set_env(mainbid, "EFS_RESOLVE_TMO", 0);
-    set_spawn_fd(ifd[0], 0, mainpid);
-    set_spawn_fd(ofd[1], 1, mainpid);
-    set_spawn_fd(ofd[1], 2, mainpid);
-
-    /* start the spawned program */
-    pm_status = ose_pm_start_program(mainbid);
-    DEBUG_CHECK_RES(pm_status, PM_SUCCESS);
-
-    /* close unused fd's */
-    close(ifd[0]);
-    close(ofd[1]);
-
-    if (handle) {
-       driver_free(handle);
-    }
-
-    return (ErlDrvData)res;
-}
-
-#define FD_DEF_HEIGHT 24
-#define FD_DEF_WIDTH 80
-/* Control op */
-#define FD_CTRL_OP_GET_WINSIZE 100
-
-static int fd_get_window_size(int fd, Uint32 *width, Uint32 *height)
-{
-#ifdef TIOCGWINSZ
-    struct winsize ws;
-    if (ioctl(fd,TIOCGWINSZ,&ws) == 0) {
-	*width = (Uint32) ws.ws_col;
-	*height = (Uint32) ws.ws_row;
-	return 0;
-    }
-#endif
-    return -1;
-}
-
-static ErlDrvSSizeT fd_control(ErlDrvData drv_data,
-			       unsigned int command,
-			       char *buf, ErlDrvSizeT len,
-			       char **rbuf, ErlDrvSizeT rlen)
-{
-   struct driver_data *data = (struct driver_data *)drv_data;
-    char resbuff[2*sizeof(Uint32)];
-    switch (command) {
-    case FD_CTRL_OP_GET_WINSIZE:
-	{
-	    Uint32 w,h;
-	    if (fd_get_window_size(data->ifd,&w,&h))
-		return 0;
-	    memcpy(resbuff,&w,sizeof(Uint32));
-	    memcpy(resbuff+sizeof(Uint32),&h,sizeof(Uint32));
-	}
-	break;
-    default:
-	return 0;
-    }
-    if (rlen < 2*sizeof(Uint32)) {
-	*rbuf = driver_alloc(2*sizeof(Uint32));
-    }
-    memcpy(*rbuf,resbuff,2*sizeof(Uint32));
-    return 2*sizeof(Uint32);
-}
-
-static ErlDrvData fd_start(ErlDrvPort port_num, char* name,
-			   SysDriverOpts* opts)
-{
-    ErlDrvData res;
-
-    CHLD_STAT_LOCK;
-    if (opts->read_write & DO_READ) {
-	init_fd_data(opts->ifd, port_num);
-    }
-    if (opts->read_write & DO_WRITE) {
-	init_fd_data(opts->ofd, port_num);
-    }
-    res = set_driver_data(port_num, opts->ifd, opts->ofd,
-				      opts->packet_bytes,
-				      opts->read_write, 0, -1);
-    CHLD_STAT_UNLOCK;
-    return res;
-}
-
-static void clear_fd_data(int fd)
-{
-    if (fd_data[fd].sz > 0) {
-	erts_free(ERTS_ALC_T_FD_ENTRY_BUF, (void *) fd_data[fd].buf);
-	ASSERT(erts_smp_atomic_read_nob(&sys_misc_mem_sz) >= fd_data[fd].sz);
-	erts_smp_atomic_add_nob(&sys_misc_mem_sz, -1*fd_data[fd].sz);
-    }
-    fd_data[fd].buf = NULL;
-    fd_data[fd].sz = 0;
-    fd_data[fd].remain = 0;
-    fd_data[fd].cpos = NULL;
-    fd_data[fd].psz = 0;
-}
-
-static void nbio_stop_fd(ErlDrvPort prt, ErlDrvEvent ev)
-{
-    int *fd;
-    driver_select(prt,ev,DO_READ|DO_WRITE,0);
-    erl_drv_ose_event_fetch(ev, NULL, NULL, (void **)&fd);
-    clear_fd_data(*fd);
-    SET_BLOCKING(*fd);
-}
-
-static void fd_stop(ErlDrvData drv_data)  /* Does not close the fds */
-{
-   struct driver_data *data = (struct driver_data *)drv_data;
-
-   if (data->ofd != -1) {
-      if (data->ifd != data->ofd) { /* read and write */
-         nbio_stop_fd(data->port_num, data->input_event);
-         nbio_stop_fd(data->port_num, data->output_event);
-      }
-      else { /* write only */
-         nbio_stop_fd(data->port_num, data->output_event);
-      }
-   }
-   else { /* read only */
-      nbio_stop_fd(data->port_num, data->input_event);
-   }
-}
-
-
-static void erl_stop(ErlDrvData drv_data)
-{
-   struct driver_data *data = (struct driver_data *)drv_data;
-
-   CHLD_STAT_LOCK;
-   data->pid = -1;
-   CHLD_STAT_UNLOCK;
-
-   if (data->ofd != -1) {
-      if (data->ifd != data->ofd) { /* read and write */
-         nbio_stop_fd(data->port_num, data->input_event);
-         nbio_stop_fd(data->port_num, data->output_event);
-      }
-      else { /* write only */
-         nbio_stop_fd(data->port_num, data->output_event);
-      }
-   }
-   else { /* read only */
-      nbio_stop_fd(data->port_num, data->input_event);
-   }
-   close(data->ifd);
-   close(data->ofd);
-}
-
-/* The parameter e is a pointer to the driver_data structure
- * related to the fd to be used as output */
-static void output(ErlDrvData drv_data, char* buf, ErlDrvSizeT len)
-{
-    ErlDrvSizeT sz;
-    char lb[4];
-    char* lbp;
-    struct driver_data *data = (struct driver_data *)drv_data;
-
-    if (((data->packet_bytes == 2) &&
-             (len > 0xffff)) || (data->packet_bytes == 1 && len > 0xff)) {
-	driver_failure_posix(data->port_num, EINVAL);
-	return; /* -1; */
-    }
-    put_int32(len, lb);
-    lbp = lb + (4-(data->packet_bytes));
-
-    if ((sz = driver_sizeq(data->port_num)) > 0) {
-       if (data->packet_bytes != 0) {
-          driver_enq(data->port_num, lbp, data->packet_bytes);
-       }
-       driver_enq(data->port_num, buf, len);
-
-       if (sz + len + data->packet_bytes >= (1 << 13))
-	    set_busy_port(data->port_num, 1);
-    }
-    else {
-       char *pbbuf;
-       if (data->packet_bytes != 0) {
-          pbbuf = malloc(len + data->packet_bytes);
-          int i;
-          for (i = 0; i < data->packet_bytes; i++) {
-             *pbbuf++ = *lbp++;
-          }
-          strncpy(pbbuf, buf, len);
-          pbbuf -= data->packet_bytes;
-       }
-       driver_select(data->port_num, data->output_event,
-		      ERL_DRV_WRITE|ERL_DRV_USE, 1);
-       WRITE_AIO(data->ofd, 
-             (data->packet_bytes ? len+data->packet_bytes : len), 
-             (data->packet_bytes ? pbbuf : buf));
-       if (data->packet_bytes != 0) free(pbbuf);
-    }
-    return; /* 0; */
-}
-
-/* This function is being run when we in recieve
- * either a read of 0 bytes, or the attach signal from a dying
- * spawned load module */
-static int port_inp_failure(ErlDrvPort port_num, ErlDrvEvent ready_fd, int res)
-				/* Result: 0 (eof) or -1 (error) */
-{
-    int *fd;
-    SIGSELECT sig_no;
-    ASSERT(res <= 0);
-
-    erl_drv_ose_event_fetch(ready_fd,&sig_no, NULL, (void **)&fd);
-    /* As we need to handle two signals, we do this in two steps */
-    if (driver_data[*fd].alive) {
-       report_exit_status(driver_data[*fd].report_exit, 0); /* status? */
-    }
-    else {
-       driver_select(port_num,ready_fd,DO_READ|DO_WRITE,0);
-       clear_fd_data(*fd);
-       driver_report_exit(driver_data[*fd].port_num, driver_data[*fd].status);
-       /* As we do not really know if the spawn has crashed or exited nicely
-        * we do not check the result status of the following call.. FIXME
-        * can we handle this in a better way? */
-       ose_pm_uninstall_load_module(driver_data[*fd].install_handle);
-       driver_free(driver_data[*fd].install_handle);
-       driver_free((void *)driver_data[*fd].aiocb.aio_buf);
-
-       close(*fd);
-    }
-
-    return 0;
-}
-
-/* The parameter e is a pointer to the driver_data structure
- * related to the fd to be used as output.
- * ready_fd is the event that triggered this call to ready_input */
-static void ready_input(ErlDrvData drv_data, ErlDrvEvent ready_fd)
-{
-    int res;
-    Uint h;
-    char *buf;
-    union SIGNAL *sig;
-    struct driver_data *data = (struct driver_data *)drv_data;
-
-    sig = erl_drv_ose_get_signal(ready_fd);
-    ASSERT(sig);
-
-
-   while (sig) {
-      /* If we've recieved an attach signal, we need to handle
-       * it in port_inp_failure */
-      if (sig->sig_no == ERTS_SIGNAL_OSE_DRV_ATTACH) {
-         port_inp_failure(data->port_num, ready_fd, 0);
-       }
-       else {
-          res = sig->fm_read_reply.actual;
-          if (res == 0) {
-             port_inp_failure(data->port_num, ready_fd, res);
-             break;
-          }
-
-          if (data->packet_bytes == 0) {
-             if (res < 0) {
-                if ((errno != EINTR) && (errno != ERRNO_BLOCK)) {
-                   port_inp_failure(data->port_num, ready_fd, res);
-                }
-             }
-             else if (res == 0) {
-                /* read of 0 bytes, eof, otherside of pipe is assumed dead */
-                port_inp_failure(data->port_num, ready_fd, res);
-                break;
-             }
-             else {
-                buf = driver_alloc(res);
-                memcpy(buf, (void *)data->aiocb.aio_buf, res);
-                driver_select(data->port_num, data->output_event,
-                      ERL_DRV_WRITE|ERL_DRV_USE, 1);
-                driver_output(data->port_num, (char*) buf, res);
-                driver_free(buf);
-             }
-                /* clear the previous read */
-                memset(data->aiocb.aio_buf, 0, res);
-
-                /* issue a new read */
-                DISPATCH_AIO(sig);
-                aio_read(&data->aiocb);
-          }
-          else if (data->packet_bytes && fd_data[data->ifd].remain > 0) {
-             /* we've read a partial package, or a header */
-
-             if (res == fd_data[data->ifd].remain) { /* we are done! */
-                char *buf = data->aiocb.aio_buf;
-                int i;
-
-                /* do we have anything buffered? */
-                if (fd_data[data->ifd].buf != NULL) {
-                   memcpy(fd_data[data->ifd].buf + fd_data[data->ifd].sz,
-                          buf, res);
-                   buf = fd_data[data->ifd].buf;
-                }
-
-                fd_data[data->ifd].sz += res;
-                driver_output(data->port_num, buf, (fd_data[data->ifd].sz>0?fd_data[data->ifd].sz:res));
-                clear_fd_data(data->ifd);
-
-                /* clear the previous read */
-                memset(data->aiocb.aio_buf, 0, res);
-             
-                /* issue a new read */
-                DISPATCH_AIO(sig);
-                data->aiocb.aio_nbytes = data->packet_bytes;
-
-                if (data->aiocb.aio_buf == NULL) {
-                   port_inp_failure(data->port_num, ready_fd, -1);
-                }
-                aio_read(&data->aiocb);
-             }
-             else if(res < fd_data[data->ifd].remain) { /* received part of a package */
-                if (fd_data[data->ifd].sz == 0) {
-
-                   fd_data[data->ifd].sz += res;
-                   memcpy(fd_data[data->ifd].buf, data->aiocb.aio_buf, res);
-                   fd_data[data->ifd].remain -= res;
-                }
-                else {
-                   memcpy(fd_data[data->ifd].buf + fd_data[data->ifd].sz,
-                          data->aiocb.aio_buf, res);
-                   fd_data[data->ifd].sz += res;
-                   fd_data[data->ifd].remain -= res;
-                }
-                /* clear the previous read */
-                memset(data->aiocb.aio_buf, 0, res);
-
-                /* issue a new read */
-                DISPATCH_AIO(sig);
-                data->aiocb.aio_nbytes = fd_data[data->ifd].remain;
-
-                if (data->aiocb.aio_buf == NULL) {
-                    port_inp_failure(data->port_num, ready_fd, -1);
-                }
-                aio_read(&data->aiocb);
-             }
-          }
-          else if (data->packet_bytes && fd_data[data->ifd].remain == 0) { /* we've recieved a header */
-
-             /* analyze the header FIXME  */
-             switch (data->packet_bytes) {
-                case 1: h = get_int8(data->aiocb.aio_buf);  break;
-                case 2: h = get_int16(data->aiocb.aio_buf); break;
-                case 4: h = get_int32(data->aiocb.aio_buf); break;
-             }
-
-             fd_data[data->ifd].buf = erts_alloc_fnf(ERTS_ALC_T_FD_ENTRY_BUF, h + data->packet_bytes);
-             fd_data[data->ifd].remain = ((h + data->packet_bytes) - res);
-
-             /* clear the previous read */
-             memset(data->aiocb.aio_buf, 0, data->packet_bytes);
-
-             /* issue a new read */
-             DISPATCH_AIO(sig);
-             data->aiocb.aio_nbytes = h;
-
-             if (data->aiocb.aio_buf == NULL) {
-                port_inp_failure(data->port_num, ready_fd, -1);
-             }
-             aio_read(&data->aiocb);
-          }
-       }
-       sig = erl_drv_ose_get_signal(ready_fd);
-    }
-}
-
-
-/* The parameter e is a pointer to the driver_data structure
- * related to the fd to be used as output.
- * ready_fd is the event that triggered this call to ready_input */
-static void ready_output(ErlDrvData drv_data, ErlDrvEvent ready_fd)
-{
-   SysIOVec *iov;
-   int vlen;
-   int res;
-   union SIGNAL *sig;
-   struct driver_data *data = (struct driver_data *)drv_data;
-
-   sig = erl_drv_ose_get_signal(ready_fd);
-   ASSERT(sig);
-
-   while (sig != NULL) {
-      if (sig->fm_write_reply.actual <= 0) {
-         int status;
-
-         status = efs_status_to_errno(sig->fm_write_reply.status);
-         driver_select(data->port_num, ready_fd, ERL_DRV_WRITE, 0);
-         DISPATCH_AIO(sig);
-         FREE_AIO(sig->fm_write_reply.buffer);
-
-         driver_failure_posix(data->port_num, status);
-      }
-      else { /* written bytes > 0 */
-          iov = driver_peekq(data->port_num, &vlen);
-          if (vlen > 0) {
-             DISPATCH_AIO(sig);
-             FREE_AIO(sig->fm_write_reply.buffer);
-             res = driver_deq(data->port_num, iov[0].iov_len);
-             if (res > 0) { 
-                iov = driver_peekq(data->port_num, &vlen);
-                WRITE_AIO(data->ofd, iov[0].iov_len, iov[0].iov_base);
-             }
-         }
-         else if (vlen == 0) {
-            DISPATCH_AIO(sig);
-            FREE_AIO(sig->fm_write_reply.buffer);
-         }
-
-      }
-      sig = erl_drv_ose_get_signal(ready_fd);
-   }
-}
-
-static void stop_select(ErlDrvEvent ready_fd, void* _)
-{
-   int *fd;
-   erl_drv_ose_event_fetch(ready_fd, NULL, NULL, (void **)&fd);
-   erl_drv_ose_event_free(ready_fd);
-   close(*fd);
-}
-
-
-void erts_do_break_handling(void)
-{
-    struct termios temp_mode;
-    int saved = 0;
-
-    /*
-     * Most functions that do_break() calls are intentionally not thread safe;
-     * therefore, make sure that all threads but this one are blocked before
-     * proceeding!
-     */
-    erts_smp_thr_progress_block();
-
-    /* during break we revert to initial settings */
-    /* this is done differently for oldshell */
-    if (using_oldshell && !replace_intr) {
-      SET_BLOCKING(1);
-    }
-    else if (isatty(0)) {
-      tcgetattr(0,&temp_mode);
-      tcsetattr(0,TCSANOW,&initial_tty_mode);
-      saved = 1;
-    }
-
-    /* call the break handling function, reset the flag */
-    do_break();
-
-    fflush(stdout);
-
-    /* after break we go back to saved settings */
-    if (using_oldshell && !replace_intr) {
-      SET_NONBLOCKING(1);
-    }
-    else if (saved) {
-      tcsetattr(0,TCSANOW,&temp_mode);
-    }
-
-    erts_smp_thr_progress_unblock();
-}
-
-static pid_t
-getpid(void)
-{
-   return get_bid(current_process());
-}
-
-int getpagesize(void)
-{
-   return 1024;
-}
-
-
-/* Fills in the systems representation of the jam/beam process identifier.
-** The Pid is put in STRING representation in the supplied buffer,
-** no interpretatione of this should be done by the rest of the
-** emulator. The buffer should be at least 21 bytes long.
-*/
-void sys_get_pid(char *buffer, size_t buffer_size){
-    pid_t p = getpid();
-    /* Assume the pid is scalar and can rest in an unsigned long... */
-    erts_snprintf(buffer, buffer_size, "%lu",(unsigned long) p);
-}
-
-int
-erts_sys_putenv_raw(char *key, char *value) {
-    return erts_sys_putenv(key, value);
-}
-int
-erts_sys_putenv(char *key, char *value)
-{
-    int res;
-
-    erts_smp_rwmtx_rwlock(&environ_rwmtx);
-    res = set_env(get_bid(current_process()), key,
-		  value);
-    erts_smp_rwmtx_rwunlock(&environ_rwmtx);
-    return res;
-}
-
-
-int
-erts_sys_unsetenv(char *key)
-{
-    int res;
-
-    erts_smp_rwmtx_rwlock(&environ_rwmtx);
-    res = set_env(get_bid(current_process()),key,NULL);
-    erts_smp_rwmtx_rwunlock(&environ_rwmtx);
-
-    return res;
-}
-
-int
-erts_sys_getenv__(char *key, char *value, size_t *size)
-{
-    int res;
-    char *orig_value = get_env(get_bid(current_process()), key);
-    if (!orig_value)
-	res = -1;
-    else {
-	size_t len = sys_strlen(orig_value);
-	if (len >= *size) {
-	    *size = len + 1;
-	    res = 1;
-	}
-	else {
-	    *size = len;
-	    sys_memcpy((void *) value, (void *) orig_value, len+1);
-	    res = 0;
-	}
-	free_buf((union SIGNAL **)&orig_value);
-    }
-    return res;
-}
-
-int
-erts_sys_getenv_raw(char *key, char *value, size_t *size) {
-    return erts_sys_getenv(key, value, size);
-}
-
-/*
- * erts_sys_getenv
- * returns:
- *  -1, if environment key is not set with a value
- *   0, if environment key is set and value fits into buffer res
- *   1, if environment key is set but does not fit into buffer res
- *      res is set with the needed buffer res value
- */
-
-int
-erts_sys_getenv(char *key, char *value, size_t *size)
-{
-    int res;
-    erts_smp_rwmtx_rlock(&environ_rwmtx);
-    res = erts_sys_getenv__(key, value, size);
-    erts_smp_rwmtx_runlock(&environ_rwmtx);
-    return res;
-}
-
-void
-sys_init_io(void)
-{
-    fd_data = (struct fd_data *)
-	erts_alloc(ERTS_ALC_T_FD_TAB, max_files * sizeof(struct fd_data));
-    erts_smp_atomic_add_nob(&sys_misc_mem_sz,
-			    max_files * sizeof(struct fd_data));
-}
-
-extern const char pre_loaded_code[];
-extern Preload pre_loaded[];
-
-void erts_sys_alloc_init(void)
-{
-}
-
-void *erts_sys_alloc(ErtsAlcType_t t, void *x, Uint sz)
-{
-    void *res = malloc((size_t) sz);
-#if HAVE_ERTS_MSEG
-    if (!res) {
-	erts_mseg_clear_cache();
-	return malloc((size_t) sz);
-    }
-#endif
-    return res;
-}
-
-void *erts_sys_realloc(ErtsAlcType_t t, void *x, void *p, Uint sz)
-{
-    void *res = realloc(p, (size_t) sz);
-#if HAVE_ERTS_MSEG
-    if (!res) {
-	erts_mseg_clear_cache();
-	return realloc(p, (size_t) sz);
-    }
-#endif
-    return res;
-}
-
-void erts_sys_free(ErtsAlcType_t t, void *x, void *p)
-{
-    free(p);
-}
-
-/* Return a pointer to a vector of names of preloaded modules */
-
-Preload*
-sys_preloaded(void)
-{
-    return pre_loaded;
-}
-
-/* Return a pointer to preloaded code for module "module" */
-unsigned char*
-sys_preload_begin(Preload* p)
-{
-    return p->code;
-}
-
-/* Clean up if allocated */
-void sys_preload_end(Preload* p)
-{
-    /* Nothing */
-}
-
-/* Read a key from console (?) */
-
-int sys_get_key(fd)
-int fd;
-{
-    int c;
-    unsigned char rbuf[64];
-
-    fflush(stdout);		/* Flush query ??? */
-
-    if ((c = read(fd,rbuf,64)) <= 0) {
-      return c;
-    }
-
-    return rbuf[0];
-}
-
-
-#ifdef DEBUG
-
-extern int erts_initialized;
-void
-erl_assert_error(const char* expr, const char* func,
-		 const char* file, int line)
-{
-    fflush(stdout);
-    fprintf(stderr, "%s:%d:%s() Assertion failed: %s\n",
-	    file, line, func, expr);
-    fflush(stderr);
-    ramlog_printf("%s:%d:%s() Assertion failed: %s\n",
-		  file, line, func, expr);
-
-    abort();
-}
-
-void
-erl_debug(char* fmt, ...)
-{
-    char sbuf[1024];		/* Temporary buffer. */
-    va_list va;
-
-    if (debug_log) {
-	va_start(va, fmt);
-	vsprintf(sbuf, fmt, va);
-	va_end(va);
-	fprintf(stderr, "%s", sbuf);
-    }
-}
-
-#endif /* DEBUG */
-
-static ERTS_INLINE void
-report_exit_status(ErtsSysReportExit *rep, int status)
-{
-   if (rep->ifd >= 0) {
-      driver_data[rep->ifd].alive = 0;
-      driver_data[rep->ifd].status = status;
-   }
-   if (rep->ofd >= 0) {
-      driver_data[rep->ofd].alive = 0;
-      driver_data[rep->ofd].status = status;
-   }
-
-   erts_free(ERTS_ALC_T_PRT_REP_EXIT, rep);
-}
-
-#define ERTS_REPORT_EXIT_STATUS report_exit_status
-
-/*
- * Called from schedule() when it runs out of runnable processes,
- * or when Erlang code has performed INPUT_REDUCTIONS reduction
- * steps. runnable == 0 iff there are no runnable Erlang processes.
- */
-void
-erl_sys_schedule(int runnable)
-{
-    ASSERT(get_fsem(current_process()) == 0);
-#ifdef ERTS_SMP
-    ASSERT(erts_get_scheduler_data()->no == 1);
-    ERTS_CHK_IO(!runnable);
-#else
-    ERTS_CHK_IO( 1 );
-#endif
-    ASSERT(get_fsem(current_process()) == 0);
-    ERTS_SMP_LC_ASSERT(!erts_thr_progress_is_blocking());
-}
-
-
-#ifdef ERTS_SMP
-
-void
-erts_sys_main_thread(void)
-{
-    erts_thread_disable_fpe();
-
-    /* Become signal receiver thread... */
-#ifdef ERTS_ENABLE_LOCK_CHECK
-    erts_lc_set_thread_name("signal_receiver");
-#endif
-
-    while (1) {
-       static const SIGSELECT sigsel[] = {0};
-       union SIGNAL *msg = receive(sigsel);
-
-       fprintf(stderr,"Main thread got message %d from 0x%x!!\r\n",
-               msg->sig_no, sender(&msg));
-       free_buf(&msg);
-    }
-}
-
-#endif /* ERTS_SMP */
-
-void
-erl_sys_args(int* argc, char** argv)
-{
-    int i, j;
-
-    erts_smp_rwmtx_init(&environ_rwmtx, "environ");
-
-    init_check_io();
-
-    /* Handled arguments have been marked with NULL. Slide arguments
-       not handled towards the beginning of argv. */
-    for (i = 0, j = 0; i < *argc; i++) {
-	if (argv[i])
-	    argv[j++] = argv[i];
-    }
-    *argc = j;
-
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/sys_float.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/sys_float.c
--- otp_src_18.3.4.5/erts/emulator/sys/ose/sys_float.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/sys_float.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,845 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2001-2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include "sys.h"
-#include "global.h"
-#include "erl_process.h"
-
-
-#ifdef NO_FPE_SIGNALS
-
-void
-erts_sys_init_float(void)
-{
-# ifdef SIGFPE
-    sys_sigset(SIGFPE, SIG_IGN); /* Ignore so we can test for NaN and Inf */
-# endif
-}
-
-#else  /* !NO_FPE_SIGNALS */
-
-#ifdef ERTS_SMP
-static erts_tsd_key_t fpe_key;
-
-/* once-only initialisation early in the main thread (via erts_sys_init_float()) */
-static void erts_init_fp_exception(void)
-{
-    /* XXX: the wrappers prevent using a pthread destructor to
-       deallocate the key's value; so when/where do we do that? */
-    erts_tsd_key_create(&fpe_key);
-}
-
-void erts_thread_init_fp_exception(void)
-{
-    unsigned long *fpe = erts_alloc(ERTS_ALC_T_FP_EXCEPTION, sizeof(*fpe));
-    *fpe = 0L;
-    erts_tsd_set(fpe_key, fpe);
-}
-
-static ERTS_INLINE volatile unsigned long *erts_thread_get_fp_exception(void)
-{
-    return (volatile unsigned long*)erts_tsd_get(fpe_key);
-}
-#else /* !SMP */
-#define erts_init_fp_exception()	/*empty*/
-static volatile unsigned long fp_exception;
-#define erts_thread_get_fp_exception()	(&fp_exception)
-#endif /* SMP */
-
-volatile unsigned long *erts_get_current_fp_exception(void)
-{
-    Process *c_p;
-
-    c_p = erts_get_current_process();
-    if (c_p)
-	return &c_p->fp_exception;
-    return erts_thread_get_fp_exception();
-}
-
-static void set_current_fp_exception(unsigned long pc)
-{
-    volatile unsigned long *fpexnp = erts_get_current_fp_exception();
-    ASSERT(fpexnp != NULL);
-    *fpexnp = pc;
-}
-
-void erts_fp_check_init_error(volatile unsigned long *fpexnp)
-{
-    char buf[64];
-    snprintf(buf, sizeof buf, "ERTS_FP_CHECK_INIT at %p: detected unhandled FPE at %p\r\n",
-	     __builtin_return_address(0), (void*)*fpexnp);
-    if (write(2, buf, strlen(buf)) <= 0)
-	erts_exit(ERTS_ABORT_EXIT, "%s", buf);
-    *fpexnp = 0;
-#if defined(__i386__) || defined(__x86_64__)
-    erts_restore_fpu();
-#endif
-}
-
-/* Is there no standard identifier for Darwin/MacOSX ? */
-#if defined(__APPLE__) && defined(__MACH__) && !defined(__DARWIN__)
-#define __DARWIN__ 1
-#endif
-
-#if (defined(__i386__) || defined(__x86_64__)) && defined(__GNUC__)
-
-static void unmask_x87(void)
-{
-    unsigned short cw;
-
-    __asm__ __volatile__("fstcw %0" : "=m"(cw));
-    cw &= ~(0x01|0x04|0x08);   /* unmask IM, ZM, OM */
-    __asm__ __volatile__("fldcw %0" : : "m"(cw));
-}
-
-/* mask x87 FPE, return true if the previous state was unmasked */
-static int mask_x87(void)
-{
-    unsigned short cw;
-    int unmasked;
-
-    __asm__ __volatile__("fstcw %0" : "=m"(cw));
-    unmasked = (cw & (0x01|0x04|0x08)) == 0;
-    /* or just set cw = 0x37f */
-    cw |= (0x01|0x04|0x08); /* mask IM, ZM, OM */
-    __asm__ __volatile__("fldcw %0" : : "m"(cw));
-    return unmasked;
-}
-
-static void unmask_sse2(void)
-{
-    unsigned int mxcsr;
-
-    __asm__ __volatile__("stmxcsr %0" : "=m"(mxcsr));
-    mxcsr &= ~(0x003F|0x0680); /* clear exn flags, unmask OM, ZM, IM (not PM, UM, DM) */
-    __asm__ __volatile__("ldmxcsr %0" : : "m"(mxcsr));
-}
-
-/* mask SSE2 FPE, return true if the previous state was unmasked */
-static int mask_sse2(void)
-{
-    unsigned int mxcsr;
-    int unmasked;
-
-    __asm__ __volatile__("stmxcsr %0" : "=m"(mxcsr));
-    unmasked = (mxcsr & 0x0680) == 0;
-    /* or just set mxcsr = 0x1f80 */
-    mxcsr &= ~0x003F; /* clear exn flags */
-    mxcsr |=  0x0680; /* mask OM, ZM, IM (not PM, UM, DM) */
-    __asm__ __volatile__("ldmxcsr %0" : : "m"(mxcsr));
-    return unmasked;
-}
-
-#if defined(__x86_64__)
-
-static inline int cpu_has_sse2(void) { return 1; }
-
-#else /* !__x86_64__ */
-
-/*
- * Check if an x86-32 processor has SSE2.
- */
-static unsigned int xor_eflags(unsigned int mask)
-{
-    unsigned int eax, edx;
-
-    eax = mask;			/* eax = mask */
-    __asm__("pushfl\n\t"
-	    "popl %0\n\t"	/* edx = original EFLAGS */
-	    "xorl %0, %1\n\t"	/* eax = mask ^ EFLAGS */
-	    "pushl %1\n\t"
-	    "popfl\n\t"		/* new EFLAGS = mask ^ original EFLAGS */
-	    "pushfl\n\t"
-	    "popl %1\n\t"	/* eax = new EFLAGS */
-	    "xorl %0, %1\n\t"	/* eax = new EFLAGS ^ old EFLAGS */
-	    "pushl %0\n\t"
-	    "popfl"		/* restore original EFLAGS */
-	    : "=d"(edx), "=a"(eax)
-	    : "1"(eax));
-    return eax;
-}
-
-static __inline__ unsigned int cpuid_eax(unsigned int op)
-{
-    unsigned int eax, save_ebx;
-
-    /* In PIC mode i386 reserves EBX. So we must save
-       and restore it ourselves to not upset gcc. */
-    __asm__(
-	"movl %%ebx, %1\n\t"
-	"cpuid\n\t"
-	"movl %1, %%ebx"
-	: "=a"(eax), "=m"(save_ebx)
-	: "0"(op)
-	: "cx", "dx");
-    return eax;
-}
-
-static __inline__ unsigned int cpuid_edx(unsigned int op)
-{
-    unsigned int eax, edx, save_ebx;
-
-    /* In PIC mode i386 reserves EBX. So we must save
-       and restore it ourselves to not upset gcc. */
-    __asm__(
-	"movl %%ebx, %2\n\t"
-	"cpuid\n\t"
-	"movl %2, %%ebx"
-	: "=a"(eax), "=d"(edx), "=m"(save_ebx)
-	: "0"(op)
-	: "cx");
-    return edx;
-}
-
-/* The AC bit, bit #18, is a new bit introduced in the EFLAGS
- * register on the Intel486 processor to generate alignment
- * faults. This bit cannot be set on the Intel386 processor.
- */
-static __inline__ int is_386(void)
-{
-    return ((xor_eflags(1<<18) >> 18) & 1) == 0;
-}
-
-/* Newer x86 processors have a CPUID instruction, as indicated by
- * the ID bit (#21) in EFLAGS being modifiable.
- */
-static __inline__ int has_CPUID(void)
-{
-    return (xor_eflags(1<<21) >> 21) & 1;
-}
-
-static int cpu_has_sse2(void)
-{
-    unsigned int maxlev, features;
-    static int has_sse2 = -1;
-
-    if (has_sse2 >= 0)
-	return has_sse2;
-    has_sse2 = 0;
-
-    if (is_386())
-	return 0;
-    if (!has_CPUID())
-	return 0;
-    maxlev = cpuid_eax(0);
-    /* Intel A-step Pentium had a preliminary version of CPUID.
-       It also didn't have SSE2. */
-    if ((maxlev & 0xFFFFFF00) == 0x0500)
-	return 0;
-    /* If max level is zero then CPUID cannot report any features. */
-    if (maxlev == 0)
-	return 0;
-    features = cpuid_edx(1);
-    has_sse2 = (features & (1 << 26)) != 0;
-
-    return has_sse2;
-}
-#endif /* !__x86_64__ */
-
-static void unmask_fpe(void)
-{
-    __asm__ __volatile__("fnclex");
-    unmask_x87();
-    if (cpu_has_sse2())
-	unmask_sse2();
-}
-
-static void unmask_fpe_conditional(int unmasked)
-{
-    if (unmasked)
-	unmask_fpe();
-}
-
-/* mask x86 FPE, return true if the previous state was unmasked */
-static int mask_fpe(void)
-{
-    int unmasked;
-
-    unmasked = mask_x87();
-    if (cpu_has_sse2())
-	unmasked |= mask_sse2();
-    return unmasked;
-}
-
-void erts_restore_fpu(void)
-{
-    __asm__ __volatile__("fninit");
-    unmask_x87();
-    if (cpu_has_sse2())
-	unmask_sse2();
-}
-
-#elif defined(__sparc__) && defined(__linux__)
-
-#if defined(__arch64__)
-#define LDX "ldx"
-#define STX "stx"
-#else
-#define LDX "ld"
-#define STX "st"
-#endif
-
-static void unmask_fpe(void)
-{
-    unsigned long fsr;
-
-    __asm__(STX " %%fsr, %0" : "=m"(fsr));
-    fsr &= ~(0x1FUL << 23);	/* clear FSR[TEM] field */
-    fsr |= (0x1AUL << 23);	/* enable NV, OF, DZ exceptions */
-    __asm__ __volatile__(LDX " %0, %%fsr" : : "m"(fsr));
-}
-
-static void unmask_fpe_conditional(int unmasked)
-{
-    if (unmasked)
-	unmask_fpe();
-}
-
-/* mask SPARC FPE, return true if the previous state was unmasked */
-static int mask_fpe(void)
-{
-    unsigned long fsr;
-    int unmasked;
-
-    __asm__(STX " %%fsr, %0" : "=m"(fsr));
-    unmasked = ((fsr >> 23) & 0x1A) == 0x1A;
-    fsr &= ~(0x1FUL << 23);	/* clear FSR[TEM] field */
-    __asm__ __volatile__(LDX " %0, %%fsr" : : "m"(fsr));
-    return unmasked;
-}
-
-#elif (defined(__powerpc__) && defined(__linux__)) || (defined(__ppc__) && defined(__DARWIN__))
-
-#if defined(__linux__)
-#include <sys/prctl.h>
-
-static void set_fpexc_precise(void)
-{
-    if (prctl(PR_SET_FPEXC, PR_FP_EXC_PRECISE) < 0) {
-	perror("PR_SET_FPEXC");
-	exit(1);
-    }
-}
-
-#elif defined(__DARWIN__)
-
-#include <mach/mach.h>
-#include <pthread.h>
-
-/*
- * FE0 FE1	MSR bits
- *  0   0	floating-point exceptions disabled
- *  0   1	floating-point imprecise nonrecoverable
- *  1   0	floating-point imprecise recoverable
- *  1   1	floating-point precise mode
- *
- * Apparently:
- * - Darwin 5.5 (MacOS X <= 10.1) starts with FE0 == FE1 == 0,
- *   and resets FE0 and FE1 to 0 after each SIGFPE.
- * - Darwin 6.0 (MacOS X 10.2) starts with FE0 == FE1 == 1,
- *   and does not reset FE0 or FE1 after a SIGFPE.
- */
-#define FE0_MASK	(1<<11)
-#define FE1_MASK	(1<<8)
-
-/* a thread cannot get or set its own MSR bits */
-static void *fpu_fpe_enable(void *arg)
-{
-    thread_t t = *(thread_t*)arg;
-    struct ppc_thread_state state;
-    unsigned int state_size = PPC_THREAD_STATE_COUNT;
-
-    if (thread_get_state(t, PPC_THREAD_STATE, (natural_t*)&state, &state_size) != KERN_SUCCESS) {
-	perror("thread_get_state");
-	exit(1);
-    }
-    if ((state.srr1 & (FE1_MASK|FE0_MASK)) != (FE1_MASK|FE0_MASK)) {
-#if 1
-	/* This would also have to be performed in the SIGFPE handler
-	   to work around the MSR reset older Darwin releases do. */
-	state.srr1 |= (FE1_MASK|FE0_MASK);
-	thread_set_state(t, PPC_THREAD_STATE, (natural_t*)&state, state_size);
-#else
-	fprintf(stderr, "srr1 == 0x%08x, your Darwin is too old\n", state.srr1);
-	exit(1);
-#endif
-    }
-    return NULL; /* Ok, we appear to be on Darwin 6.0 or later */
-}
-
-static void set_fpexc_precise(void)
-{
-    thread_t self = mach_thread_self();
-    pthread_t enabler;
-
-    if (pthread_create(&enabler, NULL, fpu_fpe_enable, &self)) {
-	perror("pthread_create");
-    } else if (pthread_join(enabler, NULL)) {
-	perror("pthread_join");
-    }
-}
-
-#endif
-
-static void set_fpscr(unsigned int fpscr)
-{
-    union {
-	double d;
-	unsigned int fpscr[2];
-    } u;
-
-    u.fpscr[0] = 0xFFF80000;
-    u.fpscr[1] = fpscr;
-    __asm__ __volatile__("mtfsf 255,%0" : : "f"(u.d));
-}
-
-static unsigned int get_fpscr(void)
-{
-    union {
-	double d;
-	unsigned int fpscr[2];
-    } u;
-
-    __asm__("mffs %0" : "=f"(u.d));
-    return u.fpscr[1];
-}
-
-static void unmask_fpe(void)
-{
-    set_fpexc_precise();
-    set_fpscr(0x80|0x40|0x10);	/* VE, OE, ZE; not UE or XE */
-}
-
-static void unmask_fpe_conditional(int unmasked)
-{
-    if (unmasked)
-	unmask_fpe();
-}
-
-/* mask PowerPC FPE, return true if the previous state was unmasked */
-static int mask_fpe(void)
-{
-    int unmasked;
-
-    unmasked = (get_fpscr() & (0x80|0x40|0x10)) == (0x80|0x40|0x10);
-    set_fpscr(0x00);
-    return unmasked;
-}
-
-#else
-
-static void unmask_fpe(void)
-{
-    fpsetmask(FP_X_INV | FP_X_OFL | FP_X_DZ);
-}
-
-static void unmask_fpe_conditional(int unmasked)
-{
-    if (unmasked)
-	unmask_fpe();
-}
-
-/* mask IEEE FPE, return true if previous state was unmasked */
-static int mask_fpe(void)
-{
-    const fp_except unmasked_mask = FP_X_INV | FP_X_OFL | FP_X_DZ;
-    fp_except old_mask;
-
-    old_mask = fpsetmask(0);
-    return (old_mask & unmasked_mask) == unmasked_mask;
-}
-
-#endif
-
-#if (defined(__linux__) && (defined(__i386__) || defined(__x86_64__) || defined(__sparc__) || defined(__powerpc__))) || (defined(__DARWIN__) && (defined(__i386__) || defined(__x86_64__) || defined(__ppc__))) || (defined(__FreeBSD__) && (defined(__x86_64__) || defined(__i386__))) || ((defined(__NetBSD__) || defined(__OpenBSD__)) && defined(__x86_64__)) || (defined(__sun__) && defined(__x86_64__))
-
-#if defined(__linux__) && defined(__i386__)
-#if !defined(X86_FXSR_MAGIC)
-#define X86_FXSR_MAGIC 0x0000
-#endif
-#elif defined(__FreeBSD__) && defined(__x86_64__)
-#include <sys/types.h>
-#include <machine/fpu.h>
-#elif defined(__FreeBSD__) && defined(__i386__)
-#include <sys/types.h>
-#include <machine/npx.h>
-#elif defined(__DARWIN__)
-#include <machine/signal.h>
-#elif defined(__OpenBSD__) && defined(__x86_64__)
-#include <sys/types.h>
-#include <machine/fpu.h>
-#endif
-#if !(defined(__OpenBSD__) && defined(__x86_64__))
-#include <ucontext.h>
-#endif
-#include <string.h>
-
-#if defined(__linux__) && defined(__x86_64__)
-#define mc_pc(mc)	((mc)->gregs[REG_RIP])
-#elif defined(__linux__) && defined(__i386__)
-#define mc_pc(mc)	((mc)->gregs[REG_EIP])
-#elif defined(__DARWIN__) && defined(__i386__)
-#ifdef DARWIN_MODERN_MCONTEXT
-#define mc_pc(mc)	((mc)->__ss.__eip)
-#else
-#define mc_pc(mc)	((mc)->ss.eip)
-#endif
-#elif defined(__DARWIN__) && defined(__x86_64__)
-#ifdef DARWIN_MODERN_MCONTEXT
-#define mc_pc(mc)	((mc)->__ss.__rip)
-#else
-#define mc_pc(mc)	((mc)->ss.rip)
-#endif
-#elif defined(__FreeBSD__) && defined(__x86_64__)
-#define mc_pc(mc)	((mc)->mc_rip)
-#elif defined(__FreeBSD__) && defined(__i386__)
-#define mc_pc(mc)	((mc)->mc_eip)
-#elif defined(__NetBSD__) && defined(__x86_64__)
-#define mc_pc(mc)	((mc)->__gregs[_REG_RIP])
-#elif defined(__NetBSD__) && defined(__i386__)
-#define mc_pc(mc)	((mc)->__gregs[_REG_EIP])
-#elif defined(__OpenBSD__) && defined(__x86_64__)
-#define mc_pc(mc)	((mc)->sc_rip)
-#elif defined(__sun__) && defined(__x86_64__)
-#define mc_pc(mc)	((mc)->gregs[REG_RIP])
-#endif
-
-static void fpe_sig_action(int sig, siginfo_t *si, void *puc)
-{
-    ucontext_t *uc = puc;
-    unsigned long pc;
-
-#if defined(__linux__)
-#if defined(__x86_64__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    fpregset_t fpstate = mc->fpregs;
-    pc = mc_pc(mc);
-    /* A failed SSE2 instruction will restart. To avoid
-       looping we mask SSE2 exceptions now and unmask them
-       again later in erts_check_fpe()/erts_restore_fpu().
-       On RISCs we update PC to skip the failed instruction,
-       but the ever increasing complexity of the x86 instruction
-       set encoding makes that a poor solution here. */
-    fpstate->mxcsr = 0x1F80;
-    fpstate->swd &= ~0xFF;
-#elif defined(__i386__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    fpregset_t fpstate = mc->fpregs;
-    pc = mc_pc(mc);
-    if ((fpstate->status >> 16) == X86_FXSR_MAGIC)
-	((struct _fpstate*)fpstate)->mxcsr = 0x1F80;
-    fpstate->sw &= ~0xFF;
-#elif defined(__sparc__) && defined(__arch64__)
-    /* on SPARC the 3rd parameter points to a sigcontext not a ucontext */
-    struct sigcontext *sc = (struct sigcontext*)puc;
-    pc = sc->sigc_regs.tpc;
-    sc->sigc_regs.tpc = sc->sigc_regs.tnpc;
-    sc->sigc_regs.tnpc += 4;
-#elif defined(__sparc__)
-    /* on SPARC the 3rd parameter points to a sigcontext not a ucontext */
-    struct sigcontext *sc = (struct sigcontext*)puc;
-    pc = sc->si_regs.pc;
-    sc->si_regs.pc = sc->si_regs.npc;
-    sc->si_regs.npc = (unsigned long)sc->si_regs.npc + 4;
-#elif defined(__powerpc__)
-#if defined(__powerpc64__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    unsigned long *regs = &mc->gp_regs[0];
-#else
-    mcontext_t *mc = uc->uc_mcontext.uc_regs;
-    unsigned long *regs = &mc->gregs[0];
-#endif
-    pc = regs[PT_NIP];
-    regs[PT_NIP] += 4;
-    regs[PT_FPSCR] = 0x80|0x40|0x10;	/* VE, OE, ZE; not UE or XE */
-#endif
-#elif defined(__DARWIN__) && (defined(__i386__) || defined(__x86_64__))
-#ifdef DARWIN_MODERN_MCONTEXT
-    mcontext_t mc = uc->uc_mcontext;
-    pc = mc_pc(mc);
-    mc->__fs.__fpu_mxcsr = 0x1F80;
-    *(unsigned short *)&mc->__fs.__fpu_fsw &= ~0xFF;
-#else
-    mcontext_t mc = uc->uc_mcontext;
-    pc = mc_pc(mc);
-    mc->fs.fpu_mxcsr = 0x1F80;
-    *(unsigned short *)&mc->fs.fpu_fsw &= ~0xFF;
-#endif /* DARWIN_MODERN_MCONTEXT */
-#elif defined(__DARWIN__) && defined(__ppc__)
-    mcontext_t mc = uc->uc_mcontext;
-    pc = mc->ss.srr0;
-    mc->ss.srr0 += 4;
-    mc->fs.fpscr = 0x80|0x40|0x10;
-#elif defined(__FreeBSD__) && defined(__x86_64__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    struct savefpu *savefpu = (struct savefpu*)&mc->mc_fpstate;
-    struct envxmm *envxmm = &savefpu->sv_env;
-    pc = mc_pc(mc);
-    envxmm->en_mxcsr = 0x1F80;
-    envxmm->en_sw &= ~0xFF;
-#elif defined(__FreeBSD__) && defined(__i386__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    union savefpu *savefpu = (union savefpu*)&mc->mc_fpstate;
-    pc = mc_pc(mc);
-    if (mc->mc_fpformat == _MC_FPFMT_XMM) {
-	struct envxmm *envxmm = &savefpu->sv_xmm.sv_env;
-	envxmm->en_mxcsr = 0x1F80;
-	envxmm->en_sw &= ~0xFF;
-    } else {
-	struct env87 *env87 = &savefpu->sv_87.sv_env;
-	env87->en_sw &= ~0xFF;
-    }
-#elif defined(__NetBSD__) && defined(__x86_64__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    struct fxsave64 *fxsave = (struct fxsave64 *)&mc->__fpregs;
-    pc = mc_pc(mc);
-    fxsave->fx_mxcsr = 0x1F80;
-    fxsave->fx_fsw &= ~0xFF;
-#elif defined(__NetBSD__) && defined(__i386__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    pc = mc_pc(mc);
-    if (uc->uc_flags & _UC_FXSAVE) {
-	struct envxmm *envxmm = (struct envxmm *)&mc->__fpregs;
-	envxmm->en_mxcsr = 0x1F80;
-	envxmm->en_sw &= ~0xFF;
-    } else {
-	struct env87 *env87 = (struct env87 *)&mc->__fpregs;
-	env87->en_sw &= ~0xFF;
-    }
-#elif defined(__OpenBSD__) && defined(__x86_64__)
-    struct fxsave64 *fxsave = uc->sc_fpstate;
-    pc = mc_pc(uc);
-    fxsave->fx_mxcsr = 0x1F80;
-    fxsave->fx_fsw &= ~0xFF;
-#elif defined(__sun__) && defined(__x86_64__)
-    mcontext_t *mc = &uc->uc_mcontext;
-    struct fpchip_state *fpstate = &mc->fpregs.fp_reg_set.fpchip_state;
-    pc = mc_pc(mc);
-    fpstate->mxcsr = 0x1F80;
-    fpstate->sw &= ~0xFF;
-#endif
-#if 0
-    {
-	char buf[64];
-	snprintf(buf, sizeof buf, "%s: FPE at %p\r\n", __FUNCTION__, (void*)pc);
-	write(2, buf, strlen(buf));
-    }
-#endif
-    set_current_fp_exception(pc);
-}
-
-static void erts_thread_catch_fp_exceptions(void)
-{
-    struct sigaction act;
-    memset(&act, 0, sizeof act);
-    act.sa_sigaction = fpe_sig_action;
-    act.sa_flags = SA_SIGINFO;
-    sigaction(SIGFPE, &act, NULL);
-    unmask_fpe();
-}
-
-#else  /* !((__linux__ && (__i386__ || __x86_64__ || __powerpc__)) || (__DARWIN__ && (__i386__ || __x86_64__ || __ppc__))) */
-
-static void fpe_sig_handler(int sig)
-{
-    set_current_fp_exception(1); /* XXX: convert to sigaction so we can get the trap PC */
-}
-
-static void erts_thread_catch_fp_exceptions(void)
-{
-    sys_sigset(SIGFPE, fpe_sig_handler);
-    unmask_fpe();
-}
-
-#endif /* (__linux__ && (__i386__ || __x86_64__ || __powerpc__)) || (__DARWIN__ && (__i386__ || __x86_64__ || __ppc__))) */
-
-/* once-only initialisation early in the main thread */
-void erts_sys_init_float(void)
-{
-    erts_init_fp_exception();
-    erts_thread_catch_fp_exceptions();
-    erts_printf_block_fpe = erts_sys_block_fpe;
-    erts_printf_unblock_fpe = erts_sys_unblock_fpe;
-}
-
-#endif /* NO_FPE_SIGNALS */
-
-void erts_thread_init_float(void)
-{
-#ifdef ERTS_SMP
-    /* This allows Erlang schedulers to leave Erlang-process context
-       and still have working FP exceptions. XXX: is this needed? */
-    erts_thread_init_fp_exception();
-#endif
-
-#ifndef NO_FPE_SIGNALS
-    /* NOTE:
-     *  erts_thread_disable_fpe() is called in all threads at
-     *  creation. We at least need to call unmask_fpe()
-     */
-#if defined(__DARWIN__) || defined(__FreeBSD__)
-    /* Darwin (7.9.0) does not appear to propagate FP exception settings
-       to a new thread from its parent. So if we want FP exceptions, we
-       must manually re-enable them in each new thread.
-       FreeBSD 6.1 appears to suffer from a similar issue. */
-    erts_thread_catch_fp_exceptions();
-#else
-    unmask_fpe();
-#endif
-
-#endif
-}
-
-void erts_thread_disable_fpe(void)
-{
-#if !defined(NO_FPE_SIGNALS)
-    (void)mask_fpe();
-#endif
-}
-
-#if !defined(NO_FPE_SIGNALS)
-int erts_sys_block_fpe(void)
-{
-    return mask_fpe();
-}
-
-void erts_sys_unblock_fpe(int unmasked)
-{
-    unmask_fpe_conditional(unmasked);
-}
-#endif
-
-/* The following check is incorporated from the Vee machine */
-
-#define ISDIGIT(d) ((d) >= '0' && (d) <= '9')
-
-/*
- ** Convert a double to ascii format 0.dddde[+|-]ddd
- ** return number of characters converted or -1 if error.
- **
- ** These two functions should maybe use localeconv() to pick up
- ** the current radix character, but since it is uncertain how
- ** expensive such a system call is, and since no-one has heard
- ** of other radix characters than '.' and ',' an ad-hoc
- ** low execution time solution is used instead.
- */
-
-int
-sys_double_to_chars_ext(double fp, char *buffer, size_t buffer_size, size_t decimals)
-{
-    char *s = buffer;
-
-    if (erts_snprintf(buffer, buffer_size, "%.*e", decimals, fp) >= buffer_size)
-        return -1;
-    /* Search upto decimal point */
-    if (*s == '+' || *s == '-') s++;
-    while (ISDIGIT(*s)) s++;
-    if (*s == ',') *s++ = '.'; /* Replace ',' with '.' */
-    /* Scan to end of string */
-    while (*s) s++;
-    return s-buffer; /* i.e strlen(buffer) */
-}
-
-/* Float conversion */
-
-int
-sys_chars_to_double(char* buf, double* fp)
-{
-#ifndef NO_FPE_SIGNALS
-    volatile unsigned long *fpexnp = erts_get_current_fp_exception();
-#endif
-    char *s = buf, *t, *dp;
-
-    /* Robert says that something like this is what he really wanted:
-     * (The [.,] radix test is NOT what Robert wanted - it was added later)
-     *
-     * 7 == sscanf(Tbuf, "%[+-]%[0-9][.,]%[0-9]%[eE]%[+-]%[0-9]%s", ....);
-     * if (*s2 == 0 || *s3 == 0 || *s4 == 0 || *s6 == 0 || *s7)
-     *   break;
-     */
-
-    /* Scan string to check syntax. */
-    if (*s == '+' || *s == '-') s++;
-    if (!ISDIGIT(*s))		/* Leading digits. */
-      return -1;
-    while (ISDIGIT(*s)) s++;
-    if (*s != '.' && *s != ',')	/* Decimal part. */
-      return -1;
-    dp = s++;			/* Remember decimal point pos just in case */
-    if (!ISDIGIT(*s))
-      return -1;
-    while (ISDIGIT(*s)) s++;
-    if (*s == 'e' || *s == 'E') {
-	/* There is an exponent. */
-	s++;
-	if (*s == '+' || *s == '-') s++;
-	if (!ISDIGIT(*s))
-	  return -1;
-	while (ISDIGIT(*s)) s++;
-    }
-    if (*s)			/* That should be it */
-      return -1;
-
-#ifdef NO_FPE_SIGNALS
-    errno = 0;
-#endif
-    __ERTS_FP_CHECK_INIT(fpexnp);
-    *fp = strtod(buf, &t);
-    __ERTS_FP_ERROR_THOROUGH(fpexnp, *fp, return -1);
-    if (t != s) {		/* Whole string not scanned */
-	/* Try again with other radix char */
-	*dp = (*dp == '.') ? ',' : '.';
-	errno = 0;
-	__ERTS_FP_CHECK_INIT(fpexnp);
-	*fp = strtod(buf, &t);
-	__ERTS_FP_ERROR_THOROUGH(fpexnp, *fp, return -1);
-    }
-
-#ifdef NO_FPE_SIGNALS
-    if (errno == ERANGE) {
-	if (*fp == HUGE_VAL || *fp == -HUGE_VAL) {
-	    /* overflow, should give error */
-	    return -1;
-	} else if (t == s && *fp == 0.0) {
-	    /* This should give 0.0 - OTP-7178 */
-	    errno = 0;
-
-	} else if (*fp == 0.0) {
-	    return -1;
-	}
-    }
-#endif
-    return 0;
-}
-
-int
-matherr(struct exception *exc)
-{
-#if !defined(NO_FPE_SIGNALS)
-    volatile unsigned long *fpexnp = erts_get_current_fp_exception();
-    if (fpexnp != NULL)
-	*fpexnp = (unsigned long)__builtin_return_address(0);
-#endif
-    return 1;
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/sys/ose/sys_time.c otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/sys_time.c
--- otp_src_18.3.4.5/erts/emulator/sys/ose/sys_time.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/sys/ose/sys_time.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,57 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2005-2009. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include "sys.h"
-#include "global.h"
-
-/******************* Routines for time measurement *********************/
-
-int erts_ticks_per_sec = 0; /* Will be SYS_CLK_TCK in erl_unix_sys.h */
-
-int sys_init_time(void)
-{
-  return SYS_CLOCK_RESOLUTION;
-}
-
-clock_t sys_times(SysTimes *now) {
-  now->tms_utime = now->tms_stime = now->tms_cutime =  now->tms_cstime = 0;
-  return 0;
-}
-
-static OSTICK last_tick_count = 0;
-static SysHrTime wrap = 0;
-static OSTICK us_per_tick;
-
-void sys_init_hrtime() {
-  us_per_tick = system_tick();
-}
-
-SysHrTime sys_gethrtime() {
-  OSTICK ticks = get_ticks();
-  if (ticks < (SysHrTime) last_tick_count) {
-    wrap += 1ULL << 32;
-  }
-  last_tick_count = ticks;
-  return ((((SysHrTime) ticks) + wrap) * 1000*us_per_tick);
-}
diff -Ndurp otp_src_18.3.4.5/erts/emulator/test/emulator.spec.ose otp_src_18.3.4.5-remove-OSE-port/erts/emulator/test/emulator.spec.ose
--- otp_src_18.3.4.5/erts/emulator/test/emulator.spec.ose	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/emulator/test/emulator.spec.ose	1970-01-01 03:00:00.000000000 +0300
@@ -1,2 +0,0 @@
-{topcase, {dir, "../emulator_test"}}.
-{skip, {obsolete_SUITE, "Not on ose"}}.
diff -Ndurp otp_src_18.3.4.5/erts/epmd/src/epmd.c otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/epmd.c
--- otp_src_18.3.4.5/erts/epmd/src/epmd.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/epmd.c	2017-02-03 21:52:59.159951425 +0200
@@ -397,7 +397,7 @@ static void run_daemon(EpmdVars *g)
 }
 #endif
 
-#if defined(VXWORKS) || defined(__OSE__)
+#if defined(VXWORKS)
 static void run_daemon(EpmdVars *g)
 {
     run(g);
diff -Ndurp otp_src_18.3.4.5/erts/epmd/src/epmd_int.h otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/epmd_int.h
--- otp_src_18.3.4.5/erts/epmd/src/epmd_int.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/epmd_int.h	2017-02-03 21:52:59.163951269 +0200
@@ -37,13 +37,6 @@
 #define DONT_USE_MAIN
 #endif
 
-#ifdef __OSE__
-#  define NO_DAEMON
-#  define NO_SYSLOG
-#  define NO_SYSCONF
-#  define NO_FCNTL
-#endif
-
 /* ************************************************************************ */
 /* Standard includes                                                        */
 
@@ -101,12 +94,7 @@
 #endif /* ! WIN32 */
 
 #include <ctype.h>
-
-#if !defined(__OSE__)
-#  include <signal.h>
-#endif
-
-
+#include <signal.h>
 #include <errno.h>
 
 #ifdef HAVE_SYSLOG_H
@@ -123,10 +111,6 @@
 
 #include <stdarg.h>
 
-#ifdef __OSE__
-#  include "sys/select.h"
-#endif
-
 #ifdef HAVE_SYSTEMD_DAEMON
 #  include <systemd/sd-daemon.h>
 #endif /* HAVE_SYSTEMD_DAEMON */
diff -Ndurp otp_src_18.3.4.5/erts/epmd/src/epmd_srv.c otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/epmd_srv.c
--- otp_src_18.3.4.5/erts/epmd/src/epmd_srv.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/epmd_srv.c	2017-02-03 21:52:59.163951269 +0200
@@ -30,11 +30,6 @@
 #  define INADDR_NONE 0xffffffff
 #endif
 
-#if defined(__OSE__)
-#  include "sys/ioctl.h"
-#  define sleep(x) delay(x*1000)
-#endif
-
 /*
  *  
  *  This server is a local name server for Erlang nodes. Erlang nodes can
@@ -335,7 +330,7 @@ void run(EpmdVars *g)
     }
 #endif /* HAVE_SYSTEMD_DAEMON */
 
-#if !defined(__WIN32__) && !defined(__OSE__)
+#if !defined(__WIN32__)
   /* We ignore the SIGPIPE signal that is raised when we call write
      twice on a socket closed by the other end. */
   signal(SIGPIPE, SIG_IGN);
diff -Ndurp otp_src_18.3.4.5/erts/epmd/src/Makefile.in otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/Makefile.in
--- otp_src_18.3.4.5/erts/epmd/src/Makefile.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/epmd/src/Makefile.in	2017-02-03 21:52:59.163951269 +0200
@@ -19,10 +19,6 @@
 #
 include $(ERL_TOP)/make/target.mk
 
-ifeq ($(findstring ose,$(TARGET)),ose)
-include $(ERL_TOP)/make/$(TARGET)/ose_lm.mk
-endif
-
 ifeq ($(TYPE),debug)
 PURIFY     =
 TYPEMARKER = .debug
@@ -32,21 +28,13 @@ else
 ifeq ($(TYPE),purify)
 PURIFY     = purify
 TYPEMARKER =
-ifeq ($(findstring ose,$(TARGET)),ose)
-  TYPE_FLAGS = -DPURIFY
-else
-  TYPE_FLAGS = -O2 -DPURIFY
-endif
+TYPE_FLAGS = -O2 -DPURIFY
 else
 
 override TYPE = opt
 PURIFY     =
 TYPEMARKER =
-ifeq ($(findstring ose,$(TARGET)),ose)
-  TYPE_FLAGS =
-else
-  TYPE_FLAGS = -O2
-endif
+TYPE_FLAGS = -O2
 endif
 endif
 
@@ -68,13 +56,9 @@ else
 ifeq ($(findstring vxworks,$(TARGET)),vxworks)
 ERTS_INTERNAL_LIBS=-L../../lib/internal/$(TARGET) -lerts_internal$(ERTS_LIB_TYPEMARKER) @ERTS_INTERNAL_X_LIBS@
 else
-ifeq ($(findstring ose,$(TARGET)),ose)
-ERTS_INTERNAL_LIBS=-L../../lib/internal/$(TARGET) -lerts_internal$(ERTS_LIB_TYPEMARKER) @ERTS_INTERNAL_X_LIBS@
-else
 ERTS_INTERNAL_LIBS=-L../../lib/internal/$(TARGET) -lerts_internal$(ERTS_LIB_TYPEMARKER) @ERTS_INTERNAL_X_LIBS@ -lm
 endif
 endif
-endif
 
 ERTS_LIB = $(ERL_TOP)/erts/lib_src/obj/$(TARGET)/$(TYPE)/MADE
 
@@ -82,11 +66,7 @@ CC      = @CC@
 WFLAGS  = @WFLAGS@
 CFLAGS  = @CFLAGS@ @DEFS@ $(TYPE_FLAGS) $(WFLAGS) $(ERTS_INCL)
 LD      = @LD@
-ifeq ($(findstring ose,$(TARGET)),ose)
-LIBS    = $(ERTS_INTERNAL_LIBS) @LIBS@
-else
 LIBS    = @LIBS@ @SYSTEMD_DAEMON_LIBS@ $(ERTS_INTERNAL_LIBS)
-endif
 LDFLAGS = @LDFLAGS@
 
 
@@ -135,25 +115,12 @@ clean:
 	rm -f *.o
 	rm -f *~ core
 
-ifeq ($(findstring ose,$(TARGET)),ose)
-$(OBJDIR)/ose_confd.o: $(OSE_CONFD)
-	$(V_CC) $(CFLAGS) -o $@ -c $<
-$(OBJDIR)/crt0_lm.o: $(CRT0_LM)
-	$(V_CC) $(CFLAGS) -o $@ -c $<
-OSE_LM_OBJS += $(OBJDIR)/ose_confd.o $(OBJDIR)/crt0_lm.o
-endif
-
 #
 # Objects & executables
 #
 
-ifeq ($(findstring ose,$(TARGET)),ose)
-$(BINDIR)/$(EPMD): $(EPMD_OBJS) $(ERTS_LIB) $(OSE_LM_OBJS)
-	$(call build-ose-load-module, $@, $(EPMD_OBJS) $(OSE_LM_OBJS), $(LIBS), $(EPMD_LMCONF))
-else
 $(BINDIR)/$(EPMD): $(EPMD_OBJS) $(ERTS_LIB)
 	$(ld_verbose)$(PURIFY) $(LD) $(LDFLAGS) -o $@ $(EPMD_OBJS) $(LIBS)
-endif
 
 $(OBJDIR)/%.o: %.c epmd.h epmd_int.h
 	$(V_CC) $(CFLAGS) $(EPMD_FLAGS) -o $@ -c $<
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/Makefile.in otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/Makefile.in
--- otp_src_18.3.4.5/erts/etc/common/Makefile.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/Makefile.in	2017-02-03 21:52:59.163951269 +0200
@@ -21,10 +21,6 @@
 include $(ERL_TOP)/make/output.mk
 include $(ERL_TOP)/make/target.mk
 
-ifeq ($(findstring ose,$(TARGET)),ose)
-include $(ERL_TOP)/make/$(TARGET)/ose_lm.mk
-endif
-
 ERTS_LIB_TYPEMARKER=.$(TYPE)
 
 USING_MINGW=@MIXED_CYGWIN_MINGW@
@@ -85,18 +81,13 @@ EMUOSDIR  = $(ERL_TOP)/erts/emulator/@ER
 SYSDIR    = $(ERL_TOP)/erts/emulator/sys/@ERLANG_OSTYPE@
 DRVDIR    = $(ERL_TOP)/erts/emulator/drivers/@ERLANG_OSTYPE@
 UXETC     = ../unix
-OSEETC	  = ../ose
 WINETC	  = ../win32
 
 ifeq ($(TARGET), win32)
 ETC       = $(WINETC)
 else
-ifeq ($(findstring ose,$(TARGET)),ose)
-ETC       = $(OSEETC)
-else
 ETC       = $(UXETC)
 endif
-endif
 
 ifeq ($(TARGET), win32)
 ERLEXEC = erlexec.dll
@@ -180,25 +171,6 @@ PORT_ENTRY_POINT=erl_port_entry
 ENTRY_LDFLAGS=-entry:$(PORT_ENTRY_POINT)
 
 else
-ifeq ($(findstring ose,$(TARGET)),ose)
-ENTRY_LDFLAGS=
-ENTRY_OBJ=
-ERLSRV_OBJECTS=
-MC_OUTPUTS=
-INET_GETHOST =
-INSTALL_EMBEDDED_PROGS = $(BINDIR)/run_erl_lm
-INSTALL_EMBEDDED_DATA =
-INSTALL_TOP = Install
-INSTALL_TOP_BIN =
-INSTALL_MISC =
-INSTALL_SRC =
-ERLEXECDIR = .
-INSTALL_LIBS =
-INSTALL_OBJS =
-INSTALL_INCLUDES =
-TEXTFILES = Install erl.src
-INSTALL_PROGS = $(INSTALL_EMBEDDED_PROGS)
-else # UNIX (!win32 && !ose)
 ENTRY_LDFLAGS=
 ENTRY_OBJ=
 ERLSRV_OBJECTS= 
@@ -223,7 +195,6 @@ INSTALL_PROGS =              \
 	$(BINDIR)/$(ERLEXEC) \
 	$(INSTALL_EMBEDDED_PROGS)
 endif
-endif
 
 .PHONY: etc
 etc:	$(ENTRY_OBJ) $(INSTALL_PROGS) $(INSTALL_LIBS) $(TEXTFILES) $(INSTALL_TOP_BIN)
@@ -269,8 +240,8 @@ endif
 	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/to_erl.o
 	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/dyn_erl.o
 	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/safe_string.o
-	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/run_erl_common.o
-	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/to_erl_common.o
+	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/run_erl.o
+	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/to_erl.o
 	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/typer.o
 	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/ct_run.o
 	rm -f $(ERL_TOP)/erts/obj*/$(TARGET)/vxcall.o
@@ -423,28 +394,24 @@ $(BINDIR)/inet_gethost@EXEEXT@: $(OBJDIR
 	$(ld_verbose)$(PURIFY) $(LD) $(LDFLAGS) $(ENTRY_LDFLAGS) -o $@ $(OBJDIR)/inet_gethost.o $(ENTRY_OBJ) $(LIBS) $(ERTS_INTERNAL_LIBS)
 
 # run_erl
-$(BINDIR)/run_erl: $(OBJDIR)/safe_string.o $(OBJDIR)/run_erl.o $(OBJDIR)/run_erl_common.o
-	$(V_LD) $(LDFLAGS) -o $@ $^ $(LIBS)
-$(OBJDIR)/run_erl.o: $(ETC)/run_erl.c ../common/run_erl_common.h $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -I ../common/ -o $@ -c $(ETC)/run_erl.c
-$(OBJDIR)/run_erl_common.o: ../common/run_erl_common.c ../common/run_erl_common.h $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -o $@ -c $<
+$(BINDIR)/run_erl: $(OBJDIR)/safe_string.o $(OBJDIR)/run_erl.o
+	$(V_LD) $(LDFLAGS) -o $@ $(OBJDIR)/safe_string.o $(OBJDIR)/run_erl.o $(LIBS)
+$(OBJDIR)/run_erl.o: $(ETC)/run_erl.c $(RC_GENERATED)
+	$(V_CC) $(CFLAGS) -o $@ -c $(ETC)/run_erl.c
 
 # to_erl
-$(BINDIR)/to_erl: $(OBJDIR)/safe_string.o $(OBJDIR)/to_erl.o $(OBJDIR)/to_erl_common.o
-	$(V_LD) $(LDFLAGS) -o $@  $^
-$(OBJDIR)/to_erl.o: $(ETC)/to_erl.c ../common/safe_string.h $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -I ../common/ -o $@ -c $(ETC)/to_erl.c
-$(OBJDIR)/to_erl_common.o: ../common/to_erl_common.c ../common/to_erl_common.h $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -o $@ -c $<
+$(BINDIR)/to_erl: $(OBJDIR)/safe_string.o $(OBJDIR)/to_erl.o
+	$(V_LD) $(LDFLAGS) -o $@  $(OBJDIR)/safe_string.o $(OBJDIR)/to_erl.o
+$(OBJDIR)/to_erl.o: $(ETC)/to_erl.c $(RC_GENERATED)
+	$(V_CC) $(CFLAGS) -o $@ -c $(ETC)/to_erl.c
 
 # dyn_erl
 $(BINDIR)/dyn_erl: $(OBJDIR)/safe_string.o $(OBJDIR)/dyn_erl.o
 	$(V_LD) $(LDFLAGS) -o $@  $(OBJDIR)/safe_string.o $(OBJDIR)/dyn_erl.o
 $(OBJDIR)/dyn_erl.o: $(UXETC)/dyn_erl.c $(RC_GENERATED)
 	$(V_CC) $(CFLAGS) -o $@ -c $(UXETC)/dyn_erl.c
-$(OBJDIR)/safe_string.o: ../common/safe_string.c $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -o $@ -c ../common/safe_string.c
+$(OBJDIR)/safe_string.o: $(ETC)/safe_string.c $(RC_GENERATED)
+	$(V_CC) $(CFLAGS) -o $@ -c $(ETC)/safe_string.c
 
 ifneq ($(TARGET),win32)
 $(BINDIR)/$(ERLEXEC): $(OBJDIR)/$(ERLEXEC).o $(ERTS_LIB)
@@ -499,30 +466,6 @@ erl.src: $(UXETC)/erl.src.src ../../vsn.
             -e 's;%VSN%;$(VSN);' \
                   $(UXETC)/erl.src.src > erl.src
 
-#---------------------------------------------------------
-# OSE specific targets
-#---------------------------------------------------------
-ifeq ($(findstring ose,$(TARGET)),ose)
-$(OBJDIR)/ose_confd.o: $(OSE_CONFD)
-	$(V_CC) $(CFLAGS) -o $@ -c $<
-$(OBJDIR)/crt0_lm.o: $(CRT0_LM)
-	$(V_CC) $(CFLAGS) -o $@ -c $<
-OSE_LM_OBJS += $(OBJDIR)/ose_confd.o $(OBJDIR)/crt0_lm.o
-
-$(BINDIR)/run_erl_lm: $(OBJDIR)/run_erl_main.o $(OBJDIR)/safe_string.o $(OBJDIR)/run_erl.o $(OBJDIR)/run_erl_common.o $(OBJDIR)/to_erl_common.o $(OSE_LM_OBJS)
-	$(call build-ose-load-module, $@, $^, $(LIBS), $(RUN_ERL_LMCONF))
-
-
-$(OBJDIR)/run_erl_main.o: $(OSEETC)/run_erl_main.c $(OSEETC)/run_erl.h ../common/to_erl_common.h $(RC_GENERATED)
-	$(V_CC) $(CFLAGS) -I ../common/ -o $@ -c $(OSEETC)/run_erl_main.c
-
-endif
-
-#---------------------------------------------------------
-# End of ose specific targets.
-#---------------------------------------------------------
-
-
 # ----------------------------------------------------
 # Release Target
 # ---------------------------------------------------- 
@@ -537,11 +480,9 @@ endif
 	$(INSTALL_DIR) "$(RELEASE_PATH)/erts-$(VSN)/bin"
 ifneq ($(TARGET), win32)
 ifneq ($(findstring vxworks,$(TARGET)), vxworks)
-ifneq ($(findstring ose,$(TARGET)), ose)
 	$(INSTALL_SCRIPT) erl.src "$(RELEASE_PATH)/erts-$(VSN)/bin"
 endif
 endif
-endif
 ifneq ($(INSTALL_PROGS),)
 	$(INSTALL_PROGRAM) $(INSTALL_PROGS) "$(RELEASE_PATH)/erts-$(VSN)/bin"
 endif
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/run_erl_common.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/run_erl_common.c
--- otp_src_18.3.4.5/erts/etc/common/run_erl_common.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/run_erl_common.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,696 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2014. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include <dirent.h>
-#include <errno.h>
-#include <fcntl.h>
-#include <stdarg.h>
-#include <stdio.h>
-#include <stdlib.h>
-#include <string.h>
-#include <sys/stat.h>
-#include <sys/types.h>
-#include <time.h>
-#include <unistd.h>
-
-#ifdef __ANDROID__
-#  include <termios.h>
-#endif
-
-#ifdef HAVE_SYSLOG_H
-#  include <syslog.h>
-#endif
-
-#ifdef HAVE_SYS_IOCTL_H
-#  include <sys/ioctl.h>
-#endif
-
-#ifdef __OSE__
-#  include "ramlog.h"
-#endif
-
-#include "run_erl_common.h"
-#include "safe_string.h"
-
-#define DEFAULT_LOG_GENERATIONS 5
-#define LOG_MAX_GENERATIONS     1000      /* No more than 1000 log files */
-#define LOG_MIN_GENERATIONS     2         /* At least two to switch between */
-#define DEFAULT_LOG_MAXSIZE     100000
-#define LOG_MIN_MAXSIZE         1000      /* Smallast value for changing log file */
-#define LOG_STUBNAME            "erlang.log."
-#define LOG_PERM                0664
-#define DEFAULT_LOG_ACTIVITY_MINUTES    5
-#define DEFAULT_LOG_ALIVE_MINUTES       15
-#define DEFAULT_LOG_ALIVE_FORMAT        "%a %b %e %T %Z %Y"
-#define ALIVE_BUFFSIZ                   1024
-
-#define STATUSFILENAME  "/run_erl.log"
-
-#define PIPE_STUBNAME   "erlang.pipe"
-#define PIPE_STUBLEN    strlen(PIPE_STUBNAME)
-#define PERM            (S_IWUSR | S_IRUSR | S_IWOTH | S_IROTH | S_IWGRP | S_IRGRP)
-
-/* OSE has defined O_SYNC but it is not recognized by open */
-#if !defined(O_SYNC) || defined(__OSE__)
-#undef O_SYNC
-#define O_SYNC 0
-#define USE_FSYNC 1
-#endif
-
-/* Global variable definitions
- * We need this complex way of handling global variables because of how
- * OSE works here. We want to make it possible to run the shell command
- * run_erl multiple times with different global variables without them
- * effecting eachother.
- */
-
-#define STATUSFILE           (RE_DATA->statusfile)
-#define LOG_DIR              (RE_DATA->log_dir)
-#define STDSTATUS            (RE_DATA->stdstatus)
-#define LOG_GENERATIONS      (RE_DATA->log_generations)
-#define LOG_MAXSIZE          (RE_DATA->log_maxsize)
-#define LOG_ACTIVITY_MINUTES (RE_DATA->log_activity_minutes)
-#define LOG_ALIVE_IN_GMT     (RE_DATA->log_alive_in_gmt)
-#define LOG_ALIVE_FORMAT     (RE_DATA->log_alive_format)
-#define RUN_DAEMON           (RE_DATA->run_daemon)
-#define LOG_ALIVE_MINUTES    (RE_DATA->log_alive_minutes)
-#define LOG_NUM              (RE_DATA->log_num)
-#define LFD                  (RE_DATA->lfd)
-#define PROTOCOL_VER         (RE_DATA->protocol_ver)
-
-struct run_erl_ {
-  /* constant config data */
-  char statusfile[FILENAME_BUFSIZ];
-  char log_dir[FILENAME_BUFSIZ];
-  FILE *stdstatus;
-  int log_generations;
-  int log_maxsize;
-  int log_activity_minutes;
-  int log_alive_in_gmt;
-  char log_alive_format[ALIVE_BUFFSIZ+1];
-  int run_daemon;
-  int log_alive_minutes;
-  /* Current log number and log fd */
-  int log_num;
-  int lfd;
-  unsigned protocol_ver;
-};
-
-typedef struct run_erl_ run_erl;
-
-#ifdef __OSE__
-static OSPPDKEY run_erl_pp_key;
-#define RE_DATA (*(run_erl**)ose_get_ppdata(run_erl_pp_key))
-#else
-static run_erl re;
-#define RE_DATA (&re)
-#endif
-
-/* prototypes */
-
-static int next_log(int log_num);
-static int prev_log(int log_num);
-static int find_next_log_num(void);
-static int open_log(int log_num, int flags);
-
-/*
- * getenv_int:
- */
-static char *getenv_int(const char *name) {
-#ifdef __OSE__
-   return get_env(get_bid(current_process()),name);
-#else
-   return getenv(name);
-#endif
-}
-
-/*
- * next_log:
- * Returns the index number that follows the given index number.
- * (Wrapping after log_generations)
- */
-static int next_log(int log_num) {
-  return log_num>=LOG_GENERATIONS?1:log_num+1;
-}
-
-/*
- * prev_log:
- * Returns the index number that precedes the given index number.
- * (Wrapping after log_generations)
- */
-static int prev_log(int log_num) {
-  return log_num<=1?LOG_GENERATIONS:log_num-1;
-}
-
-/*
- * find_next_log_num()
- * Searches through the log directory to check which logs that already
- * exist. It finds the "hole" in the sequence, and returns the index
- * number for the last log in the log sequence. If there is no hole, index
- * 1 is returned.
- */
-static int find_next_log_num(void) {
-  int i, next_gen, log_gen;
-  DIR *dirp;
-  struct dirent *direntp;
-  int log_exists[LOG_MAX_GENERATIONS+1];
-  int stub_len = strlen(LOG_STUBNAME);
-
-  /* Initialize exiting log table */
-
-  for(i=LOG_GENERATIONS; i>=0; i--)
-    log_exists[i] = 0;
-  dirp = opendir(LOG_DIR);
-  if(!dirp) {
-    ERRNO_ERR1(LOG_ERR,"Can't access log directory '%s'", LOG_DIR);
-    exit(1);
-  }
-
-  /* Check the directory for existing logs */
-
-  while((direntp=readdir(dirp)) != NULL) {
-    if(strncmp(direntp->d_name,LOG_STUBNAME,stub_len)==0) {
-      int num = atoi(direntp->d_name+stub_len);
-      if(num < 1 || num > LOG_GENERATIONS)
-	continue;
-      log_exists[num] = 1;
-    }
-  }
-  closedir(dirp);
-
-  /* Find out the next available log file number */
-
-  next_gen = 0;
-  for(i=LOG_GENERATIONS; i>=0; i--) {
-    if(log_exists[i])
-      if(next_gen)
-	break;
-      else
-	;
-    else
-      next_gen = i;
-  }
-
-  /* Find out the current log file number */
-
-  if(next_gen)
-    log_gen = prev_log(next_gen);
-  else
-    log_gen = 1;
-
-  return log_gen;
-} /* find_next_log_num() */
-
-static int open_log(int log_num, int flags)
-{
-  char buf[FILENAME_MAX];
-  time_t now;
-  struct tm *tmptr;
-  char log_buffer[ALIVE_BUFFSIZ+1];
-
-  /* Remove the next log (to keep a "hole" in the log sequence) */
-  sn_printf(buf, sizeof(buf), "%s/%s%d",
-	    LOG_DIR, LOG_STUBNAME, next_log(log_num));
-  unlink(buf);
-
-  /* Create or continue on the current log file */
-  sn_printf(buf, sizeof(buf), "%s/%s%d", LOG_DIR, LOG_STUBNAME, log_num);
-
-  LFD = sf_open(buf, flags, LOG_PERM);
-
-  if(LFD <0){
-      ERRNO_ERR1(LOG_ERR,"Can't open log file '%s'.", buf);
-    exit(1);
-  }
-
-  /* Write a LOGGING STARTED and time stamp into the log file */
-  time(&now);
-  if (LOG_ALIVE_IN_GMT) {
-      tmptr = gmtime(&now);
-  } else {
-      tmptr = localtime(&now);
-  }
-  if (!strftime(log_buffer, ALIVE_BUFFSIZ, LOG_ALIVE_FORMAT,
-		tmptr)) {
-      strn_cpy(log_buffer, sizeof(log_buffer),
-	      "(could not format time in 256 positions "
-	      "with current format string.)");
-  }
-  log_buffer[ALIVE_BUFFSIZ] = '\0';
-
-  sn_printf(buf, sizeof(buf), "\n=====\n===== LOGGING STARTED %s\n=====\n",
-	    log_buffer);
-  if (erts_run_erl_write_all(LFD, buf, strlen(buf)) < 0)
-      erts_run_erl_log_status("Error in writing to log.\n");
-
-#if USE_FSYNC
-  fsync(LFD);
-#endif
-
-  return LFD;
-}
-
-/* Instead of making sure basename exists, we do our own */
-char *simple_basename(char *path)
-{
-    char *ptr;
-    for (ptr = path; *ptr != '\0'; ++ptr) {
-	if (*ptr == '/') {
-	    path = ptr + 1;
-	}
-    }
-    return path;
-}
-
-ssize_t sf_read(int fd, void *buffer, size_t len) {
-    ssize_t n = 0;
-
-    do { n = read(fd, buffer, len); } while (n < 0 && errno == EINTR);
-
-    return n;
-}
-
-ssize_t sf_write(int fd, const void *buffer, size_t len) {
-    ssize_t n = 0;
-
-    do { n = write(fd, buffer, len); } while (n < 0 && errno == EINTR);
-
-    return n;
-}
-
-int sf_open(const char *path, int type, mode_t mode) {
-    int fd = 0;
-
-    do { fd = open(path, type, mode); } while(fd < 0 && errno == EINTR);
-
-    return fd;
-}
-
-int sf_close(int fd) {
-    int res = 0;
-
-    do { res = close(fd); } while(res < 0 && errno == EINTR);
-
-    return res;
-}
-
-/* Call write() until entire buffer has been written or error.
- * Return len or -1.
- */
-int erts_run_erl_write_all(int fd, const char* buf, int len)
-{
-    int left = len;
-    int written;
-    for (;;) {
-        do {
-	  written = write(fd,buf,left);
-	} while (written < 0 && errno == EINTR);
-	if (written == left) {
-	    return len;
-	}
-	if (written < 0) {
-	    return -1;
-	}
-	left -= written;
-	buf += written;
-    }
-    return written;
-}
-
-/* erts_run_erl_log_status()
- * Prints the arguments to a status file
- * Works like printf (see vfrpintf)
- */
-void erts_run_erl_log_status(const char *format,...)
-{
-  va_list args;
-  time_t now;
-
-  if (STDSTATUS == NULL)
-    STDSTATUS = fopen(STATUSFILE, "w");
-  if (STDSTATUS == NULL)
-    return;
-  now = time(NULL);
-  fprintf(STDSTATUS, "run_erl [%d] %s",
-#ifdef __OSE__
-	  (int)current_process(),
-#else
-	  (int)getpid(),
-#endif
-	  ctime(&now));
-  va_start(args, format);
-  vfprintf(STDSTATUS, format, args);
-  va_end(args);
-  fflush(STDSTATUS);
-  return;
-}
-
-/* Fetch the current log alive minutes */
-int erts_run_erl_log_alive_minutes() {
-  return LOG_ALIVE_MINUTES;
-}
-
-/* error_logf()
- * Prints the arguments to stderr or syslog
- * Works like printf (see vfprintf)
- */
-void erts_run_erl_log_error(int priority, int line, const char *format, ...)
-{
-    va_list args;
-    va_start(args, format);
-
-#ifdef HAVE_SYSLOG_H
-    if (RUN_DAEMON) {
-	vsyslog(priority,format,args);
-    }
-    else
-#endif
-#ifdef __OSE__
-    if (RUN_DAEMON) {
-      char *buff = malloc(sizeof(char)*1024);
-      vsnprintf(buff,1024,format, args);
-      ramlog_printf(buff);
-    }
-    else
-#endif
-    {
-	time_t now = time(NULL);
-	fprintf(stderr, "run_erl:%d [%d] %s", line,
-#ifdef __OSE__
-		(int)current_process(),
-#else
-		(int)getpid(),
-#endif
-		ctime(&now));
-	vfprintf(stderr, format, args);
-    }
-    va_end(args);
-}
-
-/* erts_run_erl_log_write()
- * Writes a message to lfd. If the current log file is full,
- * a new log file is opened.
- */
-int erts_run_erl_log_write(char* buf, size_t len)
-{
-  int size;
-  ssize_t res;
-  /* Decide if new logfile needed, and open if so */
-
-  size = lseek(LFD,0,SEEK_END);
-  if(size+len > LOG_MAXSIZE) {
-    int res;
-    do {
-      res = close(LFD);
-    } while (res < 0 && errno == EINTR);
-    LOG_NUM = next_log(LOG_NUM);
-    LFD = open_log(LOG_NUM, O_RDWR|O_CREAT|O_TRUNC|O_SYNC);
-  }
-
-  /* Write to log file */
-
-  if ((res = erts_run_erl_write_all(LFD, buf, len)) < 0) {
-    erts_run_erl_log_status("Error in writing to log.\n");
-  }
-
-#if USE_FSYNC
-  fsync(LFD);
-#endif
-  return res;
-}
-
-int erts_run_erl_log_activity(int timeout,time_t now,time_t last_activity) {
-  char log_alive_buffer[ALIVE_BUFFSIZ+1];
-  char buf[BUFSIZ];
-
-  if (timeout || now - last_activity > LOG_ACTIVITY_MINUTES*60) {
-    /* Either a time out: 15 minutes without action, */
-    /* or something is coming in right now, but it's a long time */
-    /* since last time, so let's write a time stamp this message */
-    struct tm *tmptr;
-    if (LOG_ALIVE_IN_GMT) {
-      tmptr = gmtime(&now);
-    } else {
-      tmptr = localtime(&now);
-    }
-    if (!strftime(log_alive_buffer, ALIVE_BUFFSIZ, LOG_ALIVE_FORMAT,
-		  tmptr)) {
-      strn_cpy(log_alive_buffer, sizeof(log_alive_buffer),
-	       "(could not format time in 256 positions "
-	       "with current format string.)");
-    }
-    log_alive_buffer[ALIVE_BUFFSIZ] = '\0';
-
-    sn_printf(buf, sizeof(buf), "\n===== %s%s\n",
-	      timeout?"ALIVE ":"", log_alive_buffer);
-    return erts_run_erl_log_write(buf, strlen(buf));
-  }
-  return 0;
-}
-
-int erts_run_erl_log_open() {
-
-  LOG_NUM = find_next_log_num();
-  LFD = open_log(LOG_NUM, O_RDWR|O_APPEND|O_CREAT|O_SYNC);
-  return 0;
-}
-
-int erts_run_erl_log_init(int daemon, char* logdir) {
-  char *p;
-
-#ifdef __OSE__
-  run_erl **re_pp;
-  if (!run_erl_pp_key)
-     ose_create_ppdata("run_erl_ppdata",&run_erl_pp_key);
-  re_pp = (run_erl **)ose_get_ppdata(run_erl_pp_key);
-  *re_pp = malloc(sizeof(run_erl));
-#endif
-
-  STDSTATUS = NULL;
-  LOG_GENERATIONS = DEFAULT_LOG_GENERATIONS;
-  LOG_MAXSIZE     = DEFAULT_LOG_MAXSIZE;
-  LOG_ACTIVITY_MINUTES = DEFAULT_LOG_ACTIVITY_MINUTES;
-  LOG_ALIVE_IN_GMT = 0;
-  RUN_DAEMON = 0;
-  LOG_ALIVE_MINUTES = DEFAULT_LOG_ALIVE_MINUTES;
-  LFD = 0;
-  PROTOCOL_VER = RUN_ERL_LO_VER; /* assume lowest to begin with */
-
-  /* Get values for LOG file handling from the environment */
-  if ((p = getenv_int("RUN_ERL_LOG_ALIVE_MINUTES"))) {
-      LOG_ALIVE_MINUTES = atoi(p);
-      if (!LOG_ALIVE_MINUTES) {
-	  ERROR1(LOG_ERR,"Minimum value for RUN_ERL_LOG_ALIVE_MINUTES is 1 "
-		 "(current value is %s)",p);
-      }
-      LOG_ACTIVITY_MINUTES = LOG_ALIVE_MINUTES / 3;
-      if (!LOG_ACTIVITY_MINUTES) {
-	  ++LOG_ACTIVITY_MINUTES;
-      }
-  }
-  if ((p = getenv_int(
-		   "RUN_ERL_LOG_ACTIVITY_MINUTES"))) {
-     LOG_ACTIVITY_MINUTES = atoi(p);
-      if (!LOG_ACTIVITY_MINUTES) {
-	  ERROR1(LOG_ERR,"Minimum value for RUN_ERL_LOG_ACTIVITY_MINUTES is 1 "
-		 "(current value is %s)",p);
-      }
-  }
-  if ((p = getenv_int("RUN_ERL_LOG_ALIVE_FORMAT"))) {
-      if (strlen(p) > ALIVE_BUFFSIZ) {
-	  ERROR1(LOG_ERR, "RUN_ERL_LOG_ALIVE_FORMAT can contain a maximum of "
-		 "%d characters", ALIVE_BUFFSIZ);
-      }
-      strn_cpy(LOG_ALIVE_FORMAT, sizeof(LOG_ALIVE_FORMAT), p);
-  } else {
-      strn_cpy(LOG_ALIVE_FORMAT, sizeof(LOG_ALIVE_FORMAT),
-	       DEFAULT_LOG_ALIVE_FORMAT);
-  }
-  if ((p = getenv_int("RUN_ERL_LOG_ALIVE_IN_UTC"))
-      && strcmp(p,"0")) {
-      ++LOG_ALIVE_IN_GMT;
-  }
-  if ((p = getenv_int("RUN_ERL_LOG_GENERATIONS"))) {
-    LOG_GENERATIONS = atoi(p);
-    if (LOG_GENERATIONS < LOG_MIN_GENERATIONS)
-      ERROR1(LOG_ERR,"Minimum RUN_ERL_LOG_GENERATIONS is %d",
-	     LOG_MIN_GENERATIONS);
-    if (LOG_GENERATIONS > LOG_MAX_GENERATIONS)
-      ERROR1(LOG_ERR,"Maximum RUN_ERL_LOG_GENERATIONS is %d",
-	     LOG_MAX_GENERATIONS);
-  }
-
-  if ((p = getenv_int("RUN_ERL_LOG_MAXSIZE"))) {
-    LOG_MAXSIZE = atoi(p);
-    if (LOG_MAXSIZE < LOG_MIN_MAXSIZE)
-      ERROR1(LOG_ERR,"Minimum RUN_ERL_LOG_MAXSIZE is %d", LOG_MIN_MAXSIZE);
-  }
-
-  RUN_DAEMON = daemon;
-
-  strn_cpy(LOG_DIR, sizeof(LOG_DIR), logdir);
-  strn_cpy(STATUSFILE, sizeof(STATUSFILE), LOG_DIR);
-  strn_cat(STATUSFILE, sizeof(STATUSFILE), STATUSFILENAME);
-
-  return 0;
-}
-
-/* create_fifo()
- * Creates a new fifo with the given name and permission.
- */
-static int create_fifo(char *name, int perm)
-{
-  if ((mkfifo(name, perm) < 0) && (errno != EEXIST))
-    return -1;
-  return 0;
-}
-
-/*
- * w- and r_pipename have to be pre-allocated of atleast FILENAME_MAX size
- */
-int erts_run_erl_open_fifo(char *pipename,char *w_pipename,char *r_pipename) {
-  int calculated_pipename = 0;
-  int highest_pipe_num = 0;
-  int fd;
-
-  /*
-   * Create FIFOs and open them
-   */
-
-  if(*pipename && pipename[strlen(pipename)-1] == '/') {
-    /* The user wishes us to find a unique pipe name in the specified */
-    /* directory */
-    DIR *dirp;
-    struct dirent *direntp;
-
-    calculated_pipename = 1;
-    dirp = opendir(pipename);
-    if(!dirp) {
-      ERRNO_ERR1(LOG_ERR,"Can't access pipe directory '%s'.", pipename);
-      return 1;
-    }
-
-    /* Check the directory for existing pipes */
-
-    while((direntp=readdir(dirp)) != NULL) {
-      if(strncmp(direntp->d_name,PIPE_STUBNAME,PIPE_STUBLEN)==0) {
-	int num = atoi(direntp->d_name+PIPE_STUBLEN+1);
-	if(num > highest_pipe_num)
-	  highest_pipe_num = num;
-      }
-    }
-    closedir(dirp);
-    strn_catf(pipename, BUFSIZ, "%s.%d",
-	      PIPE_STUBNAME, highest_pipe_num+1);
-  } /* if */
-
-  for(;;) {
-      /* write FIFO - is read FIFO for `to_erl' program */
-      strn_cpy(w_pipename, BUFSIZ, pipename);
-      strn_cat(w_pipename, BUFSIZ, ".r");
-      if (create_fifo(w_pipename, PERM) < 0) {
-	  ERRNO_ERR1(LOG_ERR,"Cannot create FIFO %s for writing.",
-		     w_pipename);
-	  return 1;
-      }
-
-      /* read FIFO - is write FIFO for `to_erl' program */
-      strn_cpy(r_pipename, BUFSIZ, pipename);
-      strn_cat(r_pipename, BUFSIZ, ".w");
-
-      /* Check that nobody is running run_erl already */
-      if ((fd = sf_open(r_pipename, O_WRONLY|DONT_BLOCK_PLEASE, 0)) >= 0) {
-	  /* Open as client succeeded -- run_erl is already running! */
-	  sf_close(fd);
-	  if (calculated_pipename) {
-	      ++highest_pipe_num;
-	      strn_catf(pipename, BUFSIZ, "%s.%d",
-			PIPE_STUBNAME, highest_pipe_num+1);
-	      continue;
-	  }
-	  ERROR1(LOG_ERR, "Erlang already running on pipe %s.\n", pipename);
-	  unlink(w_pipename);
-	  return 1;
-      }
-      if (create_fifo(r_pipename, PERM) < 0) {
-	  unlink(w_pipename);
-	  ERRNO_ERR1(LOG_ERR,"Cannot create FIFO %s for reading.",
-		     r_pipename);
-	  return 1;
-      }
-      break;
-  }
-  return 0;
-}
-
-/* Extract any control sequences that are ment only for run_erl
- * and should not be forwarded to the pty.
- */
-int erts_run_erl_extract_ctrl_seq(char* buf, int len, int mfd)
-{
-    static const char prefix[] = "\033_";
-    static const char suffix[] = "\033\\";
-    char* bufend = buf + len;
-    char* start = buf;
-    char* command;
-    char* end;
-
-    for (;;) {
-	start = find_str(start, bufend-start, prefix);
-	if (!start) break;
-
-	command = start + strlen(prefix);
-	end = find_str(command, bufend-command, suffix);
-	if (end) {
-	    unsigned col, row;
-	    if (sscanf(command,"version=%u", &PROTOCOL_VER)==1) {
-		/*fprintf(stderr,"to_erl v%u\n", protocol_ver);*/
-	    }
-	    else if (sscanf(command,"winsize=%u,%u", &col, &row)==2) {
-#ifdef TIOCSWINSZ
-	      struct winsize ws;
-	      ws.ws_col = col;
-	      ws.ws_row = row;
-	      if (ioctl(mfd, TIOCSWINSZ, &ws) < 0) {
-		ERRNO_ERR0(LOG_ERR,"Failed to set window size");
-	      }
-#endif
-	    }
-	    else {
-		ERROR2(LOG_ERR, "Ignoring unknown ctrl command '%.*s'\n",
-		       (int)(end-command), command);
-	    }
-
-	    /* Remove ctrl sequence from buf */
-	    end += strlen(suffix);
-	    memmove(start, end, bufend-end);
-	    bufend -= end - start;
-	}
-	else {
-	    ERROR2(LOG_ERR, "Missing suffix in ctrl sequence '%.*s'\n",
-		   (int)(bufend-start), start);
-	    break;
-	}
-    }
-    return bufend - buf;
-}
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/run_erl_common.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/run_erl_common.h
--- otp_src_18.3.4.5/erts/etc/common/run_erl_common.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/run_erl_common.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,97 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Functions that are common to both OSE and unix implementations of run_erl
- */
-#ifndef ERL_RUN_ERL_LOG_H
-#define ERL_RUN_ERL_LOG_H
-
-#include <stdio.h>
-#include <time.h>
-#include <unistd.h>
-
-#include "run_erl_vsn.h"
-
-/* Log handling */
-int erts_run_erl_log_init(int run_daemon, char* logdir);
-int erts_run_erl_log_open(void);
-int erts_run_erl_log_close(void);
-int erts_run_erl_log_write(char *buff, size_t len);
-int erts_run_erl_log_activity(int timeout, time_t now, time_t last_activity);
-
-void erts_run_erl_log_status(const char *format,...);
-void erts_run_erl_log_error(int priority, int line, const char *format,...);
-
-int erts_run_erl_open_fifo(char *pipename,char *w_pipename,char *r_pipename);
-int erts_run_erl_log_alive_minutes(void);
-int erts_run_erl_extract_ctrl_seq(char* buf, int len, int mfd);
-
-/* File operations */
-ssize_t sf_read(int fd, void *buffer, size_t len);
-ssize_t sf_write(int fd, const void *buffer, size_t len);
-int sf_open(const char *path, int type, mode_t mode);
-int sf_close(int fd);
-int erts_run_erl_write_all(int fd, const char* buf, int len);
-char *simple_basename(char *path);
-
-#ifndef LOG_ERR
-#ifdef __OSE__
-#define LOG_ERR 0
-#else
-#define LOG_ERR NULL
-#endif
-#endif
-
-#define ERROR0(Prio,Format) erts_run_erl_log_error(Prio,__LINE__,Format"\n")
-#define ERROR1(Prio,Format,A1) erts_run_erl_log_error(Prio,__LINE__,Format"\n",A1)
-#define ERROR2(Prio,Format,A1,A2) erts_run_erl_log_error(Prio,__LINE__,Format"\n",A1,A2)
-
-#ifdef HAVE_STRERROR
-#    define ADD_ERRNO(Format) "errno=%d '%s'\n"Format"\n",errno,strerror(errno)
-#else
-#    define ADD_ERRNO(Format) "errno=%d\n"Format"\n",errno
-#endif
-#define ERRNO_ERR0(Prio,Format) erts_run_erl_log_error(Prio,__LINE__,ADD_ERRNO(Format))
-#define ERRNO_ERR1(Prio,Format,A1) erts_run_erl_log_error(Prio,__LINE__,ADD_ERRNO(Format),A1)
-#define ERRNO_ERR2(Prio,Format,A1,A2) erts_run_erl_log_error(Prio,__LINE__,ADD_ERRNO(Format),A1,A2)
-
-#define RUN_ERL_USAGE \
-  "%s (pipe_name|pipe_dir/) log_dir \"command [parameters ...]\"" \
-  "\n\nDESCRIPTION:\n"							\
-  "You may also set the environment variables RUN_ERL_LOG_GENERATIONS\n" \
-  "and RUN_ERL_LOG_MAXSIZE to the number of log files to use and the\n"	\
-  "size of the log file when to switch to the next log file\n"
-
-#ifndef FILENAME_MAX
-#define FILENAME_MAX 250
-#endif
-
-#define FILENAME_BUFSIZ FILENAME_MAX
-
-#ifdef O_NONBLOCK
-#  define DONT_BLOCK_PLEASE O_NONBLOCK
-#else
-#  define DONT_BLOCK_PLEASE O_NDELAY
-#  ifndef EAGAIN
-#    define EAGAIN -3898734
-#  endif
-#endif
-
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/run_erl_vsn.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/run_erl_vsn.h
--- otp_src_18.3.4.5/erts/etc/common/run_erl_vsn.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/run_erl_vsn.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,30 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2008-2009. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-/*
- * The protocol version number used between to_erl and run_erl.
- */
-#define RUN_ERL_HI_VER 1  /* My preferred protocol version */
-#define RUN_ERL_LO_VER 0  /* The lowest version I accept to talk with */
-
-/* Version history:
- * 0: Older, without version handshake
- * 1: R12B-3, version handshake + window size ctrl
- */
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/safe_string.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/safe_string.c
--- otp_src_18.3.4.5/erts/etc/common/safe_string.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/safe_string.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,123 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2008-2009. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Module: safe_string.c
- *
- * This is a bunch of generic string operation
- * that are safe regarding buffer overflow.
- *
- * All string functions terminate the process with an error message
- * on buffer overflow.
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-#include "safe_string.h"
-#include <stdio.h>
-#include <string.h>
-#include <stdarg.h>
-#include <stdlib.h>
-
-
-static void string_overflow_handler(const char* format, ...)
-{
-    va_list args;
-    va_start(args, format);
-    vfprintf(stderr,format,args);
-    va_end(args);
-    exit(1);
-}
-
-int vsn_printf(char* dst, size_t size, const char* format, va_list args)
-{
-    int ret = vsnprintf(dst, size, format, args);
-    if (ret >= size || ret < 0) {
-	string_overflow_handler("Buffer truncated '%s'\n",dst);
-    }
-    return ret;
-}
-
-int sn_printf(char* dst, size_t size, const char* format, ...)
-{
-    va_list args;
-    int ret;
-    va_start(args, format);
-    ret = vsn_printf(dst,size,format,args);
-    va_end(args);
-    return ret;
-}
-
-int strn_cpy(char* dst, size_t size, const char* src)
-{
-    return sn_printf(dst,size,"%s",src);
-}
-
-int strn_cat(char* dst, size_t size, const char* src)
-{
-    return strn_catf(dst,size,"%s",src);
-}
-
-int strn_catf(char* dst, size_t size, const char* format, ...)
-{
-    int ret;
-    va_list args;
-#ifdef _GNU_SOURCE
-    int len = strnlen(dst,size);
-#else
-    int len = strlen(dst);
-#endif
-
-    if (len >= size) {
-	string_overflow_handler("Buffer already overflowed '%.*s'\n",
-				size, dst);
-    }
-    va_start(args, format);
-    ret = vsn_printf(dst+len, size-len, format, args);
-    va_end(args);
-    return len+ret;
-}
-
-char* find_str(const char* haystack, int hsize, const char* needle)
-{
-    int i = 0;
-    int nsize = strlen(needle);
-    hsize -= nsize - 1;
-    for (i=0; i<hsize; i++) {
-	if (haystack[i]==needle[0] && strncmp(haystack+i,needle,nsize)==0) {
-	    return (char*)(haystack+i);
-	}
-    }
-    return NULL;
-}
-
-#ifndef HAVE_MEMMOVE
-void* memmove(void *dest, const void *src, size_t n)
-{
-    int i;
-    if (src > dest) {
-	for (i=0; i<n; i++) ((char*)dest)[i] = ((char*)src)[i];
-    }
-    else {
-	for (i=(int)(n-1); i>=0; i--) ((char*)dest)[i] = ((char*)src)[i];
-    }
-    return dest;
-}
-#endif /* HAVE_MEMMOVE */
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/safe_string.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/safe_string.h
--- otp_src_18.3.4.5/erts/etc/common/safe_string.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/safe_string.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,65 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2008-2009. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Module: safe_string.h
- *
- * This is an interface to a bunch of generic string operation
- * that are safe regarding buffer overflow.
- *
- * All string functions terminate the process with an error message
- * on buffer overflow.
- */
-
-#include <stdio.h>
-#include <stdarg.h>
-
-/* Like vsnprintf()
- */
-int vsn_printf(char* dst, size_t size, const char* format, va_list args);
-
-/* Like snprintf()
- */
-int sn_printf(char* dst, size_t size, const char* format, ...);
-
-/* Like strncpy()
- * Returns length of copied string.
- */
-int strn_cpy(char* dst, size_t size, const char* src);
-
-/* Almost like strncat()
- * size is sizeof entire dst buffer.
- * Returns length of resulting string.
- */
-int strn_cat(char* dst, size_t size, const char* src);
-
-/* Combination of strncat() and snprintf()
- * size is sizeof entire dst buffer.
- * Returns length of resulting string.
- */
-int strn_catf(char* dst, size_t size, const char* format, ...);
-
-/* Simular to strstr() but search size bytes of haystack
- * without regard to '\0' characters.
- */
-char* find_str(const char* haystack, int size, const char* needle);
-
-#ifndef HAVE_MEMMOVE
-void* memmove(void *dest, const void *src, size_t n);
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/to_erl_common.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/to_erl_common.c
--- otp_src_18.3.4.5/erts/etc/common/to_erl_common.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/to_erl_common.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,717 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 1996-2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Module: to_erl.c
- *
- * This module implements a process that opens two specified FIFOs, one
- * for reading and one for writing; reads from its stdin, and writes what
- * it has read to the write FIF0; reads from the read FIFO, and writes to
- * its stdout.
- *
-  ________                            _________
- |        |--<-- pipe.r (fifo1) --<--|         |
- | to_erl |                          | run_erl | (parent)
- |________|-->-- pipe.w (fifo2) -->--|_________|
-                                          ^ master pty
-                                          |
-                                          | slave pty
-                                      ____V____
-                                     |         |
-                                     |  "erl"  | (child)
-                                     |_________|
- */
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include <sys/types.h>
-#include <sys/stat.h>
-#include <sys/time.h>
-#include <sys/types.h>
-#include <fcntl.h>
-#include <unistd.h>
-#include <stdio.h>
-#include <stdlib.h>
-#include <string.h>
-#include <dirent.h>
-#include <errno.h>
-
-#ifdef __OSE__
-#include <aio.h>
-#include "ose.h"
-#include "efs.h"
-#include "ose_spi/fm.sig"
-#else /* __UNIX__ */
-#include <termios.h>
-#include <signal.h>
-#endif
-
-#ifdef HAVE_SYS_IOCTL_H
-#  include <sys/ioctl.h>
-#endif
-
-#include "to_erl_common.h"
-#include "run_erl_vsn.h"
-#include "safe_string.h"   /* strn_cpy, strn_catf, sn_printf, etc. */
-
-#if defined(O_NONBLOCK)
-# define DONT_BLOCK_PLEASE O_NONBLOCK
-#else
-# define DONT_BLOCK_PLEASE O_NDELAY
-# if !defined(EAGAIN)
-#  define EAGAIN -3898734
-# endif
-#endif
-
-#ifdef HAVE_STRERROR
-#  define STRERROR(x) strerror(x)
-#else
-#  define STRERROR(x) ""
-#endif
-
-#define noDEBUG
-
-#ifdef __OSE__
-#define PIPE_DIR        "/pipe/"
-#else
-#define PIPE_DIR        "/tmp/"
-#endif
-#define PIPE_STUBNAME   "erlang.pipe"
-#define PIPE_STUBLEN    strlen(PIPE_STUBNAME)
-
-#ifdef DEBUG
-#define STATUS(s)  { fprintf(stderr, (s)); fflush(stderr); }
-#else
-#define STATUS(s)
-#endif
-
-#ifndef FILENAME_MAX
-#define FILENAME_MAX 250
-#endif
-
-static int tty_eof = 0;
-static int protocol_ver = RUN_ERL_LO_VER; /* assume lowest to begin with */
-
-static int write_all(int fd, const char* buf, int len);
-static int version_handshake(char* buf, int len, int wfd);
-
-
-#ifdef __OSE__
-
-#define SET_AIO(REQ,FD,SIZE,BUFF)					\
-  /* Make sure to clean data structure of previous request */		\
-  memset(&(REQ),0,sizeof(REQ));						\
-  (REQ).aio_fildes = FD;						\
-  (REQ).aio_offset = FM_POSITION_CURRENT;				\
-  (REQ).aio_nbytes = SIZE;						\
-  (REQ).aio_buf = BUFF;							\
-  (REQ).aio_sigevent.sigev_notify = SIGEV_NONE
-
-#define READ_AIO(REQ,FD,SIZE,BUFF)					\
-  SET_AIO(REQ,FD,SIZE,BUFF);						\
-  if (aio_read(&(REQ)) != 0)						\
-    fprintf(stderr,"aio_read of child_read_req(%d) failed"		\
-	    "with error %d\n",FD,errno)
-
-union SIGNAL {
-  SIGSELECT signo;
-  struct FmReadPtr fm_read_ptr;
-};
-
-#else /* __UNIX__ */
-static int recv_sig = 0;
-static struct termios tty_smode, tty_rmode;
-static int window_size_seq(char* buf, size_t bufsz);
-#ifdef DEBUG
-static void show_terminal_settings(struct termios *);
-#endif
-
-static void handle_ctrlc(int sig)
-{
-    /* Reinstall the handler, and signal break flag */
-    signal(SIGINT,handle_ctrlc);
-    recv_sig = SIGINT;
-}
-
-static void handle_sigwinch(int sig)
-{
-    recv_sig = SIGWINCH;
-}
-#endif
-
-static void usage(char *pname)
-{
-    fprintf(stderr, "Usage: ");
-    fprintf(stderr,TO_ERL_USAGE,pname);
-}
-
-int to_erl(int argc, char **argv)
-{
-    char  FIFO1[FILENAME_MAX], FIFO2[FILENAME_MAX];
-    int i, len, wfd, rfd;
-    char pipename[FILENAME_MAX];
-    int pipeIx = 1;
-    int force_lock = 0;
-    int got_some = 0;
-
-#ifdef __OSE__
-    struct aiocb stdin_read_req, pipe_read_req;
-    FmHandle stdin_fh, pipe_fh;
-    char *stdin_buf, *pipe_buf;
-    char *buf;
-    union SIGNAL *sig;
-#else /* __UNIX__ */
-    char buf[BUFSIZ];
-    fd_set readfds;
-#endif
-
-    if (argc >= 2 && argv[1][0]=='-') {
-	switch (argv[1][1]) {
-	case 'h':
-	    usage(argv[0]);
-	    exit(1);
-	case 'F':
-	    force_lock = 1;
-	    break;
-	default:
-	    fprintf(stderr,"Invalid option '%s'\n",argv[1]);
-	    exit(1);
-	}
-	pipeIx = 2;
-    }
-
-#ifdef DEBUG
-    fprintf(stderr, "%s: pid is : %d\n", argv[0],(int)
-#ifdef __OSE__
-	    current_process()
-#else /* __UNIX__ */
-	    getpid()
-#endif
-	    );
-#endif
-
-    strn_cpy(pipename, sizeof(pipename),
-	     (argv[pipeIx] ? argv[pipeIx] : PIPE_DIR));
-
-    if(*pipename && pipename[strlen(pipename)-1] == '/') {
-	/* The user wishes us to find a pipe name in the specified */
-	/* directory */
-	int highest_pipe_num = 0;
-	DIR *dirp;
-	struct dirent *direntp;
-
-	dirp = opendir(pipename);
-	if(!dirp) {
-	    fprintf(stderr, "Can't access pipe directory %s: %s\n", pipename, strerror(errno));
-	    exit(1);
-	}
-
-	/* Check the directory for existing pipes */
-
-	while((direntp=readdir(dirp)) != NULL) {
-	    if(strncmp(direntp->d_name,PIPE_STUBNAME,PIPE_STUBLEN)==0) {
-		int num = atoi(direntp->d_name+PIPE_STUBLEN+1);
-		if(num > highest_pipe_num)
-		    highest_pipe_num = num;
-	    }
-	}
-	closedir(dirp);
-	strn_catf(pipename, sizeof(pipename), (highest_pipe_num?"%s.%d":"%s"),
-		  PIPE_STUBNAME, highest_pipe_num);
-    } /* if */
-
-    /* read FIFO */
-    sn_printf(FIFO1,sizeof(FIFO1),"%s.r",pipename);
-    /* write FIFO */
-    sn_printf(FIFO2,sizeof(FIFO2),"%s.w",pipename);
-
-#ifndef __OSE__
-    /* Check that nobody is running to_erl on this pipe already */
-    if ((wfd = open (FIFO1, O_WRONLY|DONT_BLOCK_PLEASE, 0)) >= 0) {
-	/* Open as server succeeded -- to_erl is already running! */
-	close(wfd);
-	fprintf(stderr, "Another to_erl process already attached to pipe "
-			"%s.\n", pipename);
-	if (force_lock) {
-	    fprintf(stderr, "But we proceed anyway by force (-F).\n");
-	}
-	else {
-	    exit(1);
-	}
-    }
-#endif
-
-    if ((rfd = open (FIFO1, O_RDONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
-#ifdef DEBUG
-	fprintf(stderr, "Could not open FIFO %s for reading.\n", FIFO1);
-#endif
-	fprintf(stderr, "No running Erlang on pipe %s: %s\n", pipename, strerror(errno));
-	exit(1);
-    }
-#ifdef DEBUG
-    fprintf(stderr, "to_erl: %s opened for reading\n", FIFO1);
-#endif
-
-    if ((wfd = open (FIFO2, O_WRONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
-#ifdef DEBUG
-	fprintf(stderr, "Could not open FIFO %s for writing.\n", FIFO2);
-#endif
-	fprintf(stderr, "No running Erlang on pipe %s: %s\n", pipename, strerror(errno));
-	close(rfd);
-	exit(1);
-    }
-#ifdef DEBUG
-    fprintf(stderr, "to_erl: %s opened for writing\n", FIFO2);
-#endif
-
-#ifndef __OSE__
-    fprintf(stderr, "Attaching to %s (^D to exit)\n\n", pipename);
-#else
-    fprintf(stderr, "Attaching to %s (^C to exit)\n\n", pipename);
-#endif
-
-#ifndef __OSE__
-    /* Set break handler to our handler */
-    signal(SIGINT,handle_ctrlc);
-
-    /*
-     * Save the current state of the terminal, and set raw mode.
-     */
-    if (tcgetattr(0, &tty_rmode) , 0) {
-	fprintf(stderr, "Cannot get terminals current mode\n");
-	exit(-1);
-    }
-    tty_smode = tty_rmode;
-    tty_eof = '\004'; /* Ctrl+D to exit */
-#ifdef DEBUG
-    show_terminal_settings(&tty_rmode);
-#endif
-    tty_smode.c_iflag =
-	1*BRKINT |/*Signal interrupt on break.*/
-	    1*IGNPAR |/*Ignore characters with parity errors.*/
-		1*ISTRIP |/*Strip character.*/
-		    0;
-
-#if 0
-0*IGNBRK |/*Ignore break condition.*/
-0*PARMRK |/*Mark parity errors.*/
-0*INPCK  |/*Enable input parity check.*/
-0*INLCR  |/*Map NL to CR on input.*/
-0*IGNCR  |/*Ignore CR.*/
-0*ICRNL  |/*Map CR to NL on input.*/
-0*IUCLC  |/*Map upper-case to lower-case on input.*/
-0*IXON   |/*Enable start/stop output control.*/
-0*IXANY  |/*Enable any character to restart output.*/
-0*IXOFF  |/*Enable start/stop input control.*/
-0*IMAXBEL|/*Echo BEL on input line too long.*/
-#endif
-
-    tty_smode.c_oflag =
-	1*OPOST  |/*Post-process output.*/
-	    1*ONLCR  |/*Map NL to CR-NL on output.*/
-#ifdef XTABS
-		1*XTABS  |/*Expand tabs to spaces. (Linux)*/
-#endif
-#ifdef OXTABS
-		    1*OXTABS  |/*Expand tabs to spaces. (FreeBSD)*/
-#endif
-#ifdef NL0
-			1*NL0    |/*Select newline delays*/
-#endif
-#ifdef CR0
-			    1*CR0    |/*Select carriage-return delays*/
-#endif
-#ifdef TAB0
-				1*TAB0   |/*Select horizontal tab delays*/
-#endif
-#ifdef BS0
-				    1*BS0    |/*Select backspace delays*/
-#endif
-#ifdef VT0
-					1*VT0    |/*Select vertical tab delays*/
-#endif
-#ifdef FF0
-					    1*FF0    |/*Select form feed delays*/
-#endif
-											    0;
-
-#if 0
-0*OLCUC  |/*Map lower case to upper on output.*/
-0*OCRNL  |/*Map CR to NL on output.*/
-0*ONOCR  |/*No CR output at column 0.*/
-0*ONLRET |/*NL performs CR function.*/
-0*OFILL  |/*Use fill characters for delay.*/
-0*OFDEL  |/*Fill is DEL, else NULL.*/
-0*NL1    |
-0*CR1    |
-0*CR2    |
-0*CR3    |
-0*TAB1   |
-0*TAB2   |
-0*TAB3   |/*Expand tabs to spaces.*/
-0*BS1    |
-0*VT1    |
-0*FF1    |
-#endif
-
-    /* JALI: removed setting the tty_smode.c_cflag flags, since this is not */
-    /* advisable if this is a *real* terminal, such as the console. In fact */
-    /* this may hang the entire machine, deep, deep down (signalling break */
-    /* or toggling the abort switch doesn't help) */
-
-    tty_smode.c_lflag =
-									0;
-
-#if 0
-0*ISIG   |/*Enable signals.*/
-0*ICANON |/*Canonical input (erase and kill processing).*/
-0*XCASE  |/*Canonical upper/lower presentation.*/
-0*ECHO   |/*Enable echo.*/
-0*ECHOE  |/*Echo erase character as BS-SP-BS.*/
-0*ECHOK  |/*Echo NL after kill character.*/
-0*ECHONL |/*Echo NL.*/
-0*NOFLSH |/*Disable flush after interrupt or quit.*/
-0*TOSTOP |/*Send SIGTTOU for background output.*/
-0*ECHOCTL|/*Echo control characters as ^char, delete as ^?.*/
-0*ECHOPRT|/*Echo erase character as character erased.*/
-0*ECHOKE |/*BS-SP-BS erase entire line on line kill.*/
-0*FLUSHO |/*Output is being flushed.*/
-0*PENDIN |/*Retype pending input at next read or input character.*/
-0*IEXTEN |/*Enable extended (implementation-defined) functions.*/
-#endif
-
-    tty_smode.c_cc[VMIN]      =0;/* Note that VMIN is the same as VEOF! */
-    tty_smode.c_cc[VTIME]     =0;/* Note that VTIME is the same as VEOL! */
-    tty_smode.c_cc[VINTR]     =3;
-
-    tcsetattr(0, TCSADRAIN, &tty_smode);
-
-#ifdef DEBUG
-    show_terminal_settings(&tty_smode);
-#endif
-
-#endif /* !__OSE__ */
-    /*
-     * 	 "Write a ^L to the FIFO which causes the other end to redisplay
-     *    the input line."
-     * This does not seem to work as was intended in old comment above.
-     * However, this control character is now (R12B-3) used by run_erl
-     * to trigger the version handshaking between to_erl and run_erl
-     * at the start of every new to_erl-session.
-     */
-
-    if (write(wfd, "\014", 1) < 0) {
-	fprintf(stderr, "Error in writing ^L to FIFO.\n");
-    }
-
-#ifdef __OSE__
-    /* we have a tiny stack so we malloc the buffers */
-    stdin_buf = malloc(sizeof(char) * BUFSIZ);
-    pipe_buf = malloc(sizeof(char) * BUFSIZ);
-
-    efs_examine_fd(rfd,FLIB_FD_HANDLE,&pipe_fh);
-    efs_examine_fd(0,FLIB_FD_HANDLE,&stdin_fh);
-    READ_AIO(stdin_read_req,0,BUFSIZ,stdin_buf);
-    READ_AIO(pipe_read_req,rfd,BUFSIZ,pipe_buf);
-#endif
-
-    /*
-     * read and write
-     */
-    while (1) {
-#ifndef __OSE__
-	FD_ZERO(&readfds);
-	FD_SET(0, &readfds);
-	FD_SET(rfd, &readfds);
-	if (select(rfd + 1, &readfds, NULL, NULL, NULL) < 0) {
-	    if (recv_sig) {
-		FD_ZERO(&readfds);
-	    }
-	    else {
-		fprintf(stderr, "Error in select.\n");
-		break;
-	    }
-	}
-	len = 0;
-
-	/*
-	 * Read from terminal and write to FIFO
-         */
-	if (recv_sig) {
-	    switch (recv_sig) {
-	    case SIGINT:
-		fprintf(stderr, "[Break]\n\r");
-		buf[0] = '\003';
-		len = 1;
-		break;
-	    case SIGWINCH:
-		len = window_size_seq(buf,sizeof(buf));
-		break;
-	    default:
-		fprintf(stderr,"Unexpected signal: %u\n",recv_sig);
-	    }
-	    recv_sig = 0;
-	}
-	else
-#else /* __OSE__ */
-	SIGSELECT sigsel[] = {0};
-	sig = receive(sigsel);
-	len = 0;
-#endif
-#ifndef __OSE__
-	  if (FD_ISSET(0,&readfds)) {
-	    len = read(0, buf, sizeof(buf));
-#else /* __OSE__ */
-	  if (sig->signo == FM_READ_PTR_REPLY &&
-	      sig->fm_read_ptr.handle == stdin_fh) {
-	    len = sig->fm_read_ptr.status == EFS_SUCCESS ? sig->fm_read_ptr.actual : -1;
-	    buf = sig->fm_read_ptr.buffer;
-#endif
-	    if (len <= 0) {
-		close(rfd);
-		close(wfd);
-		if (len < 0) {
-		    fprintf(stderr, "Error in reading from stdin.\n");
-		} else {
-		    fprintf(stderr, "[EOF]\n\r");
-		}
-		break;
-	    }
-	    /* check if there is an eof character in input */
-	    for (i = 0; i < len-1 && buf[i] != tty_eof; i++);
-	    if (buf[i] == tty_eof) {
-		fprintf(stderr, "[Quit]\n\r");
-		break;
-	    }
-	}
-
-	if (len) {
-#ifdef DEBUG
-	    if(write(1, buf, len));
-#endif
-	    if (write_all(wfd, buf, len) != len) {
-		fprintf(stderr, "Error in writing to FIFO.\n");
-		close(rfd);
-		close(wfd);
-		break;
-	    }
-	    STATUS("\" OK\r\n");
-#ifdef __OSE__
-	    aio_dispatch(sig);
-	    READ_AIO(stdin_read_req, 0, BUFSIZ, stdin_buf);
-#endif
-	}
-
-	/*
-	 * Read from FIFO, write to terminal.
-	 */
-#ifndef __OSE__
-	if (FD_ISSET(rfd, &readfds)) {
-	    STATUS("FIFO read: ");
-	    len = read(rfd, buf, BUFSIZ);
-#else /* __OSE__ */
-        if (sig->signo == FM_READ_PTR_REPLY &&
-	    sig->fm_read_ptr.handle == pipe_fh) {
-	    len = sig->fm_read_ptr.status == EFS_SUCCESS ? sig->fm_read_ptr.actual : -1;
-	    buf = sig->fm_read_ptr.buffer;
-#endif
-	    if (len < 0 && errno == EAGAIN) {
-		/*
-		 * No data this time, but the writing end of the FIFO is still open.
-		 * Do nothing.
-		 */
-		;
-	    } else if (len <= 0) {
-		/*
-		 * Either an error or end of file. In either case, break out
-		 * of the loop.
-		 */
-		close(rfd);
-		close(wfd);
-		if (len < 0) {
-		    fprintf(stderr, "Error in reading from FIFO.\n");
-		} else
-		    fprintf(stderr, "[End]\n\r");
-		break;
-	    } else {
-		if (!got_some) {
-		    if ((len=version_handshake(buf,len,wfd)) < 0) {
-			close(rfd);
-			close(wfd);
-			break;
-		    }
-#ifndef __OSE__
-		    if (protocol_ver >= 1) {
-			/* Tell run_erl size of terminal window */
-			signal(SIGWINCH, handle_sigwinch);
-			raise(SIGWINCH);
-		    }
-#endif
-		    got_some = 1;
-		}
-
-		/*
-		 * We successfully read at least one character. Write what we got.
-		 */
-		STATUS("Terminal write: \"");
-		if (write_all(1, buf, len) != len) {
-		    fprintf(stderr, "Error in writing to terminal.\n");
-		    close(rfd);
-		    close(wfd);
-		    break;
-		}
-		STATUS("\" OK\r\n");
-#ifdef __OSE__
-		aio_dispatch(sig);
-		READ_AIO(pipe_read_req, rfd, BUFSIZ, pipe_buf);
-#endif
-	    }
-	}
-    }
-
-#ifndef __OSE__
-    /*
-     * Reset terminal characterstics
-     * XXX
-     */
-    tcsetattr(0, TCSADRAIN, &tty_rmode);
-#endif
-    return 0;
-}
-
-/* Call write() until entire buffer has been written or error.
- * Return len or -1.
- */
-static int write_all(int fd, const char* buf, int len)
-{
-    int left = len;
-    int written;
-    while (left) {
-	written = write(fd,buf,left);
-	if (written < 0) {
-	    return -1;
-	}
-	left -= written;
-	buf += written;
-    }
-    return len;
-}
-
-#ifndef __OSE__
-static int window_size_seq(char* buf, size_t bufsz)
-{
-#ifdef TIOCGWINSZ
-    struct winsize ws;
-    static const char prefix[] = "\033_";
-    static const char suffix[] = "\033\\";
-    /* This Esc sequence is called "Application Program Command"
-       and seems suitable to use for our own customized stuff. */
-
-    if (ioctl(STDIN_FILENO, TIOCGWINSZ, &ws) == 0) {
-	int len = sn_printf(buf, bufsz, "%swinsize=%u,%u%s",
-			    prefix, ws.ws_col, ws.ws_row, suffix);
-	return len;
-    }
-#endif /* TIOCGWINSZ */
-    return 0;
-}
-#endif /* !__OSE__ */
-
-/*   to_erl                     run_erl
- *     |                           |
- *     |---------- '\014' -------->| (session start)
- *     |                           |
- *     |<---- "[run_erl v1-0]" ----| (version interval)
- *     |                           |
- *     |--- Esc_"version=1"Esc\ -->| (common version)
- *     |                           |
- */
-static int version_handshake(char* buf, int len, int wfd)
-{
-    unsigned re_high=0, re_low;
-    char *end = find_str(buf,len,"]\n");
-
-    if (end && sscanf(buf,"[run_erl v%u-%u",&re_high,&re_low)==2) {
-	char wbuf[30];
-	int wlen;
-
-	if (re_low > RUN_ERL_HI_VER || re_high < RUN_ERL_LO_VER) {
-	    fprintf(stderr,"Incompatible versions: to_erl=v%u-%u run_erl=v%u-%u\n",
-		    RUN_ERL_HI_VER, RUN_ERL_LO_VER, re_high, re_low);
-	    return -1;
-	}
-	/* Choose highest common version */
-	protocol_ver = re_high < RUN_ERL_HI_VER ? re_high : RUN_ERL_HI_VER;
-
-	wlen = sn_printf(wbuf, sizeof(wbuf), "\033_version=%u\033\\",
-			 protocol_ver);
-	if (write_all(wfd, wbuf, wlen) < 0) {
-	    fprintf(stderr,"Failed to send version handshake\n");
-	    return -1;
-	}
-	end += 2;
-	len -= (end-buf);
-	memmove(buf,end,len);
-
-    }
-    else {  /* we assume old run_erl without version handshake */
-	protocol_ver = 0;
-    }
-
-    if (re_high != RUN_ERL_HI_VER) {
-	fprintf(stderr,"run_erl has different version, "
-		"using common protocol level %u\n", protocol_ver);
-    }
-
-    return len;
-}
-
-
-#if defined(DEBUG) && !defined(__OSE__)
-#define S(x)  ((x) > 0 ? 1 : 0)
-
-static void show_terminal_settings(struct termios *t)
-{
-  fprintf(stderr,"c_iflag:\n");
-  fprintf(stderr,"Signal interrupt on break:   BRKINT  %d\n", S(t->c_iflag & BRKINT));
-  fprintf(stderr,"Map CR to NL on input:       ICRNL   %d\n", S(t->c_iflag & ICRNL));
-  fprintf(stderr,"Ignore break condition:      IGNBRK  %d\n", S(t->c_iflag & IGNBRK));
-  fprintf(stderr,"Ignore CR:                   IGNCR   %d\n", S(t->c_iflag & IGNCR));
-  fprintf(stderr,"Ignore char with par. err's: IGNPAR  %d\n", S(t->c_iflag & IGNPAR));
-  fprintf(stderr,"Map NL to CR on input:       INLCR   %d\n", S(t->c_iflag & INLCR));
-  fprintf(stderr,"Enable input parity check:   INPCK   %d\n", S(t->c_iflag & INPCK));
-  fprintf(stderr,"Strip character              ISTRIP  %d\n", S(t->c_iflag & ISTRIP));
-  fprintf(stderr,"Enable start/stop input ctrl IXOFF   %d\n", S(t->c_iflag & IXOFF));
-  fprintf(stderr,"ditto output ctrl            IXON    %d\n", S(t->c_iflag & IXON));
-  fprintf(stderr,"Mark parity errors           PARMRK  %d\n", S(t->c_iflag & PARMRK));
-  fprintf(stderr,"\n");
-  fprintf(stderr,"c_oflag:\n");
-  fprintf(stderr,"Perform output processing    OPOST   %d\n", S(t->c_oflag & OPOST));
-  fprintf(stderr,"\n");
-  fprintf(stderr,"c_cflag:\n");
-  fprintf(stderr,"Ignore modem status lines    CLOCAL  %d\n", S(t->c_cflag & CLOCAL));
-  fprintf(stderr,"\n");
-  fprintf(stderr,"c_local:\n");
-  fprintf(stderr,"Enable echo                  ECHO    %d\n", S(t->c_lflag & ECHO));
-  fprintf(stderr,"\n");
-  fprintf(stderr,"c_cc:\n");
-  fprintf(stderr,"c_cc[VEOF]                           %d\n", t->c_cc[VEOF]);
-}
-#endif /* DEBUG && !__OSE__ */
diff -Ndurp otp_src_18.3.4.5/erts/etc/common/to_erl_common.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/to_erl_common.h
--- otp_src_18.3.4.5/erts/etc/common/to_erl_common.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/common/to_erl_common.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,29 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-#ifndef ERL_TO_ERL_H
-#define ERL_TO_ERL_H
-
-#define TO_ERL_USAGE "to_erl [-h|-F] %s\n"			\
-  "\t-h\tThis help text.\n"						\
-  "\t-f\tForce connection even though pipe is locked by other to_erl process."
-
-int to_erl(int argc, char **argv);
-
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/etc/ose/etc.lmconf otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/etc.lmconf
--- otp_src_18.3.4.5/erts/etc/ose/etc.lmconf	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/etc.lmconf	1970-01-01 03:00:00.000000000 +0300
@@ -1,20 +0,0 @@
-OSE_LM_STACK_SIZES=256,512,1024,2048,4096,8192,16384,65536
-OSE_LM_SIGNAL_SIZES=31,63,127,255,1023,4095,16383,65535
-OSE_LM_POOL_SIZE=0x200000
-OSE_LM_MAIN_NAME=main
-OSE_LM_MAIN_STACK_SIZE=0xF000
-OSE_LM_MAIN_PRIORITY=20
-## Has to be of a type that allows MAM
-OSE_LM_PROGRAM_TYPE=APP_RAM
-OSE_LM_DATA_INIT=YES
-OSE_LM_BSS_INIT=YES
-OSE_LM_EXEC_MODEL=SHARED
-HEAP_MAX_SIZE=1000000000
-HEAP_SMALL_BUF_INIT_SIZE=64000000
-HEAP_LARGE_BUF_THRESHOLD=16000000
-HEAP_LOCK_TYPE=2
-
-# Setting the environment variable EFS_RESOLVE_TMO on the block to 0.
-# This will eliminiate delays when trying to open files on not mounted
-# volumes.
-EFS_RESOLVE_TMO=0
diff -Ndurp otp_src_18.3.4.5/erts/etc/ose/run_erl.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/run_erl.c
--- otp_src_18.3.4.5/erts/etc/ose/run_erl.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/run_erl.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,664 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Module: run_erl.c
- *
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-/* System includes */
-#include <aio.h>
-#include <errno.h>
-#include <dirent.h>
-#include <stdlib.h>
-#include <string.h>
-#include <stdio.h>
-#include <sys/stat.h>
-#include <unistd.h>
-
-/* OSE includes */
-#include "ose.h"
-#include "ose_spi/ose_spi.h"
-#include "efs.h"
-#include "pm.h"
-#include "ose_spi/fm.sig"
-
-/* erts includes */
-#include "run_erl.h"
-#include "run_erl_common.h"
-#include "safe_string.h"    /* sn_printf, strn_cpy, strn_cat, etc */
-
-typedef struct RunErlSetup_ {
-  SIGSELECT signo;
-  int run_daemon;
-  char *logdir;
-  char *command;
-  char *pipename;
-  char *blockname;
-} RunErlSetup;
-
-typedef struct ProgramState_ {
-  /* child process */
-  int ifd, ofd;
-  OSDOMAIN domain;
-  PROCESS progpid, mainbid;
-  struct PmProgramInfo *info;
-  /* to_erl */
-  char w_pipe[FILENAME_BUFSIZ],
-       r_pipe[FILENAME_BUFSIZ];
-} ProgramState;
-
-union SIGNAL {
-  SIGSELECT signo;
-  RunErlSetup setup;
-  struct FmReadPtr fm_read_ptr;
-  struct FmWritePtr fm_write_ptr;
-};
-
-static OSBOOLEAN hunt_in_block(char *block_name,
-			       char *process_name,
-			       PROCESS *pid);
-static int create_child_process(char *command_string, char *blockname,
-				ProgramState *state);
-
-
-static OSBOOLEAN hunt_in_block(char *block_name,
-			       char *process_name,
-			       PROCESS *pid) {
-  struct OS_pid_list *list;
-  PROCESS block_id = OSE_ILLEGAL_PROCESS;
-  int i;
-  char *name;
-
-  *pid = OSE_ILLEGAL_PROCESS;
-
-  list = get_bid_list(0);
-
-  if (!list)
-    return 0;
-
-  for (i = 0; i < list->count; i++) {
-
-    if (list->list[i] == get_bid(current_process()))
-      continue;
-
-    name = (char*)get_pid_info(list->list[i], OSE_PI_NAME);
-    if (name) {
-      if (strcmp(name,block_name) == 0) {
-	block_id = list->list[i];
-	free_buf((union SIGNAL**)&name);
-	break;
-      }
-      free_buf((union SIGNAL**)&name);
-    }
-  }
-
-  free_buf((union SIGNAL**)&list);
-
-  if (block_id == OSE_ILLEGAL_PROCESS)
-    return 0;
-
-  list = get_pid_list(block_id);
-
-  if (!list)
-    return 0;
-
-  for (i = 0; i < list->count; i++) {
-    name = (char*)get_pid_info(list->list[i], OSE_PI_NAME);
-    if (name) {
-      if (strcmp(name,process_name) == 0) {
-	*pid = list->list[i];
-	free_buf((union SIGNAL**)&name);
-	break;
-      }
-      free_buf((union SIGNAL**)&name);
-    }
-  }
-
-  free_buf((union SIGNAL**)&list);
-
-  if (*pid == OSE_ILLEGAL_PROCESS)
-    return 0;
-
-  return 1;
-
-}
-
-
-static int create_child_process(char *command_string,  char *blockname,
-				ProgramState *state) {
-  char *command = command_string;
-  char *argv;
-  int i = 0;
-  int ret_status;
-  PmStatus pm_status;
-  int tmp_io[2];
-  int fd_arr[3];
-  int ifd[2], ofd[2];
-  char *handle;
-  struct PmLoadModuleInfoReply *mod_info;
-
-  /* Parse out cmd and argv from the command string */
-  while (1) {
-    if (command[i] == ' ' || command[i] == '\0') {
-      if (command[i] == '\0')
-	argv = NULL;
-      else {
-	command[i] = '\0';
-	argv = command_string + i + 1;
-      }
-      break;
-    }
-    i++;
-  }
-
-  if (blockname)
-    handle = blockname;
-  else
-    handle = simple_basename(command);
-
-  if (ose_pm_load_module_info(handle,&mod_info) == PM_SUCCESS) {
-    /* Already installed */
-    free_buf((union SIGNAL**)&mod_info);
-  } else if ((pm_status = ose_pm_install_load_module(0,"ELF",command,handle,0,0,NULL))
-	     != PM_SUCCESS) {
-      ERROR1(LOG_ERR,"ose_pm_install_load_module failed - pmstatus: 0x%08x\n",
-	     pm_status);
-      return 0;
-  }
-
-  state->domain = PM_NEW_DOMAIN;
-
-  pm_status = ose_pm_create_program(&state->domain, handle, 0, 0 , NULL,
-				    &state->progpid, &state->mainbid);
-
-  if (pm_status != PM_SUCCESS) {
-    if (pm_status == PM_EINSTALL_HANDLE_IN_USE)
-      ERROR1(LOG_ERR,"ose_pm_create_program failed - "
-	     "install handle \"%s\" is in use. You can specify another "
-	     "install handle by using the -block option to run_erl.\n",handle);
-    else
-      ERROR1(LOG_ERR,"ose_pm_create_program failed - pmstatus: 0x%08x\n",
-	     pm_status);
-    return 0;
-  }
-
-  pm_status = ose_pm_program_info(state->progpid, &state->info);
-  /* FIXME don't forget to free this ((union SIGNAL **)&info) */
-  if (pm_status != PM_SUCCESS) {
-    ERROR1(LOG_ERR,"ose_pm_program_info failed - pmstatus: 0x%08x\n",
-	   pm_status);
-    return 0;
-  }
-
-  /* We only clone stdin+stdout, what about stderr? */
-
-  /* create pipes */
-  if (pipe(ifd) < 0) {
-    if (errno == ENOENT)
-      ERRNO_ERR0(LOG_ERR,"The /pipe file system is not available\n");
-    else
-      ERRNO_ERR0(LOG_ERR,"pipe ifd failed\n");
-    return 0;
-  }
-
-  if (pipe(ofd) < 0) {
-    ERRNO_ERR0(LOG_ERR,"pipe ofd failed\n");
-    return 0;
-  }
-
-  /* FIXME Lock? */
-
-  /* backup our stdin stdout */
-  if ((tmp_io[0] = dup(0)) < 0) {
-    ERRNO_ERR0(LOG_ERR,"dup 0 failed\n");
-    return 0;
-  }
-
-  if ((tmp_io[1] = dup(1)) < 0) {
-    ERRNO_ERR0(LOG_ERR,"dup 1 failed\n");
-    return 0;
-  }
-
-  /* set new pipe to fd 0,1 */
-  if (dup2(ifd[1], 1) < 0) {
-    ERRNO_ERR0(LOG_ERR,"dup2 1 failed\n");
-    return 0;
-  }
-
-  if (dup2(ofd[0], 0) < 0) {
-    ERRNO_ERR0(LOG_ERR,"dup2 0 failed\n");
-    return 0;
-  }
-
-  /* clone array to newly created */
-  fd_arr[0] = 2; /* Number of fd's */
-  fd_arr[1] = 0;
-  fd_arr[2] = 1;
-
-  if ((ret_status = efs_clone_array(state->info->main_process, fd_arr))
-      != EFS_SUCCESS) {
-    ERROR1(LOG_ERR,"efs_close_array filed, errcode: %d\n", ret_status);
-    return 0;
-  }
-
-  if (dup2(tmp_io[1], 1) < 0) {
-    ERRNO_ERR0(LOG_ERR,"restoring dup2 1 failed\n");
-    return 0;
-  }
-
-  if (dup2(tmp_io[0], 0) < 0) {
-    ERRNO_ERR0(LOG_ERR,"restoring dup2 1 failed\n");
-    return 0;
-  }
-
-  /* close loose-ends */
-  sf_close(tmp_io[0]);
-  sf_close(tmp_io[1]);
-  sf_close(ifd[1]);
-  sf_close(ofd[0]);
-  state->ifd = ifd[0];
-  state->ofd = ofd[1];
-
-  if (argv && set_env(state->progpid, "ARGV", argv)) {
-    ERRNO_ERR0(LOG_ERR,"something went wrong with set_env\n");
-  }
-
-  /*
-   * Start the program.
-   */
-  pm_status = ose_pm_start_program(state->progpid);
-  if (pm_status != PM_SUCCESS) {
-    ERROR1(LOG_ERR,"ose_pm_install_load_module failed - pmstatus: 0x%08x\n",
-	   pm_status);
-    return 0;
-  }
-
-  return 1;
-}
-
-#define SET_AIO(REQ,FD,SIZE,BUFF)					\
-  /* Make sure to clean data structure of previous request */		\
-  memset(&(REQ),0,sizeof(REQ));						\
-  (REQ).aio_fildes = FD;						\
-  (REQ).aio_offset = FM_POSITION_CURRENT;				\
-  (REQ).aio_nbytes = SIZE;						\
-  (REQ).aio_buf = BUFF;							\
-  (REQ).aio_sigevent.sigev_notify = SIGEV_NONE
-
-#define READ_AIO(REQ,FD,SIZE,BUFF) do {					\
-  SET_AIO(REQ,FD,SIZE,BUFF);						\
-  if (aio_read(&(REQ)) != 0)						\
-    ERRNO_ERR1(LOG_ERR,"aio_read of child_read_req(%d) failed\n",FD);	\
-  } while (0)
-
-#define WRITE_AIO(FD,SIZE,BUFF) do {					\
-    struct aiocb *write_req = malloc(sizeof(struct aiocb));		\
-    char *write_buff = malloc(sizeof(char)*SIZE);			\
-    memcpy(write_buff,BUFF,SIZE);					\
-    SET_AIO(*write_req,FD,SIZE,write_buff);				\
-    if (aio_write(write_req) != 0)					\
-      ERRNO_ERR1(LOG_ERR,"aio_write of write_req(%d) failed\n",FD);	\
-  } while(0)
-
-int pass_on(ProgramState *state);
-int pass_on(ProgramState *s) {
-  SIGSELECT sigsel[] = {0,FM_READ_PTR_REPLY};
-  union SIGNAL *sig;
-  char child_read_buff[BUFSIZ], pipe_read_buff[BUFSIZ];
-  struct aiocb child_read_req, pipe_read_req;
-  int rfd, wfd = 0;
-  FmHandle rfh, child_rfh;
-  int outstanding_writes = 0, got_some = 0, child_done = 0;
-
-  if ((rfd = sf_open(s->r_pipe, O_RDONLY, 0)) < 0) {
-    ERRNO_ERR1(LOG_ERR,"Could not open FIFO '%s' for reading.\n", s->r_pipe);
-    rfd = 0;
-    return 1;
-  }
-
-  attach(NULL,s->progpid);
-
-  /* Open the log file */
-  erts_run_erl_log_open();
-
-  efs_examine_fd(rfd,FLIB_FD_HANDLE,&rfh);
-  efs_examine_fd(s->ifd,FLIB_FD_HANDLE,&child_rfh);
-
-  READ_AIO(child_read_req,s->ifd,BUFSIZ,child_read_buff);
-  READ_AIO(pipe_read_req,rfd,BUFSIZ,pipe_read_buff);
-
-  while (1) {
-    time_t now,last_activity;
-
-    time(&last_activity);
-    sig = receive_w_tmo(erts_run_erl_log_alive_minutes()*60000,sigsel);
-
-    time(&now);
-
-    if (sig) {
-      erts_run_erl_log_activity(0,now,last_activity);
-    } else {
-      /* timeout */
-      erts_run_erl_log_activity(1,now,last_activity);
-      continue;
-    }
-
-    switch (sig->signo) {
-    case OS_ATTACH_SIG: {
-      if (rfd) { sf_close(rfd); rfd = 0; }
-      free_buf(&sig);
-      child_done = 1;
-      /* Make sure to to let all outstanding write request finish */
-      if (outstanding_writes)
-	break;
-      if (wfd) sf_close(wfd);
-      return 0;
-    }
-    case FM_WRITE_PTR_REPLY: {
-      if (sig->fm_write_ptr.status == EFS_SUCCESS) {
-	if (sig->fm_write_ptr.actual < sig->fm_write_ptr.requested) {
-	  WRITE_AIO(wfd, sig->fm_write_ptr.requested-sig->fm_write_ptr.actual,
-		    sig->fm_write_ptr.buffer+sig->fm_write_ptr.actual);
-	}
-      } else {
-	/* Assume to_erl has terminated. */
-	sf_close(wfd);
-	wfd = 0;
-      }
-      free((char*)sig->fm_write_ptr.buffer);
-      aio_dispatch(sig);
-      if ((--outstanding_writes == 0) && child_done) {
-	if (wfd) sf_close(wfd);
-	return 0;
-      }
-      break;
-    }
-    case FM_READ_PTR_REPLY: {
-      /* Child fd */
-      if (sig->fm_read_ptr.handle == child_rfh) {
-
-	/* Child terminated */
-	if (sig->fm_read_ptr.status != EFS_SUCCESS ||
-	    sig->fm_read_ptr.actual == 0) {
-
-	  if (rfd) { sf_close(rfd); rfd = 0; }
-
-	  if (sig->fm_read_ptr.status != EFS_SUCCESS) {
-	    ERROR0(LOG_ERR,"Erlang closed the connection.");
-	    aio_dispatch(sig);
-	    return 1;
-	  }
-
-	  /* child closed connection gracefully */
-	  aio_dispatch(sig);
-	  if (outstanding_writes) {
-	    child_done = 1;
-	    break;
-	  }
-
-	  if (wfd) sf_close(wfd);
-
-	  return 0;
-	} else {
-	  erts_run_erl_log_write(sig->fm_read_ptr.buffer,
-				 sig->fm_read_ptr.actual);
-	  if (wfd) {
-	    WRITE_AIO(wfd, sig->fm_read_ptr.actual, sig->fm_read_ptr.buffer);
-	    outstanding_writes++;
-	  }
-	  aio_dispatch(sig);
-	  READ_AIO(child_read_req, s->ifd,BUFSIZ, child_read_buff);
-	}
-      /* pipe fd */
-      } else if (sig->fm_read_ptr.handle == rfh) {
-	if (sig->fm_read_ptr.status != EFS_SUCCESS) {
-	  if(rfd) sf_close(rfd);
-	  if(wfd) sf_close(wfd);
-	  aio_dispatch(sig);
-	  ERRNO_ERR0(LOG_ERR,"Error in reading from FIFO.");
-	  return 1;
-	}
-	if (sig->fm_read_ptr.actual == 0) {
-	  /* to_erl closed its end of the pipe */
-	  aio_dispatch(sig);
-	  sf_close(rfd);
-	  rfd = sf_open(s->r_pipe,O_RDONLY|DONT_BLOCK_PLEASE, 0);
-	  if (rfd < 0) {
-	    ERRNO_ERR1(LOG_ERR,"Could not open FIFO '%s' for reading.",
-		       s->r_pipe);
-	    rfd = 0;
-	  } else {
-	    READ_AIO(pipe_read_req,rfd,BUFSIZ,pipe_read_buff);
-	  }
-	  got_some = 0; /* reset for next session */
-	} else {
-	  int len = sig->fm_read_ptr.actual;
-	  char *buffer = sig->fm_read_ptr.buffer;
-	  if (!wfd) {
-	    /* Try to open the write pipe to to_erl. Now that we got some data
-	     * from to_erl, to_erl should already be reading this pipe - open
-	     * should succeed. But in case of error, we just ignore it.
-	     */
-	    if ((wfd = sf_open(s->w_pipe, O_WRONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
-	      erts_run_erl_log_status("Client expected on FIFO %s, "
-				      "but can't open (len=%d)\n",
-				      s->w_pipe, sig->fm_read_ptr.actual);
-	      sf_close(rfd);
-	      rfd = sf_open(s->r_pipe, O_RDONLY|DONT_BLOCK_PLEASE, 0);
-	      if (rfd < 0) {
-		ERRNO_ERR1(LOG_ERR,"Could not open FIFO '%s' for reading.",
-			   s->r_pipe);
-		return 1;
-	      }
-	      wfd = 0;
-	    } else {
-#ifdef DEBUG
-	      erts_run_erl_log_status("run_erl: %s opened for writing\n",
-				      s->w_pipe);
-#endif
-	    }
-	  }
-
-	  if (!got_some && wfd && buffer[0] == '\014') {
-	    char wbuf[30];
-	    int wlen = sn_printf(wbuf,sizeof(wbuf),"[run_erl v%u-%u]\n",
-				 RUN_ERL_HI_VER, RUN_ERL_LO_VER);
-	    /* For some reason this, the first write aio seems to
-	       not get an FM_WRITE_PTR_REPLY, so we do not do:
-	       outstanding_writes++;
-	    */
-	    WRITE_AIO(wfd, wlen, wbuf);
-	  }
-	  got_some = 1;
-
-	  /* Write the message */
-#ifdef DEBUG
-	  erts_run_erl_log_status("Pty master write; ");
-#endif
-	  len = erts_run_erl_extract_ctrl_seq(buffer,len, s->ofd);
-
-	  if (len > 0) {
-	    int wlen = erts_run_erl_write_all(s->ofd, buffer, len);
-	    if (wlen != len) {
-	      aio_dispatch(sig);
-	      ERRNO_ERR0(LOG_ERR,"Error in writing to terminal.");
-	      if(rfd) sf_close(rfd);
-	      if(wfd) sf_close(wfd);
-	      return 1;
-	    }
-	  }
-#ifdef DEBUG
-	  erts_run_erl_log_status("OK\n");
-#endif
-	  aio_dispatch(sig);
-	  READ_AIO(pipe_read_req,rfd,BUFSIZ,pipe_read_buff);
-	}
-	}
-      break;
-    }
-    default: {
-      free_buf(&sig);
-      break;
-    }
-    }
-  }
-}
-
-OS_PROCESS(run_erl_process) {
-  char *logdir, *command, *blockname;
-  SIGSELECT sigsel[] = {1,ERTS_SIGNAL_RUN_ERL_SETUP};
-  union SIGNAL *sig = receive(sigsel);
-  ProgramState state;
-  char pipename[FILENAME_BUFSIZ];
-
-  state.info = NULL;
-
-  logdir = strdup(sig->setup.logdir);
-  command = strdup(sig->setup.command);
-  strn_cpy(pipename,sizeof(pipename),sig->setup.pipename);
-
-  if (sig->setup.blockname)
-    blockname = strdup(sig->setup.blockname);
-  else
-    blockname = NULL;
-
-  erts_run_erl_log_init(sig->setup.run_daemon, logdir);
-
-  free_buf(&sig);
-
-  if (erts_run_erl_open_fifo(pipename,state.w_pipe,state.r_pipe))
-    kill_proc(current_process());
-
-  if (create_child_process(command,blockname,&state))
-    pass_on(&state);
-
-  free(logdir);
-  free(command);
-  if (blockname)
-    free(blockname);
-
-  if (state.info)
-    free_buf(((union SIGNAL**)&state.info));
-
-  sf_close(state.ifd);
-  sf_close(state.ofd);
-
-  unlink(state.w_pipe);
-  unlink(state.r_pipe);
-
-  kill_proc(current_process());
-}
-
-int run_erl(int argc,char **argv) {
-  char *pipename, *logdir, *command, *blockname = NULL;
-  int pipename_len, logdir_len, command_len, blockname_len = 0;
-  int i = 1, run_daemon = 0;
-  PROCESS pid;
-  SIGSELECT sigsel[] = {0};
-  union SIGNAL *sig;
-
-  if(argc < 4) {
-    fprintf(stderr,RUN_ERL_USAGE,"run_erl");
-    return 1;
-  }
-
-  while (1) {
-    if (argv[i][0] != '-')
-      break;
-    if (!strcmp(argv[i],"-daemon")) {
-      run_daemon = 1;
-      i++;
-      continue;
-    }
-    if (!strcmp(argv[i],"-block")) {
-      blockname = argv[i+1];
-      blockname_len = strlen(argv[i+1]) + 1;
-      i+=2;
-      continue;
-    }
-    fprintf(stderr,RUN_ERL_USAGE,"run_erl");
-    return 1;
-  }
-
-  pipename = argv[i++];
-  logdir = argv[i++];
-  command = argv[i++];
-
-  /* + 1 to include NULL at end */
-  logdir_len = strlen(logdir) + 1;
-  command_len = strlen(command) + 1;
-  pipename_len = strlen(pipename) + 1;
-
-  if (run_daemon) {
-    /* We request that the run_erl_process should be started from the
-       main process so that it does not die when the shell command
-       returns */
-    PROCESS main_pid;
-    hunt_in_block("run_erl","main",&main_pid);
-    sig = alloc(sizeof(*sig),ERTS_SIGNAL_RUN_ERL_DAEMON);
-    send(&sig,main_pid);
-    sig = receive(sigsel);
-    pid = sender(&sig);
-    free_buf(&sig);
-  } else {
-    pid = create_process(OS_BG_PROC,"run_erl_process",
-			 run_erl_process, 0x800,
-			 0, 0, 0, NULL, 0, 0);
-  }
-
-  sig = alloc(sizeof(RunErlSetup)+
-	      logdir_len+command_len+pipename_len+blockname_len,
-	      ERTS_SIGNAL_RUN_ERL_SETUP);
-  sig->setup.run_daemon = run_daemon;
-  sig->setup.logdir = ((char*)sig)+sizeof(RunErlSetup);
-  sig->setup.command = ((char*)sig)+sizeof(RunErlSetup)+logdir_len;
-  sig->setup.pipename = ((char*)sig)+sizeof(RunErlSetup)+logdir_len+command_len;
-  if (blockname)
-    sig->setup.blockname = ((char*)sig)+sizeof(RunErlSetup)+
-      logdir_len+command_len+pipename_len;
-  else
-    sig->setup.blockname = NULL;
-
-  strcpy(sig->setup.logdir,logdir);
-  strcpy(sig->setup.command,command);
-  strcpy(sig->setup.pipename,pipename);
-  if (blockname) strcpy(sig->setup.blockname,blockname);
-
-  send(&sig,pid);
-
-  if (run_daemon) {
-    /* We are a daemon, error msgs will be sent to ramlog */
-    start(pid);
-    return 1;
-  }
-
-  /* We are not daemon, error msgs will be sent to stderr and we block here */
-  efs_clone(pid);
-  start(pid);
-
-  attach(NULL,pid);
-  sig = receive(sigsel);
-
-  return 1;
-}
diff -Ndurp otp_src_18.3.4.5/erts/etc/ose/run_erl.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/run_erl.h
--- otp_src_18.3.4.5/erts/etc/ose/run_erl.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/run_erl.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,30 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-#ifndef ERL_RUN_ERL_H
-#define ERL_RUN_ERL_H
-
-#include "ose.h"
-
-#include "erts.sig"
-
-int run_erl(int argc, char **argv);
-OS_PROCESS(run_erl_process);
-
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/etc/ose/run_erl_main.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/run_erl_main.c
--- otp_src_18.3.4.5/erts/etc/ose/run_erl_main.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/ose/run_erl_main.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,80 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2013. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-/*
- * Module: run_erl_main.c
- *
- * Container for load module that installs both run_erl and to_erl command.
- */
-
-#ifdef HAVE_CONFIG_H
-#  include "config.h"
-#endif
-
-#include <stdio.h>
-
-#include "ose.h"
-#include "shell.h"
-
-#include "run_erl_common.h"
-#include "run_erl.h"
-#include "to_erl_common.h"
-
-union SIGNAL {
-  SIGSELECT signo;
-};
-
-int main(int argc, char **argv)
-{
-
-  char run_erl_usage[320],
-    to_erl_usage[120];
-
-  (void)stdin;(void)stdout;(void)stderr;
-
-  sprintf(run_erl_usage,RUN_ERL_USAGE,"run_erl [-daemon] [-block blockname]");
-  sprintf(to_erl_usage,TO_ERL_USAGE,"pipename");
-
-  shell_add_cmd_attrs(
-    "run_erl",run_erl_usage,
-    "Redirect Erlang input and output streams",
-    run_erl,DEFAULT_PROC_TYPE,DEFAULT_PRIORITY,DEFAULT_STACK_SIZE);
-
-  shell_add_cmd_attrs(
-    "to_erl",to_erl_usage,
-    "Attach to redirected Erlang input and output streams",
-    to_erl,DEFAULT_PROC_TYPE,DEFAULT_PRIORITY,DEFAULT_STACK_SIZE);
-
-  while (1) {
-    static const SIGSELECT sigsel[] = {0};
-    union SIGNAL *sig = receive(sigsel);
-
-    if (sig->signo == ERTS_SIGNAL_RUN_ERL_DAEMON) {
-      PROCESS pid = create_process(OS_BG_PROC,"run_erl_daemon",
-				   run_erl_process, 0x800,
-				   0, 0, 0, NULL, 0, 0);
-      send_w_s(&sig,pid,sender(&sig));
-    } else {
-      printf("Got unexpected signal!");
-      free_buf(&sig);
-    }
-  }
-
-  return 1;
-}
diff -Ndurp otp_src_18.3.4.5/erts/etc/unix/run_erl.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/run_erl.c
--- otp_src_18.3.4.5/erts/etc/unix/run_erl.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/run_erl.c	2017-02-03 21:52:59.163951269 +0200
@@ -1,7 +1,7 @@
 /*
  * %CopyrightBegin%
  * 
- * Copyright Ericsson AB 1996-2013. All Rights Reserved.
+ * Copyright Ericsson AB 1996-2015. All Rights Reserved.
  * 
  * Licensed under the Apache License, Version 2.0 (the "License");
  * you may not use this file except in compliance with the License.
@@ -41,13 +41,11 @@
 #ifdef HAVE_CONFIG_H
 #  include "config.h"
 #endif
-
 #ifdef HAVE_WORKING_POSIX_OPENPT
 #ifndef _XOPEN_SOURCE
 #define _XOPEN_SOURCE 600 
 #endif
 #endif
-
 #include <sys/types.h>
 #include <sys/wait.h>
 #include <sys/stat.h>
@@ -65,6 +63,11 @@
 #include <dirent.h>
 #include <termios.h>
 #include <time.h>
+
+#ifdef __ANDROID__
+#  include <termios.h>
+#endif
+
 #ifdef HAVE_SYSLOG_H
 #  include <syslog.h>
 #endif
@@ -84,25 +87,81 @@
 #  include <stropts.h>
 #endif
 
-#include "run_erl_common.h"
+#include "run_erl.h"
 #include "safe_string.h"    /* sn_printf, strn_cpy, strn_cat, etc */
 
+#ifdef O_NONBLOCK
+#  define DONT_BLOCK_PLEASE O_NONBLOCK
+#else
+#  define DONT_BLOCK_PLEASE O_NDELAY
+#  ifndef EAGAIN
+#    define EAGAIN -3898734
+#  endif
+#endif
+
+#define noDEBUG
+
+#define DEFAULT_LOG_GENERATIONS 5
+#define LOG_MAX_GENERATIONS     1000      /* No more than 1000 log files */
+#define LOG_MIN_GENERATIONS     2         /* At least two to switch between */
+#define DEFAULT_LOG_MAXSIZE     100000
+#define LOG_MIN_MAXSIZE         1000      /* Smallast value for changing log file */
+#define LOG_STUBNAME            "erlang.log."
+#define LOG_PERM                0664
+#define DEFAULT_LOG_ACTIVITY_MINUTES    5
+#define DEFAULT_LOG_ALIVE_MINUTES       15
+#define DEFAULT_LOG_ALIVE_FORMAT        "%a %b %e %T %Z %Y"
+#define ALIVE_BUFFSIZ                   256
+
+#define PERM            0600
+#define STATUSFILENAME  "/run_erl.log"
+#define PIPE_STUBNAME   "erlang.pipe"
+#define PIPE_STUBLEN    strlen(PIPE_STUBNAME)
+
+#ifndef FILENAME_MAX
+#define FILENAME_MAX 250
+#endif
+
+#ifndef O_SYNC
+#define O_SYNC 0
+#define USE_FSYNC 1
+#endif
+
 #define MAX(x,y)  ((x) > (y) ? (x) : (y))
 
+#define FILENAME_BUFSIZ FILENAME_MAX
+
 /* prototypes */
 static void usage(char *);
+static int create_fifo(char *name, int perm);
 static int open_pty_master(char **name, int *sfd);
 static int open_pty_slave(char *name);
 static void pass_on(pid_t);
 static void exec_shell(char **);
+static void status(const char *format,...);
+static void error_logf(int priority, int line, const char *format,...);
 static void catch_sigchild(int);
+static int next_log(int log_num);
+static int prev_log(int log_num);
+static int find_next_log_num(void);
+static int open_log(int log_num, int flags);
+static void write_to_log(int* lfd, int* log_num, char* buf, int len);
 static void daemon_init(void);
+static char *simple_basename(char *path);
 static void init_outbuf(void);
 static int outbuf_size(void);
 static void clear_outbuf(void);
 static char* outbuf_first(void);
 static void outbuf_delete(int bytes);
 static void outbuf_append(const char* bytes, int n);
+static int write_all(int fd, const char* buf, int len);
+static int extract_ctrl_seq(char* buf, int len);
+static void set_window_size(unsigned col, unsigned row);
+
+static ssize_t sf_write(int fd, const void *buffer, size_t len);
+static ssize_t sf_read(int fd, void *buffer, size_t len);
+static int sf_open(const char *path, int flags, mode_t mode);
+static int sf_close(int fd);
 
 #ifdef DEBUG
 static void show_terminal_settings(struct termios *t);
@@ -110,11 +169,20 @@ static void show_terminal_settings(struc
 
 /* static data */
 static char fifo1[FILENAME_BUFSIZ], fifo2[FILENAME_BUFSIZ];
+static char statusfile[FILENAME_BUFSIZ];
+static char log_dir[FILENAME_BUFSIZ];
 static char pipename[FILENAME_BUFSIZ];
 static FILE *stdstatus = NULL;
+static int log_generations = DEFAULT_LOG_GENERATIONS;
+static int log_maxsize     = DEFAULT_LOG_MAXSIZE;
+static int log_alive_minutes = DEFAULT_LOG_ALIVE_MINUTES;
+static int log_activity_minutes = DEFAULT_LOG_ACTIVITY_MINUTES;
+static int log_alive_in_gmt = 0;
+static char log_alive_format[ALIVE_BUFFSIZ+1];
 static int run_daemon = 0;
 static char *program_name;
 static int mfd; /* master pty fd */
+static unsigned protocol_ver = RUN_ERL_LO_VER; /* assume lowest to begin with */
 
 /*
  * Output buffer.
@@ -145,13 +213,29 @@ static char* outbuf_in;
                                   LOG_PID|LOG_CONS|LOG_NOWAIT,LOG_USER)
 #endif
 
+#define ERROR0(Prio,Format) error_logf(Prio,__LINE__,Format"\n")
+#define ERROR1(Prio,Format,A1) error_logf(Prio,__LINE__,Format"\n",A1)
+#define ERROR2(Prio,Format,A1,A2) error_logf(Prio,__LINE__,Format"\n",A1,A2)
+
+#ifdef HAVE_STRERROR
+#    define ADD_ERRNO(Format) "errno=%d '%s'\n"Format"\n",errno,strerror(errno)
+#else
+#    define ADD_ERRNO(Format) "errno=%d\n"Format"\n",errno
+#endif
+#define ERRNO_ERR0(Prio,Format) error_logf(Prio,__LINE__,ADD_ERRNO(Format))
+#define ERRNO_ERR1(Prio,Format,A1) error_logf(Prio,__LINE__,ADD_ERRNO(Format),A1)
+
+
 int main(int argc, char **argv)
 {
   int childpid;
   int sfd = -1;
-  char *ptyslave=NULL;
+  int fd;
+  char *p, *ptyslave=NULL;
   int i = 1;
   int off_argv;
+  int calculated_pipename = 0;
+  int highest_pipe_num = 0;
 
   program_name = argv[0];
 
@@ -169,16 +253,122 @@ int main(int argc, char **argv)
 
   off_argv = i;
   strn_cpy(pipename, sizeof(pipename), argv[i++]);
-
-  erts_run_erl_log_init(run_daemon,argv[i]);
+  strn_cpy(log_dir, sizeof(log_dir), argv[i]);
+  strn_cpy(statusfile, sizeof(statusfile), log_dir);
+  strn_cat(statusfile, sizeof(statusfile), STATUSFILENAME);
 
 #ifdef DEBUG
-  erts_run_erl_log_status("%s: pid is : %d\n", argv[0], getpid());
+  status("%s: pid is : %d\n", argv[0], getpid());
 #endif
 
-  /* Open read and write fifo */
-  if (erts_run_erl_open_fifo(pipename,fifo1,fifo2))
-    exit(1);
+  /* Get values for LOG file handling from the environment */
+  if ((p = getenv("RUN_ERL_LOG_ALIVE_MINUTES"))) {
+      log_alive_minutes = atoi(p);
+      if (!log_alive_minutes) {
+	  ERROR1(LOG_ERR,"Minimum value for RUN_ERL_LOG_ALIVE_MINUTES is 1 "
+		 "(current value is %s)",p);
+      }
+      log_activity_minutes = log_alive_minutes / 3;
+      if (!log_activity_minutes) {
+	  ++log_activity_minutes;
+      }
+  }
+  if ((p = getenv("RUN_ERL_LOG_ACTIVITY_MINUTES"))) {
+     log_activity_minutes = atoi(p);
+      if (!log_activity_minutes) {
+	  ERROR1(LOG_ERR,"Minimum value for RUN_ERL_LOG_ACTIVITY_MINUTES is 1 "
+		 "(current value is %s)",p);
+      }
+  } 
+  if ((p = getenv("RUN_ERL_LOG_ALIVE_FORMAT"))) {
+      if (strlen(p) > ALIVE_BUFFSIZ) {
+	  ERROR1(LOG_ERR, "RUN_ERL_LOG_ALIVE_FORMAT can contain a maximum of "
+		 "%d characters", ALIVE_BUFFSIZ);
+      }
+      strn_cpy(log_alive_format, sizeof(log_alive_format), p);
+  } else {
+      strn_cpy(log_alive_format, sizeof(log_alive_format), DEFAULT_LOG_ALIVE_FORMAT);
+  }
+  if ((p = getenv("RUN_ERL_LOG_ALIVE_IN_UTC")) && strcmp(p,"0")) {
+      ++log_alive_in_gmt;
+  }
+  if ((p = getenv("RUN_ERL_LOG_GENERATIONS"))) {
+    log_generations = atoi(p);
+    if (log_generations < LOG_MIN_GENERATIONS)
+      ERROR1(LOG_ERR,"Minimum RUN_ERL_LOG_GENERATIONS is %d", LOG_MIN_GENERATIONS);
+    if (log_generations > LOG_MAX_GENERATIONS)
+      ERROR1(LOG_ERR,"Maximum RUN_ERL_LOG_GENERATIONS is %d", LOG_MAX_GENERATIONS);
+  }
+
+  if ((p = getenv("RUN_ERL_LOG_MAXSIZE"))) {
+    log_maxsize = atoi(p);
+    if (log_maxsize < LOG_MIN_MAXSIZE)
+      ERROR1(LOG_ERR,"Minimum RUN_ERL_LOG_MAXSIZE is %d", LOG_MIN_MAXSIZE);
+  }
+
+  /*
+   * Create FIFOs and open them 
+   */
+
+  if(*pipename && pipename[strlen(pipename)-1] == '/') {
+    /* The user wishes us to find a unique pipe name in the specified */
+    /* directory */
+    DIR *dirp;
+    struct dirent *direntp;
+
+    calculated_pipename = 1;
+    dirp = opendir(pipename);
+    if(!dirp) {
+      ERRNO_ERR1(LOG_ERR,"Can't access pipe directory '%s'.", pipename);
+      exit(1);
+    }
+
+    /* Check the directory for existing pipes */
+    
+    while((direntp=readdir(dirp)) != NULL) {
+      if(strncmp(direntp->d_name,PIPE_STUBNAME,PIPE_STUBLEN)==0) {
+	int num = atoi(direntp->d_name+PIPE_STUBLEN+1);
+	if(num > highest_pipe_num)
+	  highest_pipe_num = num;
+      }
+    }	
+    closedir(dirp);
+    strn_catf(pipename, sizeof(pipename), "%s.%d",
+	      PIPE_STUBNAME, highest_pipe_num+1);
+  } /* if */
+
+  for(;;) {
+      /* write FIFO - is read FIFO for `to_erl' program */
+      strn_cpy(fifo1, sizeof(fifo1), pipename);
+      strn_cat(fifo1, sizeof(fifo1), ".r");
+      if (create_fifo(fifo1, PERM) < 0) {
+	  ERRNO_ERR1(LOG_ERR,"Cannot create FIFO %s for writing.", fifo1);
+	  exit(1);
+      }
+      
+      /* read FIFO - is write FIFO for `to_erl' program */
+      strn_cpy(fifo2, sizeof(fifo2), pipename);
+      strn_cat(fifo2, sizeof(fifo2), ".w");
+      
+      /* Check that nobody is running run_erl already */
+      if ((fd = sf_open(fifo2, O_WRONLY|DONT_BLOCK_PLEASE, 0)) >= 0) {
+	  /* Open as client succeeded -- run_erl is already running! */
+	  sf_close(fd);
+	  if (calculated_pipename) {
+	      ++highest_pipe_num;
+	      strn_catf(pipename, sizeof(pipename), "%s.%d",
+			PIPE_STUBNAME, highest_pipe_num+1);
+	      continue;
+	  } 
+	  fprintf(stderr, "Erlang already running on pipe %s.\n", pipename);
+	  exit(1);
+      }
+      if (create_fifo(fifo2, PERM) < 0) { 
+	  ERRNO_ERR1(LOG_ERR,"Cannot create FIFO %s for reading.", fifo2);
+	  exit(1);
+      }
+      break;
+  }
 
   /*
    * Open master pseudo-terminal
@@ -250,7 +440,7 @@ int main(int argc, char **argv)
     sf_close(2);
 
     if (dup(sfd) != 0 || dup(sfd) != 1 || dup(sfd) != 2) {
-      erts_run_erl_log_status("Cannot dup\n");
+      status("Cannot dup\n");
     }
     sf_close(sfd);
     exec_shell(argv+off_argv); /* exec_shell expects argv[2] to be */
@@ -293,7 +483,9 @@ static void pass_on(pid_t childpid)
     struct timeval timeout;
     time_t last_activity;
     char buf[BUFSIZ];
-    int rfd, wfd=0;
+    char log_alive_buffer[ALIVE_BUFFSIZ+1];
+    int lognum;
+    int rfd, wfd=0, lfd=0;
     int maxfd;
     int ready;
     int got_some = 0; /* from to_erl */
@@ -308,12 +500,13 @@ static void pass_on(pid_t childpid)
     }
     
 #ifdef DEBUG
-    erts_run_erl_log_status("run_erl: %s opened for reading\n", fifo2);
+    status("run_erl: %s opened for reading\n", fifo2);
 #endif
     
     /* Open the log file */
     
-    erts_run_erl_log_open();
+    lognum = find_next_log_num();
+    lfd = open_log(lognum, O_RDWR|O_APPEND|O_CREAT|O_SYNC);
     
     /* Enter the work loop */
     
@@ -332,8 +525,7 @@ static void pass_on(pid_t childpid)
 	    writefds_ptr = &writefds;
 	}
 	time(&last_activity);
-	/* don't assume old BSD bug */
-	timeout.tv_sec  = erts_run_erl_log_alive_minutes()*60;
+	timeout.tv_sec  = log_alive_minutes*60; /* don't assume old BSD bug */
 	timeout.tv_usec = 0;
 	ready = select(maxfd + 1, &readfds, writefds_ptr, NULL, &timeout);
 	if (ready < 0) {
@@ -363,7 +555,28 @@ static void pass_on(pid_t childpid)
 
 	    /* Check how long time we've been inactive */
 	    time(&now);
-	    erts_run_erl_log_activity(!ready,now,last_activity);
+	    if(!ready || now - last_activity > log_activity_minutes*60) {
+		/* Either a time out: 15 minutes without action, */
+		/* or something is coming in right now, but it's a long time */
+		/* since last time, so let's write a time stamp this message */
+		struct tm *tmptr;
+		if (log_alive_in_gmt) {
+		    tmptr = gmtime(&now);
+		} else {
+		    tmptr = localtime(&now);
+		}
+		if (!strftime(log_alive_buffer, ALIVE_BUFFSIZ, log_alive_format,
+			      tmptr)) {
+		    strn_cpy(log_alive_buffer, sizeof(log_alive_buffer),
+			     "(could not format time in 256 positions "
+			     "with current format string.)");
+		}
+		log_alive_buffer[ALIVE_BUFFSIZ] = '\0';
+
+		sn_printf(buf, sizeof(buf), "\n===== %s%s\n", 
+			  ready?"":"ALIVE ", log_alive_buffer);
+		write_to_log(&lfd, &lognum, buf, strlen(buf));
+	    }
 	}
 
 	/*
@@ -398,7 +611,7 @@ static void pass_on(pid_t childpid)
 	 */
 	if (FD_ISSET(mfd, &readfds)) {
 #ifdef DEBUG
-	    erts_run_erl_log_status("Pty master read; ");
+	    status("Pty master read; ");
 #endif
 	    if ((len = sf_read(mfd, buf, BUFSIZ)) <= 0) {
 		sf_close(rfd);
@@ -416,7 +629,7 @@ static void pass_on(pid_t childpid)
 		exit(0);
 	    }
 
-	    erts_run_erl_log_write(buf, len);
+	    write_to_log(&lfd, &lognum, buf, len);
 
 	    /*
 	     * Save in the output queue.
@@ -432,7 +645,7 @@ static void pass_on(pid_t childpid)
 	 */
 	if (FD_ISSET(rfd, &readfds)) {
 #ifdef DEBUG
-	    erts_run_erl_log_status("FIFO read; ");
+	    status("FIFO read; ");
 #endif
 	    if ((len = sf_read(rfd, buf, BUFSIZ)) < 0) {
 		sf_close(rfd);
@@ -461,7 +674,7 @@ static void pass_on(pid_t childpid)
 		     * should succeed. But in case of error, we just ignore it.
 		     */
 		    if ((wfd = sf_open(fifo1, O_WRONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
-			erts_run_erl_log_status("Client expected on FIFO %s, but can't open (len=%d)\n",
+			status("Client expected on FIFO %s, but can't open (len=%d)\n",
 			       fifo1, len);
 			sf_close(rfd);
 			rfd = sf_open(fifo2, O_RDONLY|DONT_BLOCK_PLEASE, 0);
@@ -473,7 +686,7 @@ static void pass_on(pid_t childpid)
 		    } 
 		    else {
 #ifdef DEBUG
-			erts_run_erl_log_status("run_erl: %s opened for writing\n", fifo1);
+			status("run_erl: %s opened for writing\n", fifo1);
 #endif
 		    }
 		}
@@ -489,15 +702,14 @@ static void pass_on(pid_t childpid)
 
 		/* Write the message */
 #ifdef DEBUG
-		erts_run_erl_log_status("Pty master write; ");
+		status("Pty master write; ");
 #endif
-		len = erts_run_erl_extract_ctrl_seq(buf, len, mfd);
+		len = extract_ctrl_seq(buf, len);
 
 		if(len==1 && buf[0] == '\003') {
 		    kill(childpid,SIGINT);
-		}
-		else if (len>0 && erts_run_erl_write_all(mfd, buf, len) != len)
-		  {
+		} 
+		else if (len>0 && write_all(mfd, buf, len) != len) {
 		    ERRNO_ERR0(LOG_ERR,"Error in writing to terminal.");
 		    sf_close(rfd);
 		    if(wfd) sf_close(wfd);
@@ -506,7 +718,7 @@ static void pass_on(pid_t childpid)
 		}
 	    }
 #ifdef DEBUG
-	    erts_run_erl_log_status("OK\n");
+	    status("OK\n");
 #endif
 	}
     }
@@ -516,6 +728,173 @@ static void catch_sigchild(int sig)
 {
 }
 
+/*
+ * next_log:
+ * Returns the index number that follows the given index number.
+ * (Wrapping after log_generations)
+ */
+static int next_log(int log_num) {
+  return log_num>=log_generations?1:log_num+1;
+}
+
+/*
+ * prev_log:
+ * Returns the index number that precedes the given index number.
+ * (Wrapping after log_generations)
+ */
+static int prev_log(int log_num) {
+  return log_num<=1?log_generations:log_num-1;
+}
+
+/*
+ * find_next_log_num()
+ * Searches through the log directory to check which logs that already
+ * exist. It finds the "hole" in the sequence, and returns the index
+ * number for the last log in the log sequence. If there is no hole, index
+ * 1 is returned.
+ */
+static int find_next_log_num(void) {
+  int i, next_gen, log_gen;
+  DIR *dirp;
+  struct dirent *direntp;
+  int log_exists[LOG_MAX_GENERATIONS+1];
+  int stub_len = strlen(LOG_STUBNAME);
+
+  /* Initialize exiting log table */
+
+  for(i=log_generations; i>=0; i--)
+    log_exists[i] = 0;
+  dirp = opendir(log_dir);
+  if(!dirp) {
+    ERRNO_ERR1(LOG_ERR,"Can't access log directory '%s'", log_dir);
+    exit(1);
+  }
+
+  /* Check the directory for existing logs */
+
+  while((direntp=readdir(dirp)) != NULL) {
+    if(strncmp(direntp->d_name,LOG_STUBNAME,stub_len)==0) {
+      int num = atoi(direntp->d_name+stub_len);
+      if(num < 1 || num > log_generations)
+	continue;
+      log_exists[num] = 1;
+    }
+  }	
+  closedir(dirp);
+
+  /* Find out the next available log file number */
+
+  next_gen = 0;
+  for(i=log_generations; i>=0; i--) {
+    if(log_exists[i])
+      if(next_gen)
+	break;
+      else 
+	;
+    else
+      next_gen = i;
+  }
+
+  /* Find out the current log file number */
+
+  if(next_gen)
+    log_gen = prev_log(next_gen);
+  else
+    log_gen = 1;
+
+  return log_gen;
+} /* find_next_log_num() */
+
+/* open_log()
+ * Opens a log file (with given index) for writing. Writing may be
+ * at the end or a trucnating write, according to flags.
+ * A LOGGING STARTED and time stamp message is inserted into the log file
+ */
+static int open_log(int log_num, int flags)
+{
+  char buf[FILENAME_MAX];
+  time_t now;
+  struct tm *tmptr;
+  char log_buffer[ALIVE_BUFFSIZ+1];
+  int lfd;
+
+  /* Remove the next log (to keep a "hole" in the log sequence) */
+  sn_printf(buf, sizeof(buf), "%s/%s%d",
+	    log_dir, LOG_STUBNAME, next_log(log_num));
+  unlink(buf);
+
+  /* Create or continue on the current log file */
+  sn_printf(buf, sizeof(buf), "%s/%s%d", log_dir, LOG_STUBNAME, log_num);
+  if((lfd = sf_open(buf, flags, LOG_PERM))<0){
+      ERRNO_ERR1(LOG_ERR,"Can't open log file '%s'.", buf);
+    exit(1);
+  }
+
+  /* Write a LOGGING STARTED and time stamp into the log file */
+  time(&now);
+  if (log_alive_in_gmt) {
+      tmptr = gmtime(&now);
+  } else {
+      tmptr = localtime(&now);
+  }
+  if (!strftime(log_buffer, ALIVE_BUFFSIZ, log_alive_format,
+		tmptr)) {
+      strn_cpy(log_buffer, sizeof(log_buffer),
+	      "(could not format time in 256 positions "
+	      "with current format string.)");
+  }
+  log_buffer[ALIVE_BUFFSIZ] = '\0';
+
+  sn_printf(buf, sizeof(buf), "\n=====\n===== LOGGING STARTED %s\n=====\n",
+	    log_buffer);
+  if (write_all(lfd, buf, strlen(buf)) < 0)
+      status("Error in writing to log.\n");
+
+#if USE_FSYNC
+  fsync(lfd);
+#endif
+
+  return lfd;
+}
+
+/* write_to_log()
+ * Writes a message to a log file. If the current log file is full,
+ * a new log file is opened.
+ */
+static void write_to_log(int* lfd, int* log_num, char* buf, int len)
+{
+  int size;
+
+  /* Decide if new logfile needed, and open if so */
+  
+  size = lseek(*lfd,0,SEEK_END);
+  if(size+len > log_maxsize) {
+    sf_close(*lfd);
+    *log_num = next_log(*log_num);
+    *lfd = open_log(*log_num, O_RDWR|O_CREAT|O_TRUNC|O_SYNC); 
+  }
+
+  /* Write to log file */
+
+  if (write_all(*lfd, buf, len) < 0) {
+    status("Error in writing to log.\n");
+  }
+
+#if USE_FSYNC
+  fsync(*lfd);
+#endif
+}
+
+/* create_fifo()
+ * Creates a new fifo with the given name and permission.
+ */
+static int create_fifo(char *name, int perm)
+{
+  if ((mkfifo(name, perm) < 0) && (errno != EEXIST))
+    return -1;
+  return 0;
+}
+
 
 /* open_pty_master()
  * Find a master device, open and return fd and slave device name.
@@ -712,9 +1091,9 @@ static void exec_shell(char **argv)
   else
     argv[0] = sh;
   argv[1] = "-c";
-  erts_run_erl_log_status("Args before exec of shell:\n");
+  status("Args before exec of shell:\n");
   for (vp = argv, i = 0; *vp; vp++, i++)
-    erts_run_erl_log_status("argv[%d] = %s\n", i, *vp);
+    status("argv[%d] = %s\n", i, *vp);
   if (stdstatus) {
       fclose(stdstatus);
   }
@@ -725,6 +1104,26 @@ static void exec_shell(char **argv)
   ERRNO_ERR0(LOG_ERR,"Could not execv");
 }
 
+/* status()
+ * Prints the arguments to a status file
+ * Works like printf (see vfrpintf)
+ */
+static void status(const char *format,...)
+{
+  va_list args;
+  time_t now;
+
+  if (stdstatus == NULL)
+    stdstatus = fopen(statusfile, "w");
+  if (stdstatus == NULL)
+    return;
+  now = time(NULL);
+  fprintf(stdstatus, "run_erl [%d] %s", (int)getpid(), ctime(&now));
+  va_start(args, format);
+  vfprintf(stdstatus, format, args);
+  va_end(args);
+  fflush(stdstatus);
+}
 
 static void daemon_init(void) 
      /* As R Stevens wants it, to a certain extent anyway... */ 
@@ -764,10 +1163,47 @@ static void daemon_init(void)
     run_daemon = 1;
 }
 
+/* error_logf()
+ * Prints the arguments to stderr or syslog
+ * Works like printf (see vfprintf)
+ */
+static void error_logf(int priority, int line, const char *format, ...)
+{
+    va_list args;
+    va_start(args, format);
+
+#ifdef HAVE_SYSLOG_H
+    if (run_daemon) {
+	vsyslog(priority,format,args);
+    }
+    else
+#endif
+    {
+	time_t now = time(NULL);
+	fprintf(stderr, "run_erl:%d [%d] %s", line, (int)getpid(), ctime(&now));
+	vfprintf(stderr, format, args);
+    }
+    va_end(args);
+}	
+
 static void usage(char *pname)
 {
-  fprintf(stderr, "Usage: ");
-  fprintf(stderr, RUN_ERL_USAGE, pname);
+  fprintf(stderr, "Usage: %s (pipe_name|pipe_dir/) log_dir \"command [parameters ...]\"\n", pname);
+  fprintf(stderr, "\nYou may also set the environment variables RUN_ERL_LOG_GENERATIONS\n");
+  fprintf(stderr, "and RUN_ERL_LOG_MAXSIZE to the number of log files to use and the\n");
+  fprintf(stderr, "size of the log file when to switch to the next log file\n");
+}
+
+/* Instead of making sure basename exists, we do our own */
+static char *simple_basename(char *path)
+{
+    char *ptr;
+    for (ptr = path; *ptr != '\0'; ++ptr) {
+	if (*ptr == '/') {
+	    path = ptr + 1;
+	}
+    }
+    return path;
 }
 
 static void init_outbuf(void)
@@ -838,6 +1274,114 @@ static void outbuf_append(const char* bu
     outbuf_in += n;
 }
 
+/* Call write() until entire buffer has been written or error.
+ * Return len or -1.
+ */
+static int write_all(int fd, const char* buf, int len)
+{
+    int left = len;
+    int written;
+    for (;;) {
+	written = sf_write(fd,buf,left);
+	if (written == left) {
+	    return len;
+	}
+	if (written < 0) {
+	    return -1;
+	}
+	left -= written;
+	buf += written;
+    }
+}
+
+static ssize_t sf_read(int fd, void *buffer, size_t len) {
+    ssize_t n = 0;
+
+    do { n = read(fd, buffer, len); } while (n < 0 && errno == EINTR);
+
+    return n;
+}
+
+static ssize_t sf_write(int fd, const void *buffer, size_t len) {
+    ssize_t n = 0;
+
+    do { n = write(fd, buffer, len); } while (n < 0 && errno == EINTR);
+
+    return n;
+}
+
+static int sf_open(const char *path, int type, mode_t mode) {
+    int fd = 0;
+
+    do { fd = open(path, type, mode); } while(fd < 0 && errno == EINTR);
+
+    return fd;
+}
+static int sf_close(int fd) {
+    int res = 0;
+
+    do { res = close(fd); } while(fd < 0 && errno == EINTR);
+
+    return res;
+}
+/* Extract any control sequences that are ment only for run_erl
+ * and should not be forwarded to the pty.
+ */
+static int extract_ctrl_seq(char* buf, int len)
+{
+    static const char prefix[] = "\033_";
+    static const char suffix[] = "\033\\";
+    char* bufend = buf + len;
+    char* start = buf;
+    char* command;
+    char* end;
+    
+    for (;;) {
+	start = find_str(start, bufend-start, prefix);
+	if (!start) break;
+	
+	command = start + strlen(prefix);
+	end = find_str(command, bufend-command, suffix);
+	if (end) {
+	    unsigned col, row;
+	    if (sscanf(command,"version=%u", &protocol_ver)==1) {
+		/*fprintf(stderr,"to_erl v%u\n", protocol_ver);*/
+	    }
+	    else if (sscanf(command,"winsize=%u,%u", &col, &row)==2) {
+		set_window_size(col,row);
+	    }
+	    else {
+		ERROR2(LOG_ERR, "Ignoring unknown ctrl command '%.*s'\n",
+		       (int)(end-command), command);
+	    }
+	  
+	    /* Remove ctrl sequence from buf */
+	    end += strlen(suffix);
+	    memmove(start, end, bufend-end);
+	    bufend -= end - start;
+	}
+	else {
+	    ERROR2(LOG_ERR, "Missing suffix in ctrl sequence '%.*s'\n",
+		   (int)(bufend-start), start);
+	    break;
+	}
+    }
+    return bufend - buf;
+}
+
+static void set_window_size(unsigned col, unsigned row)
+{
+#ifdef TIOCSWINSZ	
+    struct winsize ws;
+    ws.ws_col = col;
+    ws.ws_row = row;
+    if (ioctl(mfd, TIOCSWINSZ, &ws) < 0) {
+	ERRNO_ERR0(LOG_ERR,"Failed to set window size");
+    }
+#endif
+}
+
+
 #ifdef DEBUG
 
 #define S(x)  ((x) > 0 ? 1 : 0)
diff -Ndurp otp_src_18.3.4.5/erts/etc/unix/run_erl.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/run_erl.h
--- otp_src_18.3.4.5/erts/etc/unix/run_erl.h	1970-01-01 03:00:00.000000000 +0300
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/run_erl.h	2017-02-03 21:52:59.163951269 +0200
@@ -0,0 +1,31 @@
+/*
+ * %CopyrightBegin%
+ * 
+ * Copyright Ericsson AB 2008-2009. All Rights Reserved.
+ * 
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ *     http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ * 
+ * %CopyrightEnd%
+ */
+
+/*
+ * The protocol version number used between to_erl and run_erl.
+ */
+#define RUN_ERL_HI_VER 1  /* My preferred protocol version */
+#define RUN_ERL_LO_VER 0  /* The lowest version I accept to talk with */
+
+/* Version history:
+ * 0: Older, without version handshake
+ * 1: R12B-3, version handshake + window size ctrl
+ */
+
diff -Ndurp otp_src_18.3.4.5/erts/etc/unix/safe_string.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/safe_string.c
--- otp_src_18.3.4.5/erts/etc/unix/safe_string.c	1970-01-01 03:00:00.000000000 +0300
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/safe_string.c	2017-02-03 21:52:59.163951269 +0200
@@ -0,0 +1,124 @@
+/*
+ * %CopyrightBegin%
+ * 
+ * Copyright Ericsson AB 2008-2009. All Rights Reserved.
+ * 
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ *     http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ * 
+ * %CopyrightEnd%
+ */
+/* 
+ * Module: safe_string.c
+ * 
+ * This is a bunch of generic string operation
+ * that are safe regarding buffer overflow.
+ *
+ * All string functions terminate the process with an error message
+ * on buffer overflow.
+ */
+
+#ifdef HAVE_CONFIG_H
+#  include "config.h"
+#endif
+#include "safe_string.h"
+#include <stdio.h>
+#include <string.h>
+#include <stdarg.h>
+#include <stdlib.h>
+
+
+static void string_overflow_handler(const char* format, ...)
+{
+    va_list args;
+    va_start(args, format);
+    vfprintf(stderr,format,args);
+    va_end(args);
+    exit(1);
+}
+
+int vsn_printf(char* dst, size_t size, const char* format, va_list args)
+{
+    int ret = vsnprintf(dst, size, format, args);
+    if (ret >= size || ret < 0) {
+	string_overflow_handler("Buffer truncated '%s'\n",dst);
+    }
+    return ret;
+}
+
+int sn_printf(char* dst, size_t size, const char* format, ...)
+{
+    va_list args;
+    int ret;
+    va_start(args, format);
+    ret = vsn_printf(dst,size,format,args);
+    va_end(args);
+    return ret;
+}
+
+int strn_cpy(char* dst, size_t size, const char* src)
+{
+    return sn_printf(dst,size,"%s",src);
+}
+
+int strn_cat(char* dst, size_t size, const char* src)
+{
+    return strn_catf(dst,size,"%s",src);
+}
+
+int strn_catf(char* dst, size_t size, const char* format, ...)
+{
+    int ret;
+    va_list args;
+#ifdef _GNU_SOURCE
+    int len = strnlen(dst,size);
+#else
+    int len = strlen(dst);
+#endif
+
+    if (len >= size) {
+	string_overflow_handler("Buffer already overflowed '%.*s'\n",
+				size, dst);
+    }
+    va_start(args, format);
+    ret = vsn_printf(dst+len, size-len, format, args);
+    va_end(args);
+    return len+ret;
+}
+
+char* find_str(const char* haystack, int hsize, const char* needle)
+{
+    int i = 0;
+    int nsize = strlen(needle);
+    hsize -= nsize - 1;
+    for (i=0; i<hsize; i++) {
+	if (haystack[i]==needle[0] && strncmp(haystack+i,needle,nsize)==0) {
+	    return (char*)(haystack+i);
+	}
+    }
+    return NULL;
+}
+
+#ifndef HAVE_MEMMOVE
+void* memmove(void *dest, const void *src, size_t n)
+{
+    int i;
+    if (src > dest) {
+	for (i=0; i<n; i++) ((char*)dest)[i] = ((char*)src)[i];
+    }
+    else {
+	for (i=(int)(n-1); i>=0; i--) ((char*)dest)[i] = ((char*)src)[i];
+    }
+    return dest;
+}
+#endif /* HAVE_MEMMOVE */
+
diff -Ndurp otp_src_18.3.4.5/erts/etc/unix/safe_string.h otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/safe_string.h
--- otp_src_18.3.4.5/erts/etc/unix/safe_string.h	1970-01-01 03:00:00.000000000 +0300
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/safe_string.h	2017-02-03 21:52:59.163951269 +0200
@@ -0,0 +1,66 @@
+/*
+ * %CopyrightBegin%
+ * 
+ * Copyright Ericsson AB 2008-2009. All Rights Reserved.
+ * 
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ *     http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ * 
+ * %CopyrightEnd%
+ */
+/* 
+ * Module: safe_string.h
+ * 
+ * This is an interface to a bunch of generic string operation
+ * that are safe regarding buffer overflow.
+ *
+ * All string functions terminate the process with an error message
+ * on buffer overflow.
+ */
+
+#include <stdio.h>
+#include <stdarg.h>
+
+/* Like vsnprintf()
+ */
+int vsn_printf(char* dst, size_t size, const char* format, va_list args);
+
+/* Like snprintf()
+ */
+int sn_printf(char* dst, size_t size, const char* format, ...);
+
+/* Like strncpy()
+ * Returns length of copied string.
+ */
+int strn_cpy(char* dst, size_t size, const char* src);
+
+/* Almost like strncat()
+ * size is sizeof entire dst buffer.
+ * Returns length of resulting string.
+ */
+int strn_cat(char* dst, size_t size, const char* src);
+
+/* Combination of strncat() and snprintf()
+ * size is sizeof entire dst buffer.
+ * Returns length of resulting string.
+ */
+int strn_catf(char* dst, size_t size, const char* format, ...);
+
+/* Simular to strstr() but search size bytes of haystack
+ * without regard to '\0' characters.
+ */
+char* find_str(const char* haystack, int size, const char* needle);
+
+#ifndef HAVE_MEMMOVE
+void* memmove(void *dest, const void *src, size_t n);
+#endif
+
diff -Ndurp otp_src_18.3.4.5/erts/etc/unix/to_erl.c otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/to_erl.c
--- otp_src_18.3.4.5/erts/etc/unix/to_erl.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/etc/unix/to_erl.c	2017-02-03 21:52:59.163951269 +0200
@@ -1,7 +1,7 @@
 /*
  * %CopyrightBegin%
  * 
- * Copyright Ericsson AB 1996-2013. All Rights Reserved.
+ * Copyright Ericsson AB 1996-2015. All Rights Reserved.
  * 
  * Licensed under the Apache License, Version 2.0 (the "License");
  * you may not use this file except in compliance with the License.
@@ -17,9 +17,592 @@
  * 
  * %CopyrightEnd%
  */
+/* 
+ * Module: to_erl.c
+ * 
+ * This module implements a process that opens two specified FIFOs, one
+ * for reading and one for writing; reads from its stdin, and writes what
+ * it has read to the write FIF0; reads from the read FIFO, and writes to
+ * its stdout.
+ *
+  ________                            _________ 
+ |        |--<-- pipe.r (fifo1) --<--|         |
+ | to_erl |                          | run_erl | (parent)
+ |________|-->-- pipe.w (fifo2) -->--|_________|
+                                          ^ master pty
+                                          |
+                                          | slave pty
+                                      ____V____ 
+                                     |         |
+                                     |  "erl"  | (child)
+                                     |_________|
+ */
+#ifdef HAVE_CONFIG_H
+#  include "config.h"
+#endif
 
-#include "to_erl_common.h"
+#include <sys/types.h>
+#include <sys/stat.h>
+#include <sys/time.h>
+#include <sys/types.h>
+#include <fcntl.h>
+#include <unistd.h>
+#include <stdio.h>
+#include <stdlib.h>
+#include <string.h>
+#include <termios.h>
+#include <dirent.h>
+#include <signal.h>
+#include <errno.h>
+#ifdef HAVE_SYS_IOCTL_H
+#  include <sys/ioctl.h>
+#endif
 
-int main(int argc,char **argv) {
-  return to_erl(argc,argv);
+#include "run_erl.h"
+#include "safe_string.h"   /* strn_cpy, strn_catf, sn_printf, etc. */
+
+#if defined(O_NONBLOCK)
+# define DONT_BLOCK_PLEASE O_NONBLOCK
+#else
+# define DONT_BLOCK_PLEASE O_NDELAY
+# if !defined(EAGAIN)
+#  define EAGAIN -3898734
+# endif
+#endif
+
+#ifdef HAVE_STRERROR
+#  define STRERROR(x) strerror(x)
+#else
+#  define STRERROR(x) ""
+#endif
+
+#define noDEBUG
+
+#define PIPE_DIR        "/tmp/"
+#define PIPE_STUBNAME   "erlang.pipe"
+#define PIPE_STUBLEN    strlen(PIPE_STUBNAME)
+
+#ifdef DEBUG
+#define STATUS(s)  { fprintf(stderr, (s)); fflush(stderr); }
+#else
+#define STATUS(s)
+#endif
+
+#ifndef FILENAME_MAX
+#define FILENAME_MAX 250
+#endif
+
+static struct termios tty_smode, tty_rmode;
+static int tty_eof = 0;
+static int recv_sig = 0;
+static int protocol_ver = RUN_ERL_LO_VER; /* assume lowest to begin with */
+
+static int write_all(int fd, const char* buf, int len);
+static int window_size_seq(char* buf, size_t bufsz);
+static int version_handshake(char* buf, int len, int wfd);
+#ifdef DEBUG
+static void show_terminal_settings(struct termios *);
+#endif
+
+static void handle_ctrlc(int sig)
+{
+    /* Reinstall the handler, and signal break flag */
+    signal(SIGINT,handle_ctrlc);
+    recv_sig = SIGINT;
+}  
+
+static void handle_sigwinch(int sig)
+{
+    recv_sig = SIGWINCH;
+}
+
+static void usage(char *pname)
+{
+    fprintf(stderr, "Usage: %s [-h|-F] [pipe_name|pipe_dir/]\n", pname);
+    fprintf(stderr, "\t-h\tThis help text.\n");
+    fprintf(stderr, "\t-F\tForce connection even though pipe is locked by other to_erl process.\n");
 }
+
+int main(int argc, char **argv)
+{
+    char  FIFO1[FILENAME_MAX], FIFO2[FILENAME_MAX];
+    int i, len, wfd, rfd;
+    fd_set readfds;
+    char buf[BUFSIZ];
+    char pipename[FILENAME_MAX];
+    int pipeIx = 1;
+    int force_lock = 0;
+    int got_some = 0;
+
+    if (argc >= 2 && argv[1][0]=='-') {
+	switch (argv[1][1]) {
+	case 'h':
+	    usage(argv[0]);
+	    exit(1);
+	case 'F':
+	    force_lock = 1;
+	    break;
+	default:
+	    fprintf(stderr,"Invalid option '%s'\n",argv[1]);
+	    exit(1);
+	}
+	pipeIx = 2;
+    }
+    
+#ifdef DEBUG
+    fprintf(stderr, "%s: pid is : %d\n", argv[0], (int)getpid());
+#endif
+    
+    strn_cpy(pipename, sizeof(pipename),
+	     (argv[pipeIx] ? argv[pipeIx] : PIPE_DIR));
+    
+    if(*pipename && pipename[strlen(pipename)-1] == '/') {
+	/* The user wishes us to find a pipe name in the specified */
+	/* directory */
+	int highest_pipe_num = 0;
+	DIR *dirp;
+	struct dirent *direntp;
+
+	dirp = opendir(pipename);
+	if(!dirp) {
+	    fprintf(stderr, "Can't access pipe directory %s: %s\n", pipename, strerror(errno));
+	    exit(1);
+	}
+
+	/* Check the directory for existing pipes */
+    
+	while((direntp=readdir(dirp)) != NULL) {
+	    if(strncmp(direntp->d_name,PIPE_STUBNAME,PIPE_STUBLEN)==0) {
+		int num = atoi(direntp->d_name+PIPE_STUBLEN+1);
+		if(num > highest_pipe_num)
+		    highest_pipe_num = num;
+	    }
+	}	
+	closedir(dirp);
+	strn_catf(pipename, sizeof(pipename), (highest_pipe_num?"%s.%d":"%s"),
+		  PIPE_STUBNAME, highest_pipe_num);
+    } /* if */
+
+    /* read FIFO */
+    sn_printf(FIFO1,sizeof(FIFO1),"%s.r",pipename);
+    /* write FIFO */
+    sn_printf(FIFO2,sizeof(FIFO2),"%s.w",pipename);
+
+    /* Check that nobody is running to_erl on this pipe already */
+    if ((wfd = open (FIFO1, O_WRONLY|DONT_BLOCK_PLEASE, 0)) >= 0) {
+	/* Open as server succeeded -- to_erl is already running! */
+	close(wfd);
+	fprintf(stderr, "Another to_erl process already attached to pipe "
+			"%s.\n", pipename);
+	if (force_lock) {
+	    fprintf(stderr, "But we proceed anyway by force (-F).\n");
+	} 
+	else {
+	    exit(1);
+	}
+    }
+
+    if ((rfd = open (FIFO1, O_RDONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
+#ifdef DEBUG
+	fprintf(stderr, "Could not open FIFO %s for reading.\n", FIFO1);
+#endif
+	fprintf(stderr, "No running Erlang on pipe %s: %s\n", pipename, strerror(errno));
+	exit(1);
+    }
+#ifdef DEBUG
+    fprintf(stderr, "to_erl: %s opened for reading\n", FIFO1);
+#endif
+    
+    if ((wfd = open (FIFO2, O_WRONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
+#ifdef DEBUG
+	fprintf(stderr, "Could not open FIFO %s for writing.\n", FIFO2);
+#endif
+	fprintf(stderr, "No running Erlang on pipe %s: %s\n", pipename, strerror(errno));
+	close(rfd);
+	exit(1);
+    }
+#ifdef DEBUG
+    fprintf(stderr, "to_erl: %s opened for writing\n", FIFO2);
+#endif
+    
+    fprintf(stderr, "Attaching to %s (^D to exit)\n\n", pipename);
+    
+    /* Set break handler to our handler */
+    signal(SIGINT,handle_ctrlc);
+
+    /* 
+     * Save the current state of the terminal, and set raw mode.
+     */
+    if (tcgetattr(0, &tty_rmode) , 0) {
+	fprintf(stderr, "Cannot get terminals current mode\n");
+	exit(-1);
+    }
+    tty_smode = tty_rmode;
+    tty_eof = '\004'; /* Ctrl+D to exit */
+#ifdef DEBUG
+    show_terminal_settings(&tty_rmode);
+#endif
+    tty_smode.c_iflag =
+	1*BRKINT |/*Signal interrupt on break.*/
+	    1*IGNPAR |/*Ignore characters with parity errors.*/
+		1*ISTRIP |/*Strip character.*/
+		    0;
+    
+#if 0
+0*IGNBRK |/*Ignore break condition.*/
+0*PARMRK |/*Mark parity errors.*/
+0*INPCK  |/*Enable input parity check.*/
+0*INLCR  |/*Map NL to CR on input.*/
+0*IGNCR  |/*Ignore CR.*/
+0*ICRNL  |/*Map CR to NL on input.*/
+0*IUCLC  |/*Map upper-case to lower-case on input.*/
+0*IXON   |/*Enable start/stop output control.*/
+0*IXANY  |/*Enable any character to restart output.*/
+0*IXOFF  |/*Enable start/stop input control.*/
+0*IMAXBEL|/*Echo BEL on input line too long.*/
+#endif
+						
+    tty_smode.c_oflag =
+	1*OPOST  |/*Post-process output.*/
+	    1*ONLCR  |/*Map NL to CR-NL on output.*/
+#ifdef XTABS
+		1*XTABS  |/*Expand tabs to spaces. (Linux)*/
+#endif
+#ifdef OXTABS
+		    1*OXTABS  |/*Expand tabs to spaces. (FreeBSD)*/
+#endif
+#ifdef NL0
+			1*NL0    |/*Select newline delays*/
+#endif
+#ifdef CR0
+			    1*CR0    |/*Select carriage-return delays*/
+#endif
+#ifdef TAB0
+				1*TAB0   |/*Select horizontal tab delays*/
+#endif
+#ifdef BS0
+				    1*BS0    |/*Select backspace delays*/
+#endif
+#ifdef VT0
+					1*VT0    |/*Select vertical tab delays*/
+#endif
+#ifdef FF0
+					    1*FF0    |/*Select form feed delays*/
+#endif
+											    0;
+    
+#if 0
+0*OLCUC  |/*Map lower case to upper on output.*/
+0*OCRNL  |/*Map CR to NL on output.*/
+0*ONOCR  |/*No CR output at column 0.*/
+0*ONLRET |/*NL performs CR function.*/
+0*OFILL  |/*Use fill characters for delay.*/
+0*OFDEL  |/*Fill is DEL, else NULL.*/
+0*NL1    |
+0*CR1    |
+0*CR2    |
+0*CR3    |
+0*TAB1   |
+0*TAB2   |
+0*TAB3   |/*Expand tabs to spaces.*/
+0*BS1    |
+0*VT1    |
+0*FF1    |
+#endif
+								    
+    /* JALI: removed setting the tty_smode.c_cflag flags, since this is not */
+    /* advisable if this is a *real* terminal, such as the console. In fact */
+    /* this may hang the entire machine, deep, deep down (signalling break */
+    /* or toggling the abort switch doesn't help) */
+    
+    tty_smode.c_lflag =
+									0;
+    
+#if 0
+0*ISIG   |/*Enable signals.*/
+0*ICANON |/*Canonical input (erase and kill processing).*/
+0*XCASE  |/*Canonical upper/lower presentation.*/
+0*ECHO   |/*Enable echo.*/
+0*ECHOE  |/*Echo erase character as BS-SP-BS.*/
+0*ECHOK  |/*Echo NL after kill character.*/
+0*ECHONL |/*Echo NL.*/
+0*NOFLSH |/*Disable flush after interrupt or quit.*/
+0*TOSTOP |/*Send SIGTTOU for background output.*/
+0*ECHOCTL|/*Echo control characters as ^char, delete as ^?.*/
+0*ECHOPRT|/*Echo erase character as character erased.*/
+0*ECHOKE |/*BS-SP-BS erase entire line on line kill.*/
+0*FLUSHO |/*Output is being flushed.*/
+0*PENDIN |/*Retype pending input at next read or input character.*/
+0*IEXTEN |/*Enable extended (implementation-defined) functions.*/
+#endif
+								
+    tty_smode.c_cc[VMIN]      =0;/* Note that VMIN is the same as VEOF! */
+    tty_smode.c_cc[VTIME]     =0;/* Note that VTIME is the same as VEOL! */
+    tty_smode.c_cc[VINTR]     =3;
+    
+    tcsetattr(0, TCSADRAIN, &tty_smode);
+    
+#ifdef DEBUG
+    show_terminal_settings(&tty_smode);
+#endif
+    /*
+     * 	 "Write a ^L to the FIFO which causes the other end to redisplay
+     *    the input line."
+     * This does not seem to work as was intended in old comment above.
+     * However, this control character is now (R12B-3) used by run_erl
+     * to trigger the version handshaking between to_erl and run_erl
+     * at the start of every new to_erl-session.
+     */
+
+    if (write(wfd, "\014", 1) < 0) {
+	fprintf(stderr, "Error in writing ^L to FIFO.\n");
+    }
+
+    /*
+     * read and write
+     */
+    while (1) {
+	FD_ZERO(&readfds);
+	FD_SET(0, &readfds);
+	FD_SET(rfd, &readfds);
+	if (select(rfd + 1, &readfds, NULL, NULL, NULL) < 0) {
+	    if (recv_sig) {
+		FD_ZERO(&readfds);
+	    }
+	    else {
+		fprintf(stderr, "Error in select.\n");
+		break;
+	    }
+	}
+	len = 0;
+
+	/*
+	 * Read from terminal and write to FIFO
+         */
+	if (recv_sig) {
+	    switch (recv_sig) {
+	    case SIGINT:
+		fprintf(stderr, "[Break]\n\r");
+		buf[0] = '\003';
+		len = 1;
+		break;
+	    case SIGWINCH:
+		len = window_size_seq(buf,sizeof(buf));
+		break;
+	    default:
+		fprintf(stderr,"Unexpected signal: %u\n",recv_sig);
+	    }
+	    recv_sig = 0;
+	}
+	else if (FD_ISSET(0, &readfds)) {
+	    len = read(0, buf, sizeof(buf));
+	    if (len <= 0) {
+		close(rfd);
+		close(wfd);
+		if (len < 0) {
+		    fprintf(stderr, "Error in reading from stdin.\n");
+		} else {
+		    fprintf(stderr, "[EOF]\n\r");
+		}
+		break;
+	    }
+	    /* check if there is an eof character in input */
+	    for (i = 0; i < len && buf[i] != tty_eof; i++);
+	    if (buf[i] == tty_eof) {
+		fprintf(stderr, "[Quit]\n\r");
+		break;
+	    }
+	}
+
+	if (len) {
+#ifdef DEBUG
+	    if(write(1, buf, len));
+#endif
+	    if (write_all(wfd, buf, len) != len) {
+		fprintf(stderr, "Error in writing to FIFO.\n");
+		close(rfd);
+		close(wfd);
+		break;
+	    }
+	    STATUS("\" OK\r\n");
+	}
+
+	/*
+	 * Read from FIFO, write to terminal.
+	 */
+	if (FD_ISSET(rfd, &readfds)) {
+	    STATUS("FIFO read: ");
+	    len = read(rfd, buf, BUFSIZ);
+	    if (len < 0 && errno == EAGAIN) {
+		/*
+		 * No data this time, but the writing end of the FIFO is still open.
+		 * Do nothing.
+		 */
+		;
+	    } else if (len <= 0) {
+		/*
+		 * Either an error or end of file. In either case, break out
+		 * of the loop.
+		 */
+		close(rfd);
+		close(wfd);
+		if (len < 0) {
+		    fprintf(stderr, "Error in reading from FIFO.\n");
+		} else
+		    fprintf(stderr, "[End]\n\r");
+		break;
+	    } else {
+		if (!got_some) {
+		    if ((len=version_handshake(buf,len,wfd)) < 0) {
+			close(rfd);
+			close(wfd);
+			break;
+		    }
+		    if (protocol_ver >= 1) {
+			/* Tell run_erl size of terminal window */
+			signal(SIGWINCH, handle_sigwinch);
+			raise(SIGWINCH);
+		    }
+		    got_some = 1;
+		}
+
+		/*
+		 * We successfully read at least one character. Write what we got.
+		 */
+		STATUS("Terminal write: \"");
+		if (write_all(1, buf, len) != len) {
+		    fprintf(stderr, "Error in writing to terminal.\n");
+		    close(rfd);
+		    close(wfd);
+		    break;
+		}
+		STATUS("\" OK\r\n");
+	    }
+	}
+    }
+
+    /* 
+     * Reset terminal characterstics 
+     * XXX
+     */
+    tcsetattr(0, TCSADRAIN, &tty_rmode);
+    return 0;
+}
+
+/* Call write() until entire buffer has been written or error.
+ * Return len or -1.
+ */
+static int write_all(int fd, const char* buf, int len)
+{
+    int left = len;
+    int written;
+    while (left) {
+	written = write(fd,buf,left);
+	if (written < 0) {
+	    return -1;
+	}
+	left -= written;
+	buf += written;
+    }
+    return len;
+}
+
+static int window_size_seq(char* buf, size_t bufsz)
+{
+#ifdef TIOCGWINSZ
+    struct winsize ws;
+    static const char prefix[] = "\033_";
+    static const char suffix[] = "\033\\";
+    /* This Esc sequence is called "Application Program Command"
+       and seems suitable to use for our own customized stuff. */
+
+    if (ioctl(STDIN_FILENO, TIOCGWINSZ, &ws) == 0) {
+	int len = sn_printf(buf, bufsz, "%swinsize=%u,%u%s",
+			    prefix, ws.ws_col, ws.ws_row, suffix);
+	return len;
+    }
+#endif /* TIOCGWINSZ */
+    return 0;
+}
+
+/*   to_erl                     run_erl
+ *     |                           |
+ *     |---------- '\014' -------->| (session start)
+ *     |                           |
+ *     |<---- "[run_erl v1-0]" ----| (version interval)
+ *     |                           |
+ *     |--- Esc_"version=1"Esc\ -->| (common version)
+ *     |                           |
+ */
+static int version_handshake(char* buf, int len, int wfd)
+{
+    unsigned re_high=0, re_low;
+    char *end = find_str(buf,len,"]\n");
+    
+    if (end && sscanf(buf,"[run_erl v%u-%u",&re_high,&re_low)==2) {
+	char wbuf[30];
+	int wlen;
+
+	if (re_low > RUN_ERL_HI_VER || re_high < RUN_ERL_LO_VER) {
+	    fprintf(stderr,"Incompatible versions: to_erl=v%u-%u run_erl=v%u-%u\n",
+		    RUN_ERL_HI_VER, RUN_ERL_LO_VER, re_high, re_low);
+	    return -1;
+	}
+	/* Choose highest common version */
+	protocol_ver = re_high < RUN_ERL_HI_VER ? re_high : RUN_ERL_HI_VER;
+
+	wlen = sn_printf(wbuf, sizeof(wbuf), "\033_version=%u\033\\",
+			 protocol_ver);
+	if (write_all(wfd, wbuf, wlen) < 0) {
+	    fprintf(stderr,"Failed to send version handshake\n");
+	    return -1;
+	}
+	end += 2;
+	len -= (end-buf);
+	memmove(buf,end,len);
+
+    }
+    else {  /* we assume old run_erl without version handshake */
+	protocol_ver = 0;
+    }
+
+    if (re_high != RUN_ERL_HI_VER) {
+	fprintf(stderr,"run_erl has different version, "
+		"using common protocol level %u\n", protocol_ver);
+    }
+
+    return len;
+}
+
+
+#ifdef DEBUG
+#define S(x)  ((x) > 0 ? 1 : 0)
+
+static void show_terminal_settings(struct termios *t)
+{
+  fprintf(stderr,"c_iflag:\n");
+  fprintf(stderr,"Signal interrupt on break:   BRKINT  %d\n", S(t->c_iflag & BRKINT));
+  fprintf(stderr,"Map CR to NL on input:       ICRNL   %d\n", S(t->c_iflag & ICRNL));
+  fprintf(stderr,"Ignore break condition:      IGNBRK  %d\n", S(t->c_iflag & IGNBRK));
+  fprintf(stderr,"Ignore CR:                   IGNCR   %d\n", S(t->c_iflag & IGNCR));
+  fprintf(stderr,"Ignore char with par. err's: IGNPAR  %d\n", S(t->c_iflag & IGNPAR));
+  fprintf(stderr,"Map NL to CR on input:       INLCR   %d\n", S(t->c_iflag & INLCR));
+  fprintf(stderr,"Enable input parity check:   INPCK   %d\n", S(t->c_iflag & INPCK));
+  fprintf(stderr,"Strip character              ISTRIP  %d\n", S(t->c_iflag & ISTRIP));
+  fprintf(stderr,"Enable start/stop input ctrl IXOFF   %d\n", S(t->c_iflag & IXOFF));
+  fprintf(stderr,"ditto output ctrl            IXON    %d\n", S(t->c_iflag & IXON));
+  fprintf(stderr,"Mark parity errors           PARMRK  %d\n", S(t->c_iflag & PARMRK));
+  fprintf(stderr,"\n");
+  fprintf(stderr,"c_oflag:\n");
+  fprintf(stderr,"Perform output processing    OPOST   %d\n", S(t->c_oflag & OPOST));
+  fprintf(stderr,"\n");
+  fprintf(stderr,"c_cflag:\n");
+  fprintf(stderr,"Ignore modem status lines    CLOCAL  %d\n", S(t->c_cflag & CLOCAL));
+  fprintf(stderr,"\n");
+  fprintf(stderr,"c_local:\n");
+  fprintf(stderr,"Enable echo                  ECHO    %d\n", S(t->c_lflag & ECHO));
+  fprintf(stderr,"\n");
+  fprintf(stderr,"c_cc:\n");
+  fprintf(stderr,"c_cc[VEOF]                           %d\n", t->c_cc[VEOF]);
+}
+#endif
diff -Ndurp otp_src_18.3.4.5/erts/include/internal/ethread.h otp_src_18.3.4.5-remove-OSE-port/erts/include/internal/ethread.h
--- otp_src_18.3.4.5/erts/include/internal/ethread.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/include/internal/ethread.h	2017-02-03 21:52:59.163951269 +0200
@@ -194,28 +194,6 @@ typedef DWORD ethr_tsd_key;
 
 #define ETHR_YIELD() (Sleep(0), 0)
 
-#elif defined(ETHR_OSE_THREADS)
-
-#include "ose.h"
-#undef NIL
-
-#if defined(ETHR_HAVE_PTHREAD_H)
-#include <pthread.h>
-#endif
-
-typedef struct {
-  PROCESS id;
-  unsigned int tsd_key_index;
-  void *res;
-} ethr_tid;
-
-typedef OSPPDKEY ethr_tsd_key;
-
-#undef ETHR_HAVE_ETHR_SIG_FUNCS
-
-/* Out own RW mutexes are probably faster, but use OSEs mutexes */
-#define ETHR_USE_OWN_RWMTX_IMPL__
-
 #else /* No supported thread lib found */
 
 #ifdef ETHR_NO_SUPP_THR_LIB_NOT_FATAL
@@ -383,19 +361,7 @@ extern ethr_runtime_t ethr_runtime__;
 
 #include "ethr_atomics.h" /* The atomics API */
 
-#if defined (ETHR_OSE_THREADS)
-static ETHR_INLINE void
-ose_yield(void)
-{
-    if (get_ptype(current_process()) == OS_PRI_PROC) {
-        set_pri(get_pri(current_process()));
-    } else {
-        delay(1);
-    }
-}
-#endif
-
-#if defined(__GNUC__) && !defined(ETHR_OSE_THREADS)
+#if defined(__GNUC__)
 #  ifndef ETHR_SPIN_BODY
 #    if defined(__i386__) || defined(__x86_64__)
 #      define ETHR_SPIN_BODY __asm__ __volatile__("rep;nop" : : : "memory")
@@ -411,20 +377,9 @@ ose_yield(void)
 #  ifndef ETHR_SPIN_BODY
 #    define ETHR_SPIN_BODY do {YieldProcessor();ETHR_COMPILER_BARRIER;} while(0)
 #  endif
-#elif defined(ETHR_OSE_THREADS)
-#  ifndef ETHR_SPIN_BODY
-#    define ETHR_SPIN_BODY ose_yield()
-#  else
-#    error "OSE should use ose_yield()"
-#  endif
 #endif
 
-#ifndef ETHR_OSE_THREADS
 #define ETHR_YIELD_AFTER_BUSY_LOOPS 50
-#else
-#define ETHR_YIELD_AFTER_BUSY_LOOPS 0
-#endif
-
 
 #ifndef ETHR_SPIN_BODY
 #  define ETHR_SPIN_BODY ETHR_COMPILER_BARRIER
@@ -447,18 +402,13 @@ ose_yield(void)
 #    else
 #      define ETHR_YIELD() (pthread_yield(), 0)
 #    endif
-#  elif defined(ETHR_OSE_THREADS)
-#    define ETHR_YIELD() (ose_yield(), 0)
 #  else
 #    define ETHR_YIELD() (ethr_compiler_barrier(), 0)
 #  endif
 #endif
 
-#if defined(VALGRIND) || defined(ETHR_OSE_THREADS)
-/* mutex as fallback for spinlock for VALGRIND and OSE.
-   OSE cannot use spinlocks as processes working on the
-   same execution unit have a tendency to deadlock.
- */
+#if defined(VALGRIND)
+/* mutex as fallback for spinlock for VALGRIND. */
 #  undef ETHR_HAVE_NATIVE_SPINLOCKS
 #  undef ETHR_HAVE_NATIVE_RWSPINLOCKS
 #else
@@ -505,16 +455,9 @@ typedef struct {
     int detached;			/* boolean (default false) */
     int suggested_stack_size;		/* kilo words (default sys dependent) */
     char *name;                         /* max 14 char long (default no-name) */
-#ifdef ETHR_OSE_THREADS
-    U32 coreNo;
-#endif
 } ethr_thr_opts;
 
-#if defined(ETHR_OSE_THREADS)
-#define ETHR_THR_OPTS_DEFAULT_INITER {0, -1, NULL, 0}
-#else
 #define ETHR_THR_OPTS_DEFAULT_INITER {0, -1, NULL}
-#endif
 
 #if !defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHR_AUX_IMPL__)
 #  define ETHR_NEED_SPINLOCK_PROTOTYPES__
@@ -628,8 +571,6 @@ typedef struct ethr_ts_event_ ethr_ts_ev
 #  include "win/ethr_event.h"
 #elif defined(ETHR_PTHREADS)
 #  include "pthread/ethr_event.h"
-#elif defined(ETHR_OSE_THREADS)
-#  include "ose/ethr_event.h"
 #endif
 
 int ethr_set_main_thr_status(int, int);
@@ -701,37 +642,6 @@ ETHR_INLINE_FUNC_NAME_(ethr_get_ts_event
     if (!tsep) {
 	int res = ethr_get_tmp_ts_event__(&tsep);
 	if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-	ETHR_ASSERT(tsep);
-    }
-    return tsep;
-}
-
-static ETHR_INLINE void
-ETHR_INLINE_FUNC_NAME_(ethr_leave_ts_event)(ethr_ts_event *tsep)
-{
-    if (tsep->iflgs & ETHR_TS_EV_TMP) {
-	int res = ethr_free_ts_event__(tsep);
-	if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-    }
-}
-
-#endif
-
-#elif  defined (ETHR_OSE_THREADS)
-
-#if defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHREAD_IMPL__)
-
-extern ethr_tsd_key ethr_ts_event_key__;
-
-static ETHR_INLINE ethr_ts_event *
-ETHR_INLINE_FUNC_NAME_(ethr_get_ts_event)(void)
-{
-    ethr_ts_event *tsep = *(ethr_ts_event**)ose_get_ppdata(ethr_ts_event_key__);
-    if (!tsep) {
-	int res = ethr_get_tmp_ts_event__(&tsep);
-	if (res != 0)
 	    ETHR_FATAL_ERROR__(res);
 	ETHR_ASSERT(tsep);
     }
diff -Ndurp otp_src_18.3.4.5/erts/include/internal/ethr_mutex.h otp_src_18.3.4.5-remove-OSE-port/erts/include/internal/ethr_mutex.h
--- otp_src_18.3.4.5/erts/include/internal/ethr_mutex.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/include/internal/ethr_mutex.h	2017-02-03 21:52:59.163951269 +0200
@@ -98,7 +98,7 @@ void LeaveCriticalSection(CRITICAL_SECTI
 #if 0
 #  define ETHR_MTX_Q_LOCK_SPINLOCK__
 #  define ETHR_MTX_QLOCK_TYPE__ ethr_spinlock_t
-#elif defined(ETHR_PTHREADS) || defined(ETHR_OSE_THREADS)
+#elif defined(ETHR_PTHREADS)
 #  define ETHR_MTX_Q_LOCK_PTHREAD_MUTEX__
 #  define ETHR_MTX_QLOCK_TYPE__ pthread_mutex_t
 #elif defined(ETHR_WIN32_THREADS)
@@ -211,7 +211,7 @@ struct ethr_cond_ {
 #endif
 };
 
-#elif (defined(ETHR_PTHREADS) || defined(ETHR_OSE_THREADS)) && !defined(ETHR_DBG_WIN_MTX_WITH_PTHREADS)
+#elif defined(ETHR_PTHREADS) && !defined(ETHR_DBG_WIN_MTX_WITH_PTHREADS)
 
 typedef struct ethr_mutex_ ethr_mutex;
 struct ethr_mutex_ {
@@ -355,7 +355,7 @@ void ethr_rwmutex_rwunlock(ethr_rwmutex
 
 #ifdef ETHR_MTX_HARD_DEBUG
 #define ETHR_MTX_HARD_ASSERT(A) \
-  ((void) ((A) ? 1 : ethr_assert_failed(__FILE__, __LINE__, __func__,#A)))
+  ((void) ((A) ? 1 : ethr_assert_failed(__FILE__, __LINE__, __func__, #A)))
 #else
 #define ETHR_MTX_HARD_ASSERT(A) ((void) 1)
 #endif
@@ -634,7 +634,7 @@ ETHR_INLINE_MTX_FUNC_NAME_(ethr_mutex_un
 
 #endif /* ETHR_TRY_INLINE_FUNCS */
 
-#elif (defined(ETHR_PTHREADS) || defined(ETHR_OSE_THREADS)) && !defined(ETHR_DBG_WIN_MTX_WITH_PTHREADS)
+#elif defined(ETHR_PTHREADS) && !defined(ETHR_DBG_WIN_MTX_WITH_PTHREADS)
 
 #if defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHR_MUTEX_IMPL__)
 
diff -Ndurp otp_src_18.3.4.5/erts/include/internal/ose/ethr_event.h otp_src_18.3.4.5-remove-OSE-port/erts/include/internal/ose/ethr_event.h
--- otp_src_18.3.4.5/erts/include/internal/ose/ethr_event.h	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/include/internal/ose/ethr_event.h	1970-01-01 03:00:00.000000000 +0300
@@ -1,114 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2009-2011. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-/*
- * Author: Rickard Green
- */
-
-//#define USE_PTHREAD_API
-
-#define ETHR_EVENT_OFF_WAITER__		-1L
-#define ETHR_EVENT_OFF__		1L
-#define ETHR_EVENT_ON__ 		0L
-
-#ifdef USE_PTHREAD_API
-
-typedef struct {
-    ethr_atomic32_t state;
-    pthread_mutex_t mtx;
-    pthread_cond_t cnd;
-} ethr_event;
-
-#if defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHR_EVENT_IMPL__)
-
-static void ETHR_INLINE
-ETHR_INLINE_FUNC_NAME_(ethr_event_set)(ethr_event *e)
-{
-    ethr_sint32_t val;
-    val = ethr_atomic32_xchg_mb(&e->state, ETHR_EVENT_ON__);
-    if (val == ETHR_EVENT_OFF_WAITER__) {
-	int res = pthread_mutex_lock(&e->mtx);
-	if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-	res = pthread_cond_signal(&e->cnd);
-	if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-	res = pthread_mutex_unlock(&e->mtx);
-	if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-    }
-}
-
-static void ETHR_INLINE
-ETHR_INLINE_FUNC_NAME_(ethr_event_reset)(ethr_event *e)
-{
-    ethr_atomic32_set(&e->state, ETHR_EVENT_OFF__);
-    ETHR_MEMORY_BARRIER;
-}
-
-#endif
-
-#else
-
-typedef struct {
-    ethr_atomic32_t state;
-    PROCESS proc;
-} ethr_event;
-
-#if defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHR_EVENT_IMPL__)
-
-static void ETHR_INLINE
-ETHR_INLINE_FUNC_NAME_(ethr_event_set)(ethr_event *e)
-{
-    ethr_sint32_t val = ethr_atomic32_xchg_mb(&e->state, ETHR_EVENT_ON__);
-    if (val == ETHR_EVENT_OFF_WAITER__) {
-#ifdef DEBUG
-      OSFSEMVAL fsem_val = get_fsem(e->proc);
-
-      /* There is a race in this assert.
-	 This is because the state is set before the wait call in wait__.
-	 We hope that a delay of 10 ms is enough */
-      if (fsem_val == 0)
-	delay(10);
-      ETHR_ASSERT(get_fsem(e->proc) == -1);
-#endif
-      signal_fsem(e->proc);
-    }
-}
-
-static void ETHR_INLINE
-ETHR_INLINE_FUNC_NAME_(ethr_event_reset)(ethr_event *e)
-{
-    ethr_atomic32_set(&e->state, ETHR_EVENT_OFF__);
-    ETHR_MEMORY_BARRIER;
-}
-
-#endif
-
-#endif
-
-int ethr_event_init(ethr_event *e);
-int ethr_event_destroy(ethr_event *e);
-int ethr_event_wait(ethr_event *e);
-int ethr_event_swait(ethr_event *e, int spincount);
-#if !defined(ETHR_TRY_INLINE_FUNCS) || defined(ETHR_EVENT_IMPL__)
-void ethr_event_set(ethr_event *e);
-void ethr_event_reset(ethr_event *e);
-#endif
diff -Ndurp otp_src_18.3.4.5/erts/lib_src/common/erl_misc_utils.c otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/common/erl_misc_utils.c
--- otp_src_18.3.4.5/erts/lib_src/common/erl_misc_utils.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/common/erl_misc_utils.c	2017-02-03 21:52:59.163951269 +0200
@@ -160,8 +160,6 @@ erts_milli_sleep(long ms)
     if (ms > 0) {
 #ifdef __WIN32__
 	Sleep((DWORD) ms);
-#elif defined(__OSE__)
-	delay(ms);
 #else
 	struct timeval tv;
 	tv.tv_sec = ms / 1000;
@@ -320,10 +318,6 @@ erts_cpu_info_update(erts_cpu_info_t *cp
 	    online = 0;
 #endif
     }
-#elif defined(__OSE__)
-    online = ose_num_cpus();
-    configured = ose_num_cpus();
-    available = ose_num_cpus();
 #endif
 
     if (online > configured)
diff -Ndurp otp_src_18.3.4.5/erts/lib_src/common/ethr_aux.c otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/common/ethr_aux.c
--- otp_src_18.3.4.5/erts/lib_src/common/ethr_aux.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/common/ethr_aux.c	2017-02-03 21:52:59.163951269 +0200
@@ -207,18 +207,7 @@ ethr_init_common__(ethr_init_data *id)
 
     ethr_min_stack_size__ = ETHR_B2KW(ethr_min_stack_size__);
 
-#ifdef __OSE__
-    /* For supervisor processes, OSE adds a number of bytes to the requested stack. With this
-     * addition, the resulting size must not exceed the largest available stack size. The number
-     * of bytes that will be added  is configured in the monolith and can therefore not be
-     * specified here. We simply assume that it is less than 0x1000. The available stack sizes
-     * are configured in the .lmconf file and the largest one is usually 65536 bytes.
-     * Consequently, the requested stack size is limited to 0xF000.
-     */
-    ethr_max_stack_size__ = 0xF000;
-#else
     ethr_max_stack_size__ = 32*1024*1024;
-#endif
 #if SIZEOF_VOID_P == 8
     ethr_max_stack_size__ *= 2;
 #endif
@@ -664,10 +653,6 @@ ETHR_IMPL_NORETURN__ ethr_fatal_error__(
 int ethr_assert_failed(const char *file, int line, const char *func, char *a)
 {
     fprintf(stderr, "%s:%d: %s(): Assertion failed: %s\n", file, line, func, a);
-#ifdef __OSE__
-    ramlog_printf("%d: %s:%d: %s(): Assertion failed: %s\n",
-		  current_process(),file, line, func, a);
-#endif
     ethr_abort__();
     return 0;
 }
diff -Ndurp otp_src_18.3.4.5/erts/lib_src/common/ethr_mutex.c otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/common/ethr_mutex.c
--- otp_src_18.3.4.5/erts/lib_src/common/ethr_mutex.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/common/ethr_mutex.c	2017-02-03 21:52:59.167951112 +0200
@@ -1250,7 +1250,7 @@ ethr_cond_wait(ethr_cond *cnd, ethr_mute
     return 0;
 }
 
-#elif (defined(ETHR_PTHREADS) || defined(ETHR_OSE_THREADS)) && !defined(ETHR_DBG_WIN_MTX_WITH_PTHREADS)
+#elif defined(ETHR_PTHREADS) && !defined(ETHR_DBG_WIN_MTX_WITH_PTHREADS)
 /* -- pthread mutex and condition variables -------------------------------- */
 
 int
diff -Ndurp otp_src_18.3.4.5/erts/lib_src/ose/ethread.c otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/ose/ethread.c
--- otp_src_18.3.4.5/erts/lib_src/ose/ethread.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/ose/ethread.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,833 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2010-2011. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-/*
- * Description: OSE implementation of the ethread library
- * Author: Lukas Larsson
- */
-
-
-#ifdef HAVE_CONFIG_H
-#include "config.h"
-#endif
-
-#include "stdio.h"
-#ifdef ETHR_TIME_WITH_SYS_TIME
-#  include "time.h"
-#  include "sys/time.h"
-#else
-#  ifdef ETHR_HAVE_SYS_TIME_H
-#    include "sys/time.h"
-#  else
-#    include "time.h"
-#  endif
-#endif
-#include "sys/types.h"
-#include "unistd.h"
-
-#include "limits.h"
-
-#define ETHR_INLINE_FUNC_NAME_(X) X ## __
-#define ETHREAD_IMPL__
-
-#include "ethread.h"
-#include "ethr_internal.h"
-
-#include "erl_printf.h"
-#include "efs.h"
-#include "ose.h"
-
-#include "ose_spi.h"
-
-#include "string.h"
-#include "ctype.h"
-#include "stdlib.h"
-
-#ifndef ETHR_HAVE_ETHREAD_DEFINES
-#error Missing configure defines
-#endif
-
-#define ETHR_INVALID_TID_ID -1
-
-#define DEFAULT_PRIO_NAME        "ERTS_ETHR_DEFAULT_PRIO"
-
-/* Set the define to 1 to get some logging */
-#if 0
-#include "ramlog.h"
-#define LOG(output) ramlog_printf output
-#else
-#define LOG(output)
-#endif
-
-static ethr_tid main_thr_tid;
-static const char* own_tid_key = "ethread_own_tid";
-ethr_tsd_key ethr_ts_event_key__;
-
-#define ETHREADWRAPDATASIG 1
-
-/* Init data sent to thr_wrapper() */
-typedef struct {
-    SIGSELECT sig_no;
-    ethr_ts_event *tse;
-    ethr_tid *tid;
-    ethr_sint32_t result;
-    void *(*thr_func)(void *);
-    void *arg;
-    void *prep_func_res;
-    const char *name;
-} ethr_thr_wrap_data__;
-
-union SIGNAL {
-  SIGSELECT sig_no;
-  ethr_thr_wrap_data__ data;
-};
-
-#define ETHR_GET_OWN_TID__	((ethr_tid *) get_envp(current_process(),\
-						       own_tid_key))
-
-/*
- * --------------------------------------------------------------------------
- * Static functions
- * --------------------------------------------------------------------------
- */
-
-/* Will retrive the instrinsic name by removing the 'prefix' and the
- * suffix from 'name'.
- * The 'prefix' is given as an inparameter. If NULL or an empty string no
- * prefix will be removed.
- * If 'strip_suffix' is 1 suffixes in the form of '_123' will be removed.
- * Will return a pointer to a newly allocated buffer containing the intrinsic
- * name in uppercase characters.
- * The caller must remember to free this buffer when no lnger needed.
- */
-static char *
-ethr_intrinsic_name(const char *name, const char *prefix, int strip_suffix)
-{
-   const char *start = name;
-   const char *end  = name + strlen(name);
-   char *intrinsic_name = NULL;
-   int i;
-
-   if (name == NULL) {
-      LOG(("ERTS - ethr_intrinsic_namNo input name.\n"));
-      return NULL;
-   }
-
-   /* take care of the prefix */
-   if ((prefix != NULL) && (*prefix != '\0')) {
-      const char *found = strstr(name, prefix);
-
-      if (found == name) {
-         /* found the prefix at the beginning */
-         start += strlen(prefix);
-      }
-   }
-
-   /* take care of the suffix */
-   if (strip_suffix) {
-      const char *suffix_start = strrchr(start, '_');
-
-      if (suffix_start != NULL) {
-         const char *ch;
-         int only_numbers = 1;
-
-         for (ch = suffix_start + 1; *ch != '\0'; ch++) {
-            if (strchr("0123456789", *ch) == NULL) {
-               only_numbers = 0;
-               break;
-            }
-         }
-
-         if (only_numbers) {
-            end = suffix_start;
-         }
-      }
-   }
-
-   intrinsic_name = malloc(end - start + 1);
-   for (i = 0; (start + i) < end; i++) {
-      intrinsic_name[i] = toupper(start[i]);
-   }
-   intrinsic_name[i] = '\0';
-
-   return intrinsic_name;
-}
-
-static char *
-ethr_get_amended_env(const char *name, const char *prefix, const char *suffix)
-{
-   unsigned len;
-   char *env_name = NULL;
-   char *env_value = NULL;
-
-   if (name == NULL) {
-      return NULL;
-   }
-
-   len = strlen(name);
-
-   if (prefix != NULL) {
-      len += strlen(prefix);
-   }
-
-   if (suffix != NULL) {
-      len += strlen(suffix);
-   }
-
-   env_name = malloc(len + 1);
-   sprintf(env_name, "%s%s%s", (prefix != NULL) ? prefix : "",
-                               name,
-                               (suffix != NULL) ? suffix : "");
-   env_value = get_env(get_bid(current_process()), env_name);
-
-   if (env_value == NULL) {
-      LOG(("ERTS - ethr_get_amended_env(): %s environment variable not present\n", env_name));
-   } else {
-      LOG(("ERTS - ethr_get_amended_env(): Found %s environment variable: %s.\n", env_name, env_value));
-   }
-   free(env_name);
-
-   return env_value;
-}
-
-/* Reads the environment variable derived from 'name' and interprets it as as an
- * OSE priority. If successfull it will update 'out_prio'.
- * Returns:  0 if successfull
- *          -1 orherwise.
- */
-static int
-ethr_get_prio(const char *name, OSPRIORITY *out_prio)
-{
-   int rc = -1;
-   char *intrinsic_name = NULL;
-   char *prio_env = NULL;
-   long prio;
-   char *endptr = NULL;
-
-   LOG(("ERTS - ethr_get_prio(): name: %s.\n", name));
-
-   intrinsic_name = ethr_intrinsic_name(name, NULL, 1);
-   LOG(("ERTS - ethr_get_prio(): Intrinsic name: %s.\n", intrinsic_name));
-
-   prio_env = ethr_get_amended_env(intrinsic_name, "ERTS_", "_PRIO");
-   if (prio_env == NULL) {
-      goto fini;
-   }
-
-   prio = efs_str_to_long(prio_env, (const char **)&endptr);
-   if (endptr != NULL) {
-      LOG(("ERTS - ethr_get_prio(): Environment varible for '%s' includes "
-           "non-numerical characters: '%s'.\n", intrinsic_name, prio_env));
-      goto fini;
-   }
-
-   if ((prio < 0) || (prio > 32)) {
-      LOG(("ERTS - ethr_get_prio(): prio for '%s' (%d) is out of bounds (0-32).\n",
-               intrinsic_name, prio));
-      goto fini;
-   }
-
-   /* Success */
-   *out_prio = (OSPRIORITY)prio;
-   rc = 0;
-
-fini:
-   if (intrinsic_name != NULL) {
-      free(intrinsic_name);
-   }
-   if (prio_env != NULL) {
-      free_buf((union SIGNAL **) &prio_env);
-   }
-
-   return rc;
-}
-
-static PROCESS blockId(void) {
-   static PROCESS bid = (PROCESS)0;
-
-   /* For now we only use the same block. */
-   /*   if (bid == 0) {
-      bid = create_block("Erlang-VM", 0, 0, 0, 0);
-   }
-   return bid; */
-   return 0;
-}
-
-static void thr_exit_cleanup(ethr_tid *tid, void *res)
-{
-
-     ETHR_ASSERT(tid == ETHR_GET_OWN_TID__);
-
-     tid->res = res;
-
-     ethr_run_exit_handlers__();
-     ethr_ts_event_destructor__((void *) ethr_get_tse__());
-}
-
-//static OS_PROCESS(thr_wrapper);
-static OS_PROCESS(thr_wrapper)
-{
-    ethr_tid my_tid;
-    ethr_sint32_t result;
-    void *res;
-    void *(*thr_func)(void *);
-    void *arg;
-    ethr_ts_event *tsep = NULL;
-
-#ifdef DEBUG
-    {
-       PROCESS pid = current_process();
-
-       const char *execMode;
-
-       PROCESS     bid      = get_bid(pid);
-
-       /* In the call below, 16 is a secret number provided by frbr that makes
-        * the function return current domain. */
-       OSADDRESS   domain   = get_pid_info(current_process(), 16);
-
-#ifdef HAVE_OSE_SPI_H
-       execMode = get_pid_info(pid, OSE_PI_SUPERVISOR)
-          ? "Supervisor"
-          : "User";
-#else
-       execMode = "unknown";
-#endif
-
-       fprintf(stderr,"[0x%x] New process. Bid:0x%x, domain:%d, exec mode:%s\n",
-               current_process(), bid, domain, execMode);
-    }
-#endif
-
-    {
-       SIGSELECT sigsel[] = {1,ETHREADWRAPDATASIG};
-       union SIGNAL *init_msg = receive(sigsel);
-
-       thr_func = init_msg->data.thr_func;
-       arg      = init_msg->data.arg;
-
-       result = (ethr_sint32_t) ethr_make_ts_event__(&tsep);
-
-       if (result == 0) {
-          tsep->iflgs |= ETHR_TS_EV_ETHREAD;
-          my_tid = *init_msg->data.tid;
-          set_envp(current_process(), own_tid_key, (OSADDRESS)&my_tid);
-          if (ethr_thr_child_func__)
-             ethr_thr_child_func__(init_msg->data.prep_func_res);
-       }
-
-       init_msg->data.result = result;
-
-       send(&init_msg,sender(&init_msg));
-    }
-
-    /* pthread mutex api says we have to do this */
-    signal_fsem(current_process());
-    ETHR_ASSERT(get_fsem(current_process()) == 0);
-
-    res = result == 0 ? (*thr_func)(arg) : NULL;
-
-    ethr_thr_exit(&res);
-}
-
-/* internal exports */
-
-int ethr_set_tse__(ethr_ts_event *tsep)
-{
-  return ethr_tsd_set(ethr_ts_event_key__,(void *) tsep);
-}
-
-ethr_ts_event *ethr_get_tse__(void)
-{
-  return (ethr_ts_event *) ethr_tsd_get(ethr_ts_event_key__);
-}
-
-#if defined(ETHR_PPC_RUNTIME_CONF__)
-
-static int
-ppc_init__(void)
-{
-    int pid;
-
-
-    ethr_runtime__.conf.have_lwsync = 0;
-
-    return 0;
-}
-
-#endif
-
-#if defined(ETHR_X86_RUNTIME_CONF__)
-
-void
-ethr_x86_cpuid__(int *eax, int *ebx, int *ecx, int *edx)
-{
-#if ETHR_SIZEOF_PTR == 4
-    int have_cpuid;
-    /*
-     * If it is possible to toggle eflags bit 21,
-     * we have the cpuid instruction.
-     */
-    __asm__ ("pushf\n\t"
-             "popl %%eax\n\t"
-             "movl %%eax, %%ecx\n\t"
-             "xorl $0x200000, %%eax\n\t"
-             "pushl %%eax\n\t"
-             "popf\n\t"
-             "pushf\n\t"
-             "popl %%eax\n\t"
-             "movl $0x0, %0\n\t"
-             "xorl %%ecx, %%eax\n\t"
-             "jz no_cpuid\n\t"
-	     "movl $0x1, %0\n\t"
-             "no_cpuid:\n\t"
-             : "=r"(have_cpuid)
-             :
-             : "%eax", "%ecx", "cc");
-    if (!have_cpuid) {
-	*eax = *ebx = *ecx = *edx = 0;
-	return;
-    }
-#endif
-#if ETHR_SIZEOF_PTR == 4 && defined(__PIC__) && __PIC__
-    /*
-     * When position independet code is used in 32-bit mode, the B register
-     * is used for storage of global offset table address, and we may not
-     * use it as input or output in an asm. We need to save and restore the
-     * B register explicitly (for some reason gcc doesn't provide this
-     * service to us).
-     */
-    __asm__ ("pushl %%ebx\n\t"
-	     "cpuid\n\t"
-	     "movl %%ebx, %1\n\t"
-	     "popl %%ebx\n\t"
-	     : "=a"(*eax), "=r"(*ebx), "=c"(*ecx), "=d"(*edx)
-	     : "0"(*eax)
-	     : "cc");
-#else
-    __asm__ ("cpuid\n\t"
-	     : "=a"(*eax), "=b"(*ebx), "=c"(*ecx), "=d"(*edx)
-	     : "0"(*eax)
-	     : "cc");
-#endif
-}
-
-#endif /* ETHR_X86_RUNTIME_CONF__ */
-
-/*
- * --------------------------------------------------------------------------
- * Exported functions
- * --------------------------------------------------------------------------
- */
-
-int
-ethr_init(ethr_init_data *id)
-{
-    int res;
-
-    if (!ethr_not_inited__)
-	return EINVAL;
-
-
-#if defined(ETHR_PPC_RUNTIME_CONF__)
-    res = ppc_init__();
-    if (res != 0)
-	goto error;
-#endif
-
-    res = ethr_init_common__(id);
-    if (res != 0)
-	goto error;
-
-    main_thr_tid.id = current_process();
-    main_thr_tid.tsd_key_index = 0;
-
-    set_envp(current_process(),own_tid_key,(OSADDRESS)&main_thr_tid);
-    signal_fsem(current_process());
-
-
-    ETHR_ASSERT(&main_thr_tid == ETHR_GET_OWN_TID__);
-
-    ethr_not_inited__ = 0;
-
-    ethr_tsd_key_create(&ethr_ts_event_key__,"ethread_tse");
-
-    return 0;
- error:
-    ethr_not_inited__ = 1;
-    return res;
-
-}
-
-int
-ethr_late_init(ethr_late_init_data *id)
-{
-    int res = ethr_late_init_common__(id);
-    if (res != 0)
-	return res;
-    ethr_not_completely_inited__ = 0;
-    return res;
-}
-
-int
-ethr_thr_create(ethr_tid *tid, void * (*func)(void *), void *arg,
-		ethr_thr_opts *opts)
-{
-    int res;
-    int use_stack_size = (opts && opts->suggested_stack_size >= 0
-			  ? opts->suggested_stack_size
-			  : 0x200 /* Use system default */);
-    OSPRIORITY use_prio;
-    char *use_name;
-    char default_thr_name[20];
-    static int no_of_thr = 0;
-    cpuid_t use_core;
-
-    union SIGNAL *init_msg;
-    SIGSELECT sigsel[] = {1,ETHREADWRAPDATASIG};
-    void *prep_func_res;
-
-
-    if (opts != NULL) {
-        LOG(("ERTS - ethr_thr_create(): opts supplied: name: %s, coreNo: %u.\n",
-                      opts->name, opts->coreNo));
-        use_name = opts->name;
-        use_core = opts->coreNo;
-        if (0 != ethr_get_prio(use_name, &use_prio)) {
-           if (0 != ethr_get_prio("DEFAULT", &use_prio)) {
-              use_prio = get_pri(current_process());
-              LOG(("ERTS - ethr_thr_create(): Using current process' prio: %d.\n", use_prio));
-           } else {
-              LOG(("ERTS - ethr_thr_create(): Using default prio: %d.\n", use_prio));
-           }
-        } else {
-           LOG(("ERTS - ethr_thr_create(): Using configured prio: %d.\n", use_prio));
-        }
-    } else {
-        LOG(("ERTS - ethr_thr_create(): opts not supplied. Using defaults.\n"));
-        no_of_thr++;
-        sprintf(default_thr_name, "ethread_%d", no_of_thr);
-        use_name = default_thr_name;
-        use_core = ose_cpu_id();
-
-        if (0 != ethr_get_prio("DEFAULT", &use_prio)) {
-           use_prio = get_pri(current_process());
-           LOG(("ERTS - ethr_thr_create(): Using current process' prio: %d.\n", use_prio));
-        }
-    }
-
-#ifdef ETHR_MODIFIED_DEFAULT_STACK_SIZE
-    if (use_stack_size < 0)
-	use_stack_size = ETHR_MODIFIED_DEFAULT_STACK_SIZE;
-#endif
-
-#if ETHR_XCHK
-    if (ethr_not_completely_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-    if (!tid || !func) {
-	ETHR_ASSERT(0);
-	return EINVAL;
-    }
-#endif
-
-    if (use_stack_size >= 0) {
-	size_t suggested_stack_size = (size_t) use_stack_size;
-	size_t stack_size;
-#ifdef ETHR_DEBUG
-	suggested_stack_size /= 2; /* Make sure we got margin */
-#endif
-#ifdef ETHR_STACK_GUARD_SIZE
-	/* The guard is at least on some platforms included in the stack size
-	   passed when creating threads */
-	suggested_stack_size += ETHR_B2KW(ETHR_STACK_GUARD_SIZE);
-#endif
-
-	if (suggested_stack_size < ethr_min_stack_size__)
-	    stack_size = ETHR_KW2B(ethr_min_stack_size__);
-	else if (suggested_stack_size > ethr_max_stack_size__)
-	    stack_size = ETHR_KW2B(ethr_max_stack_size__);
-	else
-	    stack_size = ETHR_PAGE_ALIGN(ETHR_KW2B(suggested_stack_size));
-	use_stack_size = stack_size;
-    }
-
-    init_msg = alloc(sizeof(ethr_thr_wrap_data__), ETHREADWRAPDATASIG);
-
-    /* Call prepare func if it exist */
-    if (ethr_thr_prepare_func__)
-	init_msg->data.prep_func_res = ethr_thr_prepare_func__();
-    else
-	init_msg->data.prep_func_res = NULL;
-
-    LOG(("ERTS - ethr_thr_create(): Process [0x%x] is creating '%s', coreNo = %u, prio:%u\n",
-                  current_process(), use_name, use_core, use_prio));
-
-    tid->id = create_process(OS_PRI_PROC, use_name, thr_wrapper,
-			     use_stack_size, use_prio, 0,
-                             get_bid(current_process()), NULL, 0, 0);
-      if (ose_bind_process(tid->id, use_core)) {
-         LOG(("ERTS - ethr_thr_create(): Bound pid 0x%x (%s) to core no %u.\n",
-              tid->id, use_name, use_core));
-      } else {
-            LOG(("ERTS - ethr_thr_create(): Failed binding pid 0x%x (%s) to core no %u.\n",
-                 tid->id, use_name, use_core));
-      }
-
-    /*FIXME!!! Normally this shouldn't be used in shared mode. Still there is
-     * a problem with stdin fd in fd_ processes which should be further
-     * investigated */
-    efs_clone(tid->id);
-
-    tid->tsd_key_index = 0;
-    tid->res = NULL;
-
-    init_msg->data.tse      = ethr_get_ts_event();
-    init_msg->data.thr_func = func;
-    init_msg->data.arg      = arg;
-    init_msg->data.tid      = tid;
-    init_msg->data.name     = opts->name;
-
-    send(&init_msg, tid->id);
-
-    start(tid->id);
-    init_msg = receive(sigsel);
-
-    res = init_msg->data.result;
-    prep_func_res = init_msg->data.prep_func_res;
-
-    free_buf(&init_msg);
-    /* Cleanup... */
-
-    if (ethr_thr_parent_func__)
-	ethr_thr_parent_func__(prep_func_res);
-
-    LOG(("ERTS - ethr_thr_create(): Exiting.\n"));
-    return res;
-}
-
-int
-ethr_thr_join(ethr_tid tid, void **res)
-{
-    SIGSELECT sigsel[] = {1,OS_ATTACH_SIG};
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-#endif
-
-    if (tid.id == ETHR_INVALID_TID_ID)
-      return EINVAL;
-
-    attach(NULL,tid.id);
-    receive(sigsel);
-
-    if (res)
-      *res = tid.res;
-
-    return 0;
-}
-
-int
-ethr_thr_detach(ethr_tid tid)
-{
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-#endif
-    return 0;
-}
-
-void
-ethr_thr_exit(void *res)
-{
-    ethr_tid *tid;
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return;
-    }
-#endif
-    tid = ETHR_GET_OWN_TID__;
-    if (!tid) {
-	ETHR_ASSERT(0);
-	kill_proc(current_process());
-    }
-    thr_exit_cleanup(tid, res);
-    /* Harakiri possible? */
-    kill_proc(current_process());
-}
-
-ethr_tid
-ethr_self(void)
-{
-    ethr_tid *tid;
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-      ethr_tid dummy_tid = {ETHR_INVALID_TID_ID, 0, NULL};
-	ETHR_ASSERT(0);
-	return dummy_tid;
-    }
-#endif
-    tid = ETHR_GET_OWN_TID__;
-    if (!tid) {
-	ethr_tid dummy_tid = {ETHR_INVALID_TID_ID, 0, NULL};
-	return dummy_tid;
-    }
-    return *tid;
-}
-
-int
-ethr_equal_tids(ethr_tid tid1, ethr_tid tid2)
-{
-    return tid1.id == tid2.id && tid1.id != ETHR_INVALID_TID_ID;
-}
-
-
-/*
- * Thread specific events
- */
-
-ethr_ts_event *
-ethr_get_ts_event(void)
-{
-    return ethr_get_ts_event__();
-}
-
-void
-ethr_leave_ts_event(ethr_ts_event *tsep)
-{
-    ethr_leave_ts_event__(tsep);
-}
-
-/*
- * Thread specific data
- */
-
-int
-ethr_tsd_key_create(ethr_tsd_key *keyp, char *keyname)
-{
-
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-    if (!keyp) {
-	ETHR_ASSERT(0);
-	return EINVAL;
-    }
-#endif
-
-    ose_create_ppdata(keyname,keyp);
-
-    return 0;
-}
-
-int
-ethr_tsd_key_delete(ethr_tsd_key key)
-{
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-#endif
-    /* Not possible to delete ppdata */
-
-    return 0;
-}
-
-int
-ethr_tsd_set(ethr_tsd_key key, void *value)
-{
-    void **ppdp;
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-#endif
-    ppdp = (void **)ose_get_ppdata(key);
-    *ppdp = value;
-    return 0;
-}
-
-void *
-ethr_tsd_get(ethr_tsd_key key)
-{
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return NULL;
-    }
-#endif
-    return *(void**)ose_get_ppdata(key);
-}
-
-/*
- * Signal functions
- */
-
-#if ETHR_HAVE_ETHR_SIG_FUNCS
-
-int ethr_sigmask(int how, const sigset_t *set, sigset_t *oset)
-{
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-    if (!set && !oset) {
-	ETHR_ASSERT(0);
-	return EINVAL;
-    }
-#endif
-  return pthread_sigmask(how, set, oset);
-}
-
-int ethr_sigwait(const sigset_t *set, int *sig)
-{
-#if ETHR_XCHK
-    if (ethr_not_inited__) {
-	ETHR_ASSERT(0);
-	return EACCES;
-    }
-    if (!set || !sig) {
-	ETHR_ASSERT(0);
-	return EINVAL;
-    }
-#endif
-    if (sigwait(set, sig) < 0)
-	return errno;
-    return 0;
-}
-
-#endif /* #if ETHR_HAVE_ETHR_SIG_FUNCS */
-
-ETHR_IMPL_NORETURN__
-ethr_abort__(void)
-{
-    abort();
-}
diff -Ndurp otp_src_18.3.4.5/erts/lib_src/ose/ethr_event.c otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/ose/ethr_event.c
--- otp_src_18.3.4.5/erts/lib_src/ose/ethr_event.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/erts/lib_src/ose/ethr_event.c	1970-01-01 03:00:00.000000000 +0300
@@ -1,220 +0,0 @@
-/*
- * %CopyrightBegin%
- *
- * Copyright Ericsson AB 2009-2010. All Rights Reserved.
- *
- * Licensed under the Apache License, Version 2.0 (the "License");
- * you may not use this file except in compliance with the License.
- * You may obtain a copy of the License at
- *
- *     http://www.apache.org/licenses/LICENSE-2.0
- *
- * Unless required by applicable law or agreed to in writing, software
- * distributed under the License is distributed on an "AS IS" BASIS,
- * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
- * See the License for the specific language governing permissions and
- * limitations under the License.
- *
- * %CopyrightEnd%
- */
-
-/*
- * Author: Rickard Green
- */
-
-#define ETHR_INLINE_FUNC_NAME_(X) X ## __
-#define ETHR_EVENT_IMPL__
-
-#ifdef HAVE_CONFIG_H
-#include "config.h"
-#endif
-
-#include "ethread.h"
-
-#ifdef USE_PTHREAD_API
-
-int
-ethr_event_init(ethr_event *e)
-{
-    int res;
-    ethr_atomic32_init(&e->state, ETHR_EVENT_OFF__);
-    res = pthread_mutex_init(&e->mtx, NULL);
-    if (res != 0)
-	return res;
-    res = pthread_cond_init(&e->cnd, NULL);
-    if (res != 0) {
-	pthread_mutex_destroy(&e->mtx);
-	return res;
-    }
-    return 0;
-}
-
-int
-ethr_event_destroy(ethr_event *e)
-{
-    int res;
-    res = pthread_mutex_destroy(&e->mtx);
-    if (res != 0)
-	return res;
-    res = pthread_cond_destroy(&e->cnd);
-    if (res != 0)
-	return res;
-    return 0;
-}
-
-static ETHR_INLINE int
-wait__(ethr_event *e, int spincount)
-{
-    int sc = spincount;
-    ethr_sint32_t val;
-    int res, ulres;
-    int until_yield = ETHR_YIELD_AFTER_BUSY_LOOPS;
-
-    if (spincount < 0)
-	ETHR_FATAL_ERROR__(EINVAL);
-
-    while (1) {
-	val = ethr_atomic32_read(&e->state);
-	if (val == ETHR_EVENT_ON__)
-	    return 0;
-	if (sc == 0)
-	    break;
-	sc--;
-	ETHR_SPIN_BODY;
-	if (--until_yield == 0) {
-	    until_yield = ETHR_YIELD_AFTER_BUSY_LOOPS;
-	    res = ETHR_YIELD();
-	    if (res != 0)
-		ETHR_FATAL_ERROR__(res);
-	}
-    }
-
-    if (val != ETHR_EVENT_OFF_WAITER__) {
-	val = ethr_atomic32_cmpxchg(&e->state,
-				    ETHR_EVENT_OFF_WAITER__,
-				    ETHR_EVENT_OFF__);
-	if (val == ETHR_EVENT_ON__)
-	    return 0;
-	ETHR_ASSERT(val == ETHR_EVENT_OFF__);
-    }
-
-    ETHR_ASSERT(val == ETHR_EVENT_OFF_WAITER__
-		|| val == ETHR_EVENT_OFF__);
-
-    res = pthread_mutex_lock(&e->mtx);
-    if (res != 0)
-	ETHR_FATAL_ERROR__(res);
-
-    while (1) {
-
-	val = ethr_atomic32_read(&e->state);
-	if (val == ETHR_EVENT_ON__)
-	    break;
-
-	res = pthread_cond_wait(&e->cnd, &e->mtx);
-	if (res == EINTR)
-	    break;
-	if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-    }
-
-    ulres = pthread_mutex_unlock(&e->mtx);
-    if (ulres != 0)
-	ETHR_FATAL_ERROR__(ulres);
-
-    return res; /* 0 || EINTR */
-}
-
-#else
-/* --- OSE implementation of events ---------------------------- */
-
-#ifdef DEBUG
-union SIGNAL {
-  SIGSELECT signo;
-};
-#endif
-
-int
-ethr_event_init(ethr_event *e)
-{
-    ethr_atomic32_init(&e->state, ETHR_EVENT_OFF__);
-    e->proc = current_process();
-    return 0;
-}
-
-int
-ethr_event_destroy(ethr_event *e)
-{
-  return 0;
-}
-
-static ETHR_INLINE int
-wait__(ethr_event *e, int spincount)
-{
-    int sc = spincount;
-    int res;
-    int until_yield = ETHR_YIELD_AFTER_BUSY_LOOPS;
-
-    if (spincount < 0)
-	ETHR_FATAL_ERROR__(EINVAL);
-
-    ETHR_ASSERT(e->proc == current_process());
-    ETHR_ASSERT(get_fsem(current_process()) == 0);
-
-    while (1) {
-      ethr_sint32_t val;
-      while (1) {
-        val = ethr_atomic32_read(&e->state);
-	if (val == ETHR_EVENT_ON__)
-	  return 0;
-	if (sc == 0)
-	  break;
-	sc--;
-	ETHR_SPIN_BODY;
-	if (--until_yield == 0) {
-	  until_yield = ETHR_YIELD_AFTER_BUSY_LOOPS;
-	  res = ETHR_YIELD();
-	  if (res != 0)
-	    ETHR_FATAL_ERROR__(res);
-	}
-      }
-      if (val != ETHR_EVENT_OFF_WAITER__) {
-	val = ethr_atomic32_cmpxchg(&e->state,
-				    ETHR_EVENT_OFF_WAITER__,
-				    ETHR_EVENT_OFF__);
-	if (val == ETHR_EVENT_ON__)
-	  return 0;
-	ETHR_ASSERT(val == ETHR_EVENT_OFF__);
-      }
-
-      wait_fsem(1);
-
-      ETHR_ASSERT(get_fsem(current_process()) == 0);
-    }
-}
-
-#endif
-
-void
-ethr_event_reset(ethr_event *e)
-{
-    ethr_event_reset__(e);
-}
-
-void
-ethr_event_set(ethr_event *e)
-{
-    ethr_event_set__(e);
-}
-
-int
-ethr_event_wait(ethr_event *e)
-{
-    return wait__(e, 0);
-}
-
-int
-ethr_event_swait(ethr_event *e, int spincount)
-{
-    return wait__(e, spincount);
-}
diff -Ndurp otp_src_18.3.4.5/HOWTO/INSTALL-CROSS.md otp_src_18.3.4.5-remove-OSE-port/HOWTO/INSTALL-CROSS.md
--- otp_src_18.3.4.5/HOWTO/INSTALL-CROSS.md	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/HOWTO/INSTALL-CROSS.md	2017-02-03 21:52:59.167951112 +0200
@@ -520,29 +520,6 @@ When a variable has been set, no warning
     `posix_memalign` implementation that accepts larger than page size
     alignment.
 
-*   `erl_xcomp_ose_ldflags_pass1` - Linker flags for the OSE module (pass 1)
-
-*   `erl_xcomp_ose_ldflags_pass2` - Linker flags for the OSE module (pass 2)
-
-*   `erl_xcomp_ose_OSEROOT` - OSE installation root directory
-
-*   `erl_xcomp_ose_STRIP` - Strip utility shipped with the OSE distribution
-
-*   `erl_xcomp_ose_LM_POST_LINK` - OSE postlink tool
-
-*   `erl_xcomp_ose_LM_SET_CONF` - Sets the configuration for an OSE load module
-
-*   `erl_xcomp_ose_LM_ELF_SIZE` - Prints the section size information for an
-	OSE load module
-
-*   `erl_xcomp_ose_LM_LCF` - OSE load module linker configuration file
-
-*   `erl_xcomp_ose_BEAM_LM_CONF` - Beam OSE load module configuration file
-
-*   `erl_xcomp_ose_EPMD_LM_CONF` - EPMD OSE load module configuration file
-
-*   `erl_xcomp_ose_RUN_ERL_LM_CONF` - run_erl_lm OSE load module configuration file
-
 Copyright and License
 ---------------------
 
diff -Ndurp otp_src_18.3.4.5/lib/asn1/c_src/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/asn1/c_src/Makefile
--- otp_src_18.3.4.5/lib/asn1/c_src/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/asn1/c_src/Makefile	2017-02-03 21:52:59.167951112 +0200
@@ -97,12 +97,7 @@ endif
 
 _create_dirs := $(shell mkdir -p $(OBJDIR) $(LIBDIR))
 
-ifneq ($(findstring ose,$(TARGET)),ose)
 opt: $(NIF_SHARED_OBJ_FILE)
-else
-# Do not build dynamic files on OSE
-opt:
-endif
 
 debug: opt
 
@@ -140,9 +135,7 @@ include $(ERL_TOP)/make/otp_release_targ
 
 release_spec: opt
 	$(INSTALL_DIR) "$(RELSYSDIR)/priv/lib"
-ifneq ($(findstring ose,$(TARGET)),ose)
 	$(INSTALL_PROGRAM) $(NIF_SHARED_OBJ_FILE) "$(RELSYSDIR)/priv/lib"
-endif
 	$(INSTALL_DIR) "$(RELSYSDIR)/c_src"
 	$(INSTALL_DATA) *.c "$(RELSYSDIR)/c_src"
 
diff -Ndurp otp_src_18.3.4.5/lib/crypto/c_src/crypto.c otp_src_18.3.4.5-remove-OSE-port/lib/crypto/c_src/crypto.c
--- otp_src_18.3.4.5/lib/crypto/c_src/crypto.c	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/crypto/c_src/crypto.c	2017-02-03 21:52:59.167951112 +0200
@@ -507,47 +507,6 @@ static void hmac_context_dtor(ErlNifEnv*
 #define PRINTF_ERR1(FMT,A1)
 #define PRINTF_ERR2(FMT,A1,A2)
 
-#ifdef __OSE__
-
-/* For crypto on OSE we have to initialize the crypto library on each
-   process that uses it. So since we do not know which scheduler is going
-   to execute the nif we have to check before each nif call that we have
-   initialized crypto in that process. */
-
-#include "ose.h"
-#include "openssl/osessl.h"
-
-static ErlNifTSDKey crypto_init_key;
-static int check_ose_crypto(void);
-static int init_ose_crypto(void);
-
-static int check_ose_crypto() {
-    int key = (int)enif_tsd_get(crypto_init_key);
-    if (!key) {
-	if (!CRYPTO_OSE5_init()) {
-	    PRINTF_ERR0("CRYPTO: Call to CRYPTO_OSE5_init failed");
-	    return 0;
-	}
-	enif_tsd_set(crypto_init_key,1);
-    }
-    return 1;
-}
-
-static int init_ose_crypto() {
-    /* Crypto nif upgrade does not work on OSE so no need to
-       destroy this key */
-    enif_tsd_key_create("crypto_init_key", &crypto_init_key);
-    return check_ose_crypto();
-}
-
-#define INIT_OSE_CRYPTO() init_ose_crypto()
-#define CHECK_OSE_CRYPTO() check_ose_crypto()
-#else
-#define INIT_OSE_CRYPTO() 1
-#define CHECK_OSE_CRYPTO()
-#endif
-
-
 static int verify_lib_version(void)
 {
     const unsigned long libv = SSLeay();
@@ -609,9 +568,6 @@ static int init(ErlNifEnv* env, ERL_NIF_
     ErlNifBinary lib_bin;
     char lib_buf[1000];
 
-    if (!INIT_OSE_CRYPTO())
-      return 0;
-
     if (!verify_lib_version())
 	return 0;
 
@@ -853,7 +809,6 @@ static ERL_NIF_TERM md5(ErlNifEnv* env,
 {/* (Data) */
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -865,7 +820,6 @@ static ERL_NIF_TERM md5(ErlNifEnv* env,
 static ERL_NIF_TERM md5_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {/* () */   
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     MD5_Init((MD5_CTX *) enif_make_new_binary(env, MD5_CTX_LEN, &ret));
     return ret;
 }
@@ -874,7 +828,6 @@ static ERL_NIF_TERM md5_update(ErlNifEnv
     MD5_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin)
 	|| ctx_bin.size != MD5_CTX_LEN
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
@@ -891,7 +844,6 @@ static ERL_NIF_TERM md5_final(ErlNifEnv*
     ErlNifBinary ctx_bin;
     MD5_CTX ctx_clone; 
     ERL_NIF_TERM ret;    
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != MD5_CTX_LEN) {
 	return enif_make_badarg(env);
     }
@@ -904,7 +856,6 @@ static ERL_NIF_TERM ripemd160(ErlNifEnv*
 {/* (Data) */
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -916,7 +867,6 @@ static ERL_NIF_TERM ripemd160(ErlNifEnv*
 static ERL_NIF_TERM ripemd160_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {/* () */
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     RIPEMD160_Init((RIPEMD160_CTX *) enif_make_new_binary(env, RIPEMD160_CTX_LEN, &ret));
     return ret;
 }
@@ -925,7 +875,6 @@ static ERL_NIF_TERM ripemd160_update(Erl
     RIPEMD160_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin)
 	|| ctx_bin.size != RIPEMD160_CTX_LEN
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
@@ -942,7 +891,6 @@ static ERL_NIF_TERM ripemd160_final(ErlN
     ErlNifBinary ctx_bin;
     RIPEMD160_CTX ctx_clone;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != RIPEMD160_CTX_LEN) {
 	return enif_make_badarg(env);
     }
@@ -956,7 +904,6 @@ static ERL_NIF_TERM sha(ErlNifEnv* env,
 {/* (Data) */    
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -968,7 +915,6 @@ static ERL_NIF_TERM sha(ErlNifEnv* env,
 static ERL_NIF_TERM sha_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {/* () */   
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     SHA1_Init((SHA_CTX *) enif_make_new_binary(env, SHA_CTX_LEN, &ret));
     return ret;
 }
@@ -977,7 +923,6 @@ static ERL_NIF_TERM sha_update(ErlNifEnv
     SHA_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != SHA_CTX_LEN
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
 	return enif_make_badarg(env);
@@ -993,7 +938,6 @@ static ERL_NIF_TERM sha_final(ErlNifEnv*
     ErlNifBinary ctx_bin;
     SHA_CTX ctx_clone;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != SHA_CTX_LEN) {
 	return enif_make_badarg(env);
     }
@@ -1007,7 +951,6 @@ static ERL_NIF_TERM sha224_nif(ErlNifEnv
 #ifdef HAVE_SHA224
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -1023,7 +966,6 @@ static ERL_NIF_TERM sha224_init_nif(ErlN
 {/* () */
 #ifdef HAVE_SHA224
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     SHA224_Init((SHA256_CTX *) enif_make_new_binary(env, sizeof(SHA256_CTX), &ret));
     return ret;
 #else
@@ -1036,7 +978,6 @@ static ERL_NIF_TERM sha224_update_nif(Er
     SHA256_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA256_CTX)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
 	return enif_make_badarg(env);
@@ -1056,7 +997,6 @@ static ERL_NIF_TERM sha224_final_nif(Erl
     ErlNifBinary ctx_bin;
     SHA256_CTX ctx_clone;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA256_CTX)) {
 	return enif_make_badarg(env);
     }
@@ -1073,7 +1013,6 @@ static ERL_NIF_TERM sha256_nif(ErlNifEnv
 #ifdef HAVE_SHA256
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -1089,7 +1028,6 @@ static ERL_NIF_TERM sha256_init_nif(ErlN
 {/* () */   
 #ifdef HAVE_SHA256
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     SHA256_Init((SHA256_CTX *) enif_make_new_binary(env, sizeof(SHA256_CTX), &ret));
     return ret;
 #else
@@ -1102,7 +1040,6 @@ static ERL_NIF_TERM sha256_update_nif(Er
     SHA256_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA256_CTX)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
 	return enif_make_badarg(env);
@@ -1122,7 +1059,6 @@ static ERL_NIF_TERM sha256_final_nif(Erl
     ErlNifBinary ctx_bin;
     SHA256_CTX ctx_clone;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA256_CTX)) {
 	return enif_make_badarg(env);
     }
@@ -1139,7 +1075,6 @@ static ERL_NIF_TERM sha384_nif(ErlNifEnv
 #ifdef HAVE_SHA384
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -1155,7 +1090,6 @@ static ERL_NIF_TERM sha384_init_nif(ErlN
 {/* () */
 #ifdef HAVE_SHA384
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     SHA384_Init((SHA512_CTX *) enif_make_new_binary(env, sizeof(SHA512_CTX), &ret));
     return ret;
 #else
@@ -1168,7 +1102,6 @@ static ERL_NIF_TERM sha384_update_nif(Er
     SHA512_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA512_CTX)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
 	return enif_make_badarg(env);
@@ -1188,7 +1121,6 @@ static ERL_NIF_TERM sha384_final_nif(Erl
     ErlNifBinary ctx_bin;
     SHA512_CTX ctx_clone;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA512_CTX)) {
 	return enif_make_badarg(env);
     }
@@ -1205,7 +1137,6 @@ static ERL_NIF_TERM sha512_nif(ErlNifEnv
 #ifdef HAVE_SHA512
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -1233,7 +1164,6 @@ static ERL_NIF_TERM sha512_update_nif(Er
     SHA512_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA512_CTX)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
 	return enif_make_badarg(env);
@@ -1253,7 +1183,6 @@ static ERL_NIF_TERM sha512_final_nif(Erl
     ErlNifBinary ctx_bin;
     SHA512_CTX ctx_clone;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != sizeof(SHA512_CTX)) {
 	return enif_make_badarg(env);
     }
@@ -1270,7 +1199,6 @@ static ERL_NIF_TERM md4(ErlNifEnv* env,
 {/* (Data) */    
     ErlNifBinary ibin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &ibin)) {
 	return enif_make_badarg(env);
     }
@@ -1282,7 +1210,6 @@ static ERL_NIF_TERM md4(ErlNifEnv* env,
 static ERL_NIF_TERM md4_init(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {/* () */   
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     MD4_Init((MD4_CTX *) enif_make_new_binary(env, MD4_CTX_LEN, &ret));
     return ret;
 }
@@ -1291,7 +1218,6 @@ static ERL_NIF_TERM md4_update(ErlNifEnv
     MD4_CTX* new_ctx;
     ErlNifBinary ctx_bin, data_bin;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != MD4_CTX_LEN
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)) {
 	return enif_make_badarg(env);
@@ -1307,7 +1233,6 @@ static ERL_NIF_TERM md4_final(ErlNifEnv*
     ErlNifBinary ctx_bin;
     MD4_CTX ctx_clone;
     ERL_NIF_TERM ret;    
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &ctx_bin) || ctx_bin.size != MD4_CTX_LEN) {
 	return enif_make_badarg(env);
     }
@@ -1322,7 +1247,6 @@ static ERL_NIF_TERM md5_mac_n(ErlNifEnv*
     ErlNifBinary key, data;
     unsigned mac_sz;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)
 	|| !enif_get_uint(env,argv[2],&mac_sz) || mac_sz > MD5_LEN) {
@@ -1340,7 +1264,6 @@ static ERL_NIF_TERM sha_mac_n(ErlNifEnv*
     ErlNifBinary key, data;
     unsigned mac_sz;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)
 	|| !enif_get_uint(env,argv[2],&mac_sz) || mac_sz > SHA_LEN) {
@@ -1360,7 +1283,6 @@ static ERL_NIF_TERM sha224_mac_nif(ErlNi
     ErlNifBinary key, data;
     unsigned mac_sz;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)
 	|| !enif_get_uint(env,argv[2],&mac_sz) || mac_sz > SHA224_DIGEST_LENGTH) {
@@ -1383,7 +1305,6 @@ static ERL_NIF_TERM sha256_mac_nif(ErlNi
     ErlNifBinary key, data;
     unsigned mac_sz;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)
 	|| !enif_get_uint(env,argv[2],&mac_sz) || mac_sz > SHA256_DIGEST_LENGTH) {
@@ -1406,7 +1327,6 @@ static ERL_NIF_TERM sha384_mac_nif(ErlNi
     ErlNifBinary key, data;
     unsigned mac_sz;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)
 	|| !enif_get_uint(env,argv[2],&mac_sz) || mac_sz > SHA384_DIGEST_LENGTH) {
@@ -1430,7 +1350,6 @@ static ERL_NIF_TERM sha512_mac_nif(ErlNi
     ErlNifBinary key, data;
     unsigned mac_sz;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)
 	|| !enif_get_uint(env,argv[2],&mac_sz) || mac_sz > SHA512_DIGEST_LENGTH) {
@@ -1462,7 +1381,6 @@ static ERL_NIF_TERM hmac_init(ErlNifEnv*
     const EVP_MD *md;
     ERL_NIF_TERM ret;
     
-    CHECK_OSE_CRYPTO();
 
     if (argv[0] == atom_sha) md = EVP_sha1();
 #ifdef HAVE_SHA224
@@ -1502,7 +1420,6 @@ static ERL_NIF_TERM hmac_update(ErlNifEn
     ErlNifBinary data;
     struct hmac_context* obj;
     
-    CHECK_OSE_CRYPTO();
 
     if (!enif_get_resource(env, argv[0], hmac_context_rtype, (void**)&obj)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data)) {
@@ -1529,7 +1446,6 @@ static ERL_NIF_TERM hmac_final(ErlNifEnv
     unsigned int req_len = 0;
     unsigned int mac_len;
 
-    CHECK_OSE_CRYPTO();
     
     if (!enif_get_resource(env,argv[0],hmac_context_rtype, (void**)&obj)
 	|| (argc == 2 && !enif_get_uint(env, argv[1], &req_len))) {
@@ -1564,7 +1480,6 @@ static ERL_NIF_TERM des_cbc_crypt(ErlNif
     DES_cblock ivec_clone; /* writable copy */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key) || key.size != 8
 	|| !enif_inspect_binary(env, argv[1], &ivec) || ivec.size != 8
@@ -1587,7 +1502,6 @@ static ERL_NIF_TERM des_cfb_crypt(ErlNif
     DES_cblock ivec_clone; /* writable copy */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key) || key.size != 8
 	|| !enif_inspect_binary(env, argv[1], &ivec) || ivec.size != 8
@@ -1607,7 +1521,6 @@ static ERL_NIF_TERM des_ecb_crypt(ErlNif
     ErlNifBinary key, text;
     DES_key_schedule schedule;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key) || key.size != 8 ||
 	!enif_inspect_iolist_as_binary(env, argv[1], &text) || text.size != 8) {
 	return enif_make_badarg(env);
@@ -1627,7 +1540,6 @@ static ERL_NIF_TERM des_ede3_cbc_crypt(E
     DES_cblock ivec_clone; /* writable copy */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key1) || key1.size != 8
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &key2) || key2.size != 8
@@ -1657,7 +1569,6 @@ static ERL_NIF_TERM des_ede3_cfb_crypt_n
     DES_cblock ivec_clone; /* writable copy */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key1) || key1.size != 8
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &key2) || key2.size != 8
@@ -1714,7 +1625,6 @@ static ERL_NIF_TERM aes_cfb_128_crypt(Er
     int new_ivlen = 0;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| !(key.size == 16 || key.size == 24 || key.size == 32)
@@ -1744,7 +1654,6 @@ static ERL_NIF_TERM aes_ctr_encrypt(ErlN
     unsigned int num = 0;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| AES_set_encrypt_key(key.data, key.size*8, &aes_key) != 0
@@ -1777,7 +1686,6 @@ static ERL_NIF_TERM aes_ctr_stream_encry
     unsigned char * ivec2_buf;
     unsigned char * ecount2_buf;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_get_tuple(env, argv[0], &state_arity, &state_term)
         || state_arity != 4
@@ -1816,7 +1724,6 @@ static ERL_NIF_TERM aes_gcm_encrypt(ErlN
     unsigned char *outp;
     ERL_NIF_TERM out, out_tag;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
 	|| AES_set_encrypt_key(key.data, key.size*8, &aes_key) != 0
@@ -1866,7 +1773,6 @@ static ERL_NIF_TERM aes_gcm_decrypt(ErlN
     unsigned char *outp;
     ERL_NIF_TERM out;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key)
         || AES_set_encrypt_key(key.data, key.size*8, &aes_key) != 0
@@ -1937,7 +1843,6 @@ static ERL_NIF_TERM chacha20_poly1305_en
     unsigned char poly1305_key[32];
     poly1305_state poly1305;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key) || key.size != 32
 	|| !enif_inspect_binary(env, argv[1], &iv) || iv.size != CHACHA20_NONCE_LEN
@@ -1991,7 +1896,6 @@ static ERL_NIF_TERM chacha20_poly1305_de
     unsigned char mac[POLY1305_TAG_LEN];
     poly1305_state poly1305;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key) || key.size != 32
 	|| !enif_inspect_binary(env, argv[1], &iv) || iv.size != CHACHA20_NONCE_LEN
@@ -2046,7 +1950,6 @@ static ERL_NIF_TERM aes_ecb_crypt(ErlNif
     unsigned char* ret_ptr;
     ERL_NIF_TERM ret;    
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
     || (key_bin.size != 16 && key_bin.size != 32)
@@ -2077,7 +1980,6 @@ static ERL_NIF_TERM rand_bytes_1(ErlNifE
     unsigned bytes;
     unsigned char* data;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_get_uint(env, argv[0], &bytes)) {
 	return enif_make_badarg(env);
     }
@@ -2091,7 +1993,6 @@ static ERL_NIF_TERM strong_rand_bytes_ni
     unsigned bytes;
     unsigned char* data;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_get_uint(env, argv[0], &bytes)) {
 	return enif_make_badarg(env);
     }
@@ -2109,7 +2010,6 @@ static ERL_NIF_TERM rand_bytes_3(ErlNifE
     unsigned char* data;
     unsigned top_mask, bot_mask;
     ERL_NIF_TERM ret;
-    CHECK_OSE_CRYPTO();
     if (!enif_get_uint(env, argv[0], &bytes)
 	|| !enif_get_uint(env, argv[1], &top_mask)
 	|| !enif_get_uint(env, argv[2], &bot_mask)) {
@@ -2133,7 +2033,6 @@ static ERL_NIF_TERM strong_rand_mpint_ni
     unsigned dlen;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_get_uint(env, argv[0], &bits)
 	|| !enif_get_int(env, argv[1], &top)
@@ -2203,7 +2102,6 @@ static ERL_NIF_TERM rand_uniform_nif(Erl
     unsigned dlen;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_bn_from_mpint(env, argv[0], &bn_from)
 	|| !get_bn_from_mpint(env, argv[1], &bn_rand)) {
@@ -2236,7 +2134,6 @@ static ERL_NIF_TERM mod_exp_nif(ErlNifEn
     unsigned extra_byte;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_bn_from_bin(env, argv[0], &bn_base)
 	|| !get_bn_from_bin(env, argv[1], &bn_exponent)
@@ -2280,7 +2177,6 @@ static ERL_NIF_TERM dss_verify_nif(ErlNi
     DSA *dsa;
     int i;
 
-    CHECK_OSE_CRYPTO();
 
     if (argv[0] == atom_sha) {
 	if (enif_get_tuple(env, argv[1], &tpl_arity, &tpl_terms)) {
@@ -2449,7 +2345,6 @@ static ERL_NIF_TERM rsa_verify_nif(ErlNi
     struct digest_type_t* digp = NULL;
     unsigned char* digest = NULL;
 
-    CHECK_OSE_CRYPTO();
 
     digp = get_digest_type(type);
     if (!digp) {
@@ -2511,7 +2406,6 @@ static ERL_NIF_TERM aes_cbc_crypt(ErlNif
     unsigned char* ret_ptr;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
 	|| (key_bin.size != 16 && key_bin.size != 32)
@@ -2572,7 +2466,6 @@ static ERL_NIF_TERM aes_ige_crypt_nif(Er
     unsigned char* ret_ptr;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
        || (key_bin.size != 16 && key_bin.size != 32)
@@ -2610,7 +2503,6 @@ static ERL_NIF_TERM do_exor(ErlNifEnv* e
     int i;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env,argv[0], &d1)
 	|| !enif_inspect_iolist_as_binary(env,argv[1], &d2)
@@ -2632,7 +2524,6 @@ static ERL_NIF_TERM rc4_encrypt(ErlNifEn
     RC4_KEY rc4_key;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env,argv[0], &key)
 	|| !enif_inspect_iolist_as_binary(env,argv[1], &data)) {
@@ -2650,7 +2541,6 @@ static ERL_NIF_TERM rc4_set_key(ErlNifEn
     ErlNifBinary key;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env,argv[0], &key)) {
 	return enif_make_badarg(env);
@@ -2667,7 +2557,6 @@ static ERL_NIF_TERM rc4_encrypt_with_sta
     RC4_KEY* rc4_key;
     ERL_NIF_TERM new_state, new_data;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env,argv[0], &state)
 	|| state.size != sizeof(RC4_KEY)
@@ -2689,7 +2578,6 @@ static ERL_NIF_TERM rc2_cbc_crypt(ErlNif
     ERL_NIF_TERM ret;
     unsigned char iv_copy[8];
 
-    CHECK_OSE_CRYPTO();
     
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
 	|| (key_bin.size != 5 && key_bin.size != 8 && key_bin.size != 16)
@@ -2751,7 +2639,6 @@ static ERL_NIF_TERM rsa_sign_nif(ErlNifE
     struct digest_type_t *digp;
     unsigned char* digest;
 
-    CHECK_OSE_CRYPTO();
 
     digp = get_digest_type(argv[0]);
     if (!digp) {
@@ -2819,7 +2706,6 @@ static ERL_NIF_TERM dss_sign_nif(ErlNifE
     DSA* dsa;
     int i;
 
-    CHECK_OSE_CRYPTO();
 
     if (argv[0] == atom_sha) {
 	if (enif_get_tuple(env, argv[1], &tpl_arity, &tpl_terms)) {
@@ -2906,7 +2792,6 @@ static ERL_NIF_TERM rsa_public_crypt(Erl
     int padding, i;
     RSA* rsa;
 
-    CHECK_OSE_CRYPTO();
 
     rsa = RSA_new();
 
@@ -2956,7 +2841,6 @@ static ERL_NIF_TERM rsa_private_crypt(Er
     int padding, i;
     RSA* rsa;
 
-    CHECK_OSE_CRYPTO();
 
     rsa = RSA_new();
 
@@ -3004,7 +2888,6 @@ static ERL_NIF_TERM dh_generate_paramete
     unsigned char *p_ptr, *g_ptr;
     ERL_NIF_TERM ret_p, ret_g;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_get_int(env, argv[0], &prime_len)
 	|| !enif_get_int(env, argv[1], &generator)) {
@@ -3033,7 +2916,6 @@ static ERL_NIF_TERM dh_check(ErlNifEnv*
     int i;
     ERL_NIF_TERM ret, head, tail;
 
-    CHECK_OSE_CRYPTO();
 
     dh_params = DH_new();
 
@@ -3070,7 +2952,6 @@ static ERL_NIF_TERM dh_generate_key_nif(
     int mpint; /* 0 or 4 */
     unsigned long len = 0;
 
-    CHECK_OSE_CRYPTO();
 
     dh_params = DH_new();
 
@@ -3126,7 +3007,6 @@ static ERL_NIF_TERM dh_compute_key_nif(E
     ErlNifBinary ret_bin;
     ERL_NIF_TERM ret, head, tail;
 
-    CHECK_OSE_CRYPTO();
 
     dh_params = DH_new();
 
@@ -3168,7 +3048,6 @@ static ERL_NIF_TERM srp_value_B_nif(ErlN
     unsigned dlen;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_bn_from_bin(env, argv[0], &bn_multiplier)
 	|| !get_bn_from_bin(env, argv[1], &bn_verifier)
@@ -3230,7 +3109,6 @@ static ERL_NIF_TERM srp_user_secret_nif(
     unsigned dlen;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_bn_from_bin(env, argv[0], &bn_a)
 	|| !get_bn_from_bin(env, argv[1], &bn_u)
@@ -3311,7 +3189,6 @@ static ERL_NIF_TERM srp_host_secret_nif(
     unsigned dlen;
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_bn_from_bin(env, argv[0], &bn_verifier)
 	|| !get_bn_from_bin(env, argv[1], &bn_b)
@@ -3373,7 +3250,6 @@ static ERL_NIF_TERM bf_cfb64_crypt(ErlNi
     int bf_n = 0; /* blowfish ivec pos */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
 	|| !enif_inspect_binary(env, argv[1], &ivec_bin)
@@ -3398,7 +3274,6 @@ static ERL_NIF_TERM bf_cbc_crypt(ErlNifE
     unsigned char bf_tkey[8]; /* blowfish ivec */    
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
 	|| !enif_inspect_binary(env, argv[1], &ivec_bin)
@@ -3423,7 +3298,6 @@ static ERL_NIF_TERM bf_ecb_crypt(ErlNifE
     BF_KEY bf_key; /* blowfish key 8 */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
 	|| !enif_inspect_iolist_as_binary(env, argv[1], &data_bin)
@@ -3445,7 +3319,6 @@ static ERL_NIF_TERM blowfish_ofb64_encry
     int bf_n = 0; /* blowfish ivec pos */
     ERL_NIF_TERM ret;
 
-    CHECK_OSE_CRYPTO();
 
     if (!enif_inspect_iolist_as_binary(env, argv[0], &key_bin)
 	|| !enif_inspect_binary(env, argv[1], &ivec_bin)
@@ -3773,7 +3646,6 @@ static ERL_NIF_TERM ec_key_generate(ErlN
     ERL_NIF_TERM priv_key;
     ERL_NIF_TERM pub_key = atom_undefined;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_ec_key(env, argv[0], argv[1], atom_undefined, &key))
 	goto badarg;
@@ -3816,7 +3688,6 @@ static ERL_NIF_TERM ecdsa_sign_nif(ErlNi
     struct digest_type_t *digp;
     unsigned char* digest;
 
-    CHECK_OSE_CRYPTO();
 
     digp = get_digest_type(argv[0]);
     if (!digp) {
@@ -3885,7 +3756,6 @@ static ERL_NIF_TERM ecdsa_verify_nif(Erl
     struct digest_type_t* digp = NULL;
     unsigned char* digest = NULL;
 
-    CHECK_OSE_CRYPTO();
 
     digp = get_digest_type(type);
     if (!digp) {
@@ -3950,7 +3820,6 @@ static ERL_NIF_TERM ecdh_compute_key_nif
     EC_POINT *my_ecpoint;
     EC_KEY *other_ecdh = NULL;
 
-    CHECK_OSE_CRYPTO();
 
     if (!get_ec_key(env, argv[1], argv[2], atom_undefined, &key))
 	return enif_make_badarg(env);
@@ -3995,7 +3864,6 @@ out_err:
 static ERL_NIF_TERM rand_seed_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {
     ErlNifBinary seed_bin;
-    CHECK_OSE_CRYPTO();
     if (!enif_inspect_binary(env, argv[0], &seed_bin))
         return enif_make_badarg(env);
     RAND_seed(seed_bin.data,seed_bin.size);
diff -Ndurp otp_src_18.3.4.5/lib/crypto/c_src/Makefile.in otp_src_18.3.4.5-remove-OSE-port/lib/crypto/c_src/Makefile.in
--- otp_src_18.3.4.5/lib/crypto/c_src/Makefile.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/crypto/c_src/Makefile.in	2017-02-03 21:52:59.167951112 +0200
@@ -127,12 +127,7 @@ ALL_STATIC_CFLAGS = $(DED_STATIC_CFLAGS)
 
 _create_dirs := $(shell mkdir -p $(OBJDIR) $(LIBDIR))
 
-ifneq ($(findstring ose,$(TARGET)),ose)
 debug opt valgrind: $(NIF_LIB) $(CALLBACK_LIB)
-else
-# Do not build dynamic files on OSE
-debug opt valgrind:
-endif
 
 static_lib: $(NIF_ARCHIVE)
 
@@ -203,14 +198,12 @@ release_spec: opt
 	$(INSTALL_DIR) "$(RELSYSDIR)/priv/obj"
 	$(INSTALL_DIR) "$(RELSYSDIR)/priv/lib"
 	$(INSTALL_DATA) $(NIF_MAKEFILE) "$(RELSYSDIR)/priv/obj"
-ifneq ($(findstring ose,$(TARGET)),ose)
 	$(INSTALL_PROGRAM) $(CRYPTO_OBJS) "$(RELSYSDIR)/priv/obj"
 	$(INSTALL_PROGRAM) $(NIF_LIB) "$(RELSYSDIR)/priv/lib"
 ifeq ($(DYNAMIC_CRYPTO_LIB),yes)
 	$(INSTALL_PROGRAM) $(CALLBACK_OBJS) "$(RELSYSDIR)/priv/obj"
 	$(INSTALL_PROGRAM) $(CALLBACK_LIB) "$(RELSYSDIR)/priv/lib"
 endif
-endif
 
 release_docs_spec:
 
diff -Ndurp otp_src_18.3.4.5/lib/crypto/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/crypto/Makefile
--- otp_src_18.3.4.5/lib/crypto/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/crypto/Makefile	2017-02-03 21:52:59.167951112 +0200
@@ -24,11 +24,7 @@ include $(ERL_TOP)/make/$(TARGET)/otp.mk
 # Macros
 #
 
-ifneq ($(findstring ose,$(TARGET)),ose)
 SUB_DIRECTORIES = src c_src doc/src
-else
-SUB_DIRECTORIES =  src doc/src
-endif
 static_lib: SUB_DIRECTORIES = c_src
 
 include vsn.mk
diff -Ndurp otp_src_18.3.4.5/lib/crypto/test/crypto_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/crypto/test/crypto_SUITE.erl
--- otp_src_18.3.4.5/lib/crypto/test/crypto_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/crypto/test/crypto_SUITE.erl	2017-02-03 21:52:59.167951112 +0200
@@ -118,10 +118,10 @@ init_per_suite(Config) ->
 		_ ->
 		    Config
 	    catch error:low_entropy ->
-		    %% Make sure we are on OSE, otherwise we want to crash
-		    {ose,_} = os:type(),
+                    %% We are testing on an OS with low entropy in its random
+                    %% seed. So we have to seed it with a binary to get started.
 
-		    %% This is NOT how you want to seed this, it is just here
+		    %% This is NOT how you want to do seeding, it is just here
 		    %% to make the tests pass. Check your OS manual for how you
 		    %% really want to seed.
 		    {H,M,L} = erlang:now(),
diff -Ndurp otp_src_18.3.4.5/lib/hipe/cerl/erl_bif_types.erl otp_src_18.3.4.5-remove-OSE-port/lib/hipe/cerl/erl_bif_types.erl
--- otp_src_18.3.4.5/lib/hipe/cerl/erl_bif_types.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/hipe/cerl/erl_bif_types.erl	2017-02-03 21:52:59.167951112 +0200
@@ -926,8 +926,7 @@ type(erlang, system_info, 1, Xs, Opaques
 		     t_list(t_pid());
 		   ['os_type'] ->
 		     t_tuple([t_sup([t_atom('unix'),
-				     t_atom('win32'),
-				     t_atom('ose')]),
+				     t_atom('win32')]),
 			      t_atom()]);
 		   ['os_version'] ->
 		     t_sup(t_tuple([t_non_neg_fixnum(),
diff -Ndurp otp_src_18.3.4.5/lib/kernel/doc/src/notes.xml otp_src_18.3.4.5-remove-OSE-port/lib/kernel/doc/src/notes.xml
--- otp_src_18.3.4.5/lib/kernel/doc/src/notes.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/doc/src/notes.xml	2017-02-03 21:52:59.167951112 +0200
@@ -623,8 +623,7 @@
 	    Erlang/OTP has been ported to the realtime operating
 	    system OSE. The port supports both smp and non-smp
 	    emulator. For details around the port and how to started
-	    see the User's Guide in the <seealso
-	    marker="ose:ose_intro">ose</seealso> application. </p>
+	    see the User's Guide in the ose application. </p>
           <p>
 	    Note that not all parts of Erlang/OTP has been ported. </p>
           <p>
diff -Ndurp otp_src_18.3.4.5/lib/kernel/doc/src/ref_man.xml.src otp_src_18.3.4.5-remove-OSE-port/lib/kernel/doc/src/ref_man.xml.src
--- otp_src_18.3.4.5/lib/kernel/doc/src/ref_man.xml.src	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/doc/src/ref_man.xml.src	1970-01-01 03:00:00.000000000 +0300
@@ -1,68 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE application SYSTEM "application.dtd">
-
-<application xmlns:xi="http://www.w3.org/2001/XInclude">
-  <header>
-    <copyright>
-      <year>1996</year><year>2013</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>Kernel Reference Manual</title>
-    <prepared></prepared>
-    <docno></docno>
-    <date></date>
-    <rev></rev>
-  </header>
-  <description>
-    <p>The <em>Kernel</em> application has all the code necessary to run
-      the Erlang runtime system itself: file servers and code servers
-      and so on.</p>
-  </description>
-  <xi:include href="kernel_app.xml"/>
-  <xi:include href="application.xml"/>
-  <xi:include href="auth.xml"/>
-  <xi:include href="code.xml"/>
-  <xi:include href="disk_log.xml"/>
-  <xi:include href="erl_boot_server.xml"/>
-  <xi:include href="erl_ddll.xml"/>
-  <xi:include href="erl_prim_loader_stub.xml"/>
-  <xi:include href="erlang_stub.xml"/>
-  <xi:include href="error_handler.xml"/>
-  <xi:include href="error_logger.xml"/>
-  <xi:include href="file.xml"/>
-  <xi:include href="gen_tcp.xml"/>
-  <xi:include href="gen_udp.xml"/>
-  <xi:include href="gen_sctp.xml"/>
-  <xi:include href="global.xml"/>
-  <xi:include href="global_group.xml"/>
-  <xi:include href="heart.xml"/>
-  <xi:include href="inet.xml"/>
-  <xi:include href="inet_res.xml"/>
-  <xi:include href="init_stub.xml"/>
-  <xi:include href="net_adm.xml"/>
-  <xi:include href="net_kernel.xml"/>
-  <xi:include href="os.xml"/>
-  <xi:include href="pg2.xml"/>
-  <xi:include href="rpc.xml"/>
-  <xi:include href="seq_trace.xml"/>
-  <xi:include href="user.xml"/>
-  <xi:include href="wrap_log_reader.xml"/>
-  <xi:include href="zlib_stub.xml"/>
-  <xi:include href="app.xml"/>
-  <xi:include href="config.xml"/>
-</application>
diff -Ndurp otp_src_18.3.4.5/lib/kernel/src/inet_config.erl otp_src_18.3.4.5-remove-OSE-port/lib/kernel/src/inet_config.erl
--- otp_src_18.3.4.5/lib/kernel/src/inet_config.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/src/inet_config.erl	2017-02-03 21:52:59.167951112 +0200
@@ -188,9 +188,6 @@ do_load_resolv({win32,Type}, longnames)
     win32_load_from_registry(Type),
     inet_db:set_lookup([native]);
 
-do_load_resolv({ose,_}, _) ->
-    inet_db:set_lookup([file]);
-
 do_load_resolv(_, _) ->
     inet_db:set_lookup([native]).
 
diff -Ndurp otp_src_18.3.4.5/lib/kernel/src/os.erl otp_src_18.3.4.5-remove-OSE-port/lib/kernel/src/os.erl
--- otp_src_18.3.4.5/lib/kernel/src/os.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/src/os.erl	2017-02-03 21:52:59.167951112 +0200
@@ -93,7 +93,7 @@ unsetenv(_) ->
 %%% End of BIFs
 
 -spec type() -> {Osfamily, Osname} when
-      Osfamily :: unix | win32 | ose,
+      Osfamily :: unix | win32,
       Osname :: atom().
 
 type() ->
diff -Ndurp otp_src_18.3.4.5/lib/kernel/test/erl_prim_loader_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/erl_prim_loader_SUITE.erl
--- otp_src_18.3.4.5/lib/kernel/test/erl_prim_loader_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/erl_prim_loader_SUITE.erl	2017-02-03 21:52:59.167951112 +0200
@@ -260,46 +260,41 @@ multiple_slaves(doc) ->
     ["Start nodes in parallell, all using the 'inet' loading method, ",
      "verify that the boot server manages"];
 multiple_slaves(Config) when is_list(Config) ->
-    case os:type() of
-	{ose,_} ->
-	    {comment, "OSE: multiple nodes not supported"};
-	_ ->
-	    ?line Name = erl_prim_test_multiple_slaves,
-	    ?line Host = host(),
-	    ?line Cookie = atom_to_list(erlang:get_cookie()),
-	    ?line IpStr = ip_str(Host),
-	    ?line LFlag = get_loader_flag(os:type()),
-	    ?line Args = LFlag ++ " -hosts " ++ IpStr ++
-		" -setcookie " ++ Cookie,
+    ?line Name = erl_prim_test_multiple_slaves,
+    ?line Host = host(),
+    ?line Cookie = atom_to_list(erlang:get_cookie()),
+    ?line IpStr = ip_str(Host),
+    ?line LFlag = get_loader_flag(os:type()),
+    ?line Args = LFlag ++ " -hosts " ++ IpStr ++
+        " -setcookie " ++ Cookie,
 
-	    NoOfNodes = 10,			% no of slave nodes to be started
+    NoOfNodes = 10,			% no of slave nodes to be started
 
-	    NamesAndNodes = 
-		lists:map(fun(N) ->
-				  NameN = atom_to_list(Name) ++ 
-				          integer_to_list(N),
-				  NodeN = NameN ++ "@" ++ Host,
-				  {list_to_atom(NameN),list_to_atom(NodeN)}
-			  end, lists:seq(1, NoOfNodes)),
+    NamesAndNodes = 
+        lists:map(fun(N) ->
+                          NameN = atom_to_list(Name) ++ 
+                              integer_to_list(N),
+                          NodeN = NameN ++ "@" ++ Host,
+                          {list_to_atom(NameN),list_to_atom(NodeN)}
+                  end, lists:seq(1, NoOfNodes)),
 
-	    ?line Nodes = start_multiple_nodes(NamesAndNodes, Args, []),
+    ?line Nodes = start_multiple_nodes(NamesAndNodes, Args, []),
 
-	    %% "queue up" the nodes to wait for the boot server to respond
-	    %% (note: test_server supervises each node start by accept()
-	    %% on a socket, the timeout value for the accept has to be quite 
-	    %% long for this test to work).
-	    ?line test_server:sleep(test_server:seconds(5)),
-	    %% start the code loading circus!
-	    ?line {ok,BootPid} = erl_boot_server:start_link([Host]),
-	    %% give the nodes a chance to boot up before attempting to stop them
-	    ?line test_server:sleep(test_server:seconds(10)),
+    %% "queue up" the nodes to wait for the boot server to respond
+    %% (note: test_server supervises each node start by accept()
+    %% on a socket, the timeout value for the accept has to be quite 
+    %% long for this test to work).
+    ?line test_server:sleep(test_server:seconds(5)),
+    %% start the code loading circus!
+    ?line {ok,BootPid} = erl_boot_server:start_link([Host]),
+    %% give the nodes a chance to boot up before attempting to stop them
+    ?line test_server:sleep(test_server:seconds(10)),
 
-	    ?line wait_and_shutdown(lists:reverse(Nodes), 30),
+    ?line wait_and_shutdown(lists:reverse(Nodes), 30),
 
-	    ?line unlink(BootPid),
-	    ?line exit(BootPid, kill),
-	    ok
-    end.
+    ?line unlink(BootPid),
+    ?line exit(BootPid, kill),
+    ok.
 
 start_multiple_nodes([{Name,Node} | NNs], Args, Started) ->
     ?line {ok,Node} = start_node(Name, Args, [{wait, false}]),
diff -Ndurp otp_src_18.3.4.5/lib/kernel/test/file_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/file_SUITE.erl
--- otp_src_18.3.4.5/lib/kernel/test/file_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/file_SUITE.erl	2017-02-03 21:52:59.171950956 +0200
@@ -168,12 +168,7 @@ init_per_suite(Config) when is_list(Conf
 		     ok ->
 			 [{sasl,started}]
 		 end,
-    ok = case os:type() of
-	     {ose,_} ->
-		 ok;
-	     _ ->
-		 application:start(os_mon)
-	 end,
+    application:start(os_mon),
 
     case os:type() of
 	{win32, _} ->
@@ -199,12 +194,7 @@ end_per_suite(Config) when is_list(Confi
 	    ok
     end,
 
-    case os:type() of
-	{ose,_} ->
-	    ok;
-	_ ->
-	    application:stop(os_mon)
-    end,
+    application:stop(os_mon),
     case proplists:get_value(sasl, Config) of
 	started ->
 	    application:stop(sasl);
@@ -889,10 +879,7 @@ open1(Config) when is_list(Config) ->
     ?line io:format(Fd1,Str,[]),
     ?line {ok,0} = ?FILE_MODULE:position(Fd1,bof),
     ?line Str = io:get_line(Fd1,''),
-    ?line case io:get_line(Fd2,'') of
-	      Str -> Str;
-	      eof -> Str
-	  end,
+    ?line Str = io:get_line(Fd2,''),
     ?line ok = ?FILE_MODULE:close(Fd2),
     ?line {ok,0} = ?FILE_MODULE:position(Fd1,bof),
     ?line ok = ?FILE_MODULE:truncate(Fd1),
@@ -2368,9 +2355,6 @@ e_rename(Config) when is_list(Config) ->
 	    %% At least Windows NT can 
 	    %% successfully move a file to
 	    %% another drive.
-	    ok;
-	{ose, _} ->
-	    %% disabled for now
 	    ok
     end,
     [] = flush(),
diff -Ndurp otp_src_18.3.4.5/lib/kernel/test/gen_tcp_misc_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/gen_tcp_misc_SUITE.erl
--- otp_src_18.3.4.5/lib/kernel/test/gen_tcp_misc_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/gen_tcp_misc_SUITE.erl	2017-02-03 21:52:59.171950956 +0200
@@ -58,14 +58,6 @@
 	 oct_acceptor/1,
 	 otp_7731_server/1, zombie_server/2, do_iter_max_socks/2]).
 
-init_per_testcase(wrapping_oct, Config) when is_list(Config) ->
-    Dog = case os:type() of
-	      {ose,_} ->
-		  test_server:timetrap(test_server:minutes(20));
-	      _Else ->
-		  test_server:timetrap(test_server:seconds(600))
-	  end,
-    [{watchdog, Dog}|Config];
 init_per_testcase(iter_max_socks, Config) when is_list(Config) ->
     Dog = case os:type() of
               {win32,_} ->
@@ -74,14 +66,6 @@ init_per_testcase(iter_max_socks, Config
                   test_server:timetrap(test_server:seconds(240))
           end,
     [{watchdog, Dog}|Config];
-init_per_testcase(accept_system_limit, Config) when is_list(Config) ->
-    case os:type() of
-        {ose,_} ->
-            {skip,"Skip in OSE"};
-        _ ->
-            Dog = test_server:timetrap(test_server:seconds(240)),
-            [{watchdog,Dog}|Config]
-    end;
 init_per_testcase(wrapping_oct, Config) when is_list(Config) ->
     Dog = test_server:timetrap(test_server:seconds(600)),
     [{watchdog, Dog}|Config];
diff -Ndurp otp_src_18.3.4.5/lib/kernel/test/prim_file_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/prim_file_SUITE.erl
--- otp_src_18.3.4.5/lib/kernel/test/prim_file_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/kernel/test/prim_file_SUITE.erl	2017-02-03 21:52:59.171950956 +0200
@@ -455,10 +455,7 @@ open1(Config) when is_list(Config) ->
     ?line ?PRIM_FILE:write(Fd1,Str),
     ?line {ok,0} = ?PRIM_FILE:position(Fd1,bof),
     ?line {ok, Str} = ?PRIM_FILE:read(Fd1,Length),
-    ?line case ?PRIM_FILE:read(Fd2,Length) of
-	      {ok,Str} -> Str;
-	      eof -> Str
-	  end,
+    ?line {ok, Str} = ?PRIM_FILE:read(Fd2,Length),
     ?line ok = ?PRIM_FILE:close(Fd2),
     ?line {ok,0} = ?PRIM_FILE:position(Fd1,bof),
     ?line ok = ?PRIM_FILE:truncate(Fd1),
@@ -1629,7 +1626,7 @@ e_rename(Config) when is_list(Config) ->
 	    %% successfully move a file to
 	    %% another drive.
 	    ok;
-	{unix, _ } ->
+	_ ->
 	    OtherFs = "/tmp",
 	    ?line NameOnOtherFs =
 	    filename:join(OtherFs, 
@@ -1653,10 +1650,7 @@ e_rename(Config) when is_list(Config) ->
 		Else ->
 		    Else
 	    end,
-	    Com;
-	{ose, _} ->
-	    %% disabled for now
-	    ok
+	    Com
     end,
     ?line test_server:timetrap_cancel(Dog),
     Comment.
diff -Ndurp otp_src_18.3.4.5/lib/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/Makefile
--- otp_src_18.3.4.5/lib/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/Makefile	2017-02-03 21:52:59.171950956 +0200
@@ -36,7 +36,7 @@ ALL_ERLANG_APPLICATIONS = xmerl edoc erl
 	          public_key ssl observer odbc diameter \
 	          cosTransactions cosEvent cosTime cosNotification \
 	          cosProperty cosFileTransfer cosEventDomain et megaco webtool \
-		  eunit ssh typer percept eldap dialyzer hipe ose
+		  eunit ssh typer percept eldap dialyzer hipe
 
 ifdef BUILD_ALL
   ERLANG_APPLICATIONS += $(ALL_ERLANG_APPLICATIONS)
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/book.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/book.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/book.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/book.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,49 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE book SYSTEM "book.dtd">
-
-<book xmlns:xi="http://www.w3.org/2001/XInclude">
-  <header titlestyle="normal">
-    <copyright>
-      <year>2014</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>OSE</title>
-    <prepared>Lukas Larsson</prepared>
-    <docno></docno>
-    <date>2014-01-08</date>
-    <rev>1.0</rev>
-    <file>book.xml</file>
-  </header>
-  <insidecover>
-  </insidecover>
-  <pagetext>OSE</pagetext>
-  <preamble>
-    <contents level="2"></contents>
-  </preamble>
-  <parts>
-    <xi:include href="part.xml"/>
-  </parts>
-  <applications>
-    <xi:include href="ref_man.xml"/>
-  </applications>
-  <releasenotes>
-    <xi:include href="notes.xml"/>
-  </releasenotes>
-  <listofterms></listofterms>
-  <index></index>
-</book>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/Makefile
--- otp_src_18.3.4.5/lib/ose/doc/src/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/Makefile	1970-01-01 03:00:00.000000000 +0300
@@ -1,133 +0,0 @@
-#
-# %CopyrightBegin%
-#
-# Copyright Ericsson AB 1997-2012. All Rights Reserved.
-#
-# Licensed under the Apache License, Version 2.0 (the "License");
-# you may not use this file except in compliance with the License.
-# You may obtain a copy of the License at
-#
-#     http://www.apache.org/licenses/LICENSE-2.0
-#
-# Unless required by applicable law or agreed to in writing, software
-# distributed under the License is distributed on an "AS IS" BASIS,
-# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-# See the License for the specific language governing permissions and
-# limitations under the License.
-#
-# %CopyrightEnd%
-#
-include $(ERL_TOP)/make/target.mk
-include $(ERL_TOP)/make/$(TARGET)/otp.mk
-
-# ----------------------------------------------------
-# Application version
-# ----------------------------------------------------
-include ../../vsn.mk
-VSN=$(OSE_VSN)
-APPLICATION=ose
-
-# ----------------------------------------------------
-# Release directory specification
-# ----------------------------------------------------
-RELSYSDIR = $(RELEASE_PATH)/lib/$(APPLICATION)-$(VSN)
-
-# ----------------------------------------------------
-# Help application directory specification
-# ----------------------------------------------------
-EDOC_DIR = $(ERL_TOP)/lib/edoc
-SYNTAX_TOOLS_DIR = $(ERL_TOP)/lib/syntax_tools
-
-# ----------------------------------------------------
-# Target Specs
-# ----------------------------------------------------
-XML_APPLICATION_FILES = ref_man.xml
-
-XML_REF3_FILES = \
-	ose.xml \
-	ose_erl_driver.xml
-
-XML_REF6_FILES = ose_app.xml
-
-XML_PART_FILES = part.xml
-XML_CHAPTER_FILES = notes.xml ose_intro.xml ose_signals_chapter.xml
-
-BOOK_FILES = book.xml
-
-XML_FILES = \
-	$(BOOK_FILES) $(XML_CHAPTER_FILES) \
-	$(XML_PART_FILES) $(XML_REF3_FILES) $(XML_REF6_FILES) \
-	$(XML_APPLICATION_FILES)
-
-# ----------------------------------------------------
-
-HTML_FILES = $(XML_APPLICATION_FILES:%.xml=$(HTMLDIR)/%.html) \
-	$(XML_PART_FILES:%.xml=$(HTMLDIR)/%.html)
-
-INFO_FILE = ../../info
-
-MAN3_FILES = $(XML_REF3_FILES:%.xml=$(MAN3DIR)/%.3)
-MAN6_FILES = $(XML_REF6_FILES:%_app.xml=$(MAN6DIR)/%.6)
-
-HTML_REF_MAN_FILE = $(HTMLDIR)/index.html
-
-TOP_PDF_FILE = $(PDFDIR)/$(APPLICATION)-$(VSN).pdf
-
-SPECS_FILES =
-
-TOP_SPECS_FILE =
-
-# ----------------------------------------------------
-# FLAGS
-# ----------------------------------------------------
-XML_FLAGS +=
-
-SPECS_FLAGS = -I../../include -I../../../kernel/include
-
-OSE_SRC_DIR = ../../src
-
-# ----------------------------------------------------
-# Targets
-# ----------------------------------------------------
-docs: man pdf html
-
-$(TOP_PDF_FILE): $(XML_FILES)
-
-pdf: $(TOP_PDF_FILE)
-
-html: $(HTML_REF_MAN_FILE)
-
-man: $(MAN3_FILES) $(MAN6_FILES)
-
-ose.xml: $(OSE_SRC_DIR)/ose.erl
-	escript $(DOCGEN)/priv/bin/xml_from_edoc.escript\
-	 $(OSE_SRC_DIR)/$(@:%.xml=%.erl)
-
-debug opt:
-
-clean clean_docs:
-	rm -rf $(HTMLDIR)/*
-	rm -f $(MAN3DIR)/*
-	rm -f $(MAN6DIR)/*
-	rm -f $(TOP_PDF_FILE) $(TOP_PDF_FILE:%.pdf=%.fo)
-	rm -f $(SPECDIR)/*
-	rm -f errs core *~
-
-# ----------------------------------------------------
-# Release Target
-# ----------------------------------------------------
-include $(ERL_TOP)/make/otp_release_targets.mk
-
-release_docs_spec: docs
-	$(INSTALL_DIR) "$(RELSYSDIR)/doc/pdf"
-	$(INSTALL_DATA) $(TOP_PDF_FILE) "$(RELSYSDIR)/doc/pdf"
-	$(INSTALL_DIR) "$(RELSYSDIR)/doc/html"
-	$(INSTALL_DATA) $(HTMLDIR)/* \
-		"$(RELSYSDIR)/doc/html"
-	$(INSTALL_DATA) $(INFO_FILE) "$(RELSYSDIR)"
-	$(INSTALL_DIR) "$(RELEASE_PATH)/man/man3"
-	$(INSTALL_DATA) $(MAN3DIR)/* "$(RELEASE_PATH)/man/man3"
-	$(INSTALL_DIR) "$(RELEASE_PATH)/man/man6"
-	$(INSTALL_DATA) $(MAN6_FILES) "$(RELEASE_PATH)/man/man6"
-
-release_spec:
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/notes.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/notes.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/notes.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/notes.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,109 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE chapter SYSTEM "chapter.dtd">
-
-<chapter>
-  <header>
-    <copyright>
-      <year>2014</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>OSE Release Notes</title>
-    <prepared></prepared>
-    <docno></docno>
-    <date></date>
-    <rev></rev>
-    <file>notes.xml</file>
-  </header>
-  <p>This document describes the changes made to the OSE application.</p>
-
-<section><title>Ose 1.1</title>
-
-    <section><title>Improvements and New Features</title>
-      <list>
-        <item>
-          <p>
-	    Change license text from Erlang Public License to Apache
-	    Public License v2</p>
-          <p>
-	    Own Id: OTP-12845</p>
-        </item>
-      </list>
-    </section>
-
-</section>
-
-<section><title>Ose 1.0.2</title>
-
-    <section><title>Fixed Bugs and Malfunctions</title>
-      <list>
-        <item>
-          <p>
-	    Add missing release notes for the OSE application.</p>
-          <p>
-	    Own Id: OTP-12177</p>
-        </item>
-      </list>
-    </section>
-
-</section>
-
-<section><title>Ose 1.0.1</title>
-
-    <section><title>Fixed Bugs and Malfunctions</title>
-      <list>
-        <item>
-          <p>
-	    Fix some spelling mistakes in documentation</p>
-          <p>
-	    Own Id: OTP-12152</p>
-        </item>
-      </list>
-    </section>
-
-</section>
-
-<section><title>Ose 1.0</title>
-
-    <section><title>Improvements and New Features</title>
-      <list>
-        <item>
-          <p>
-	    Erlang/OTP has been ported to the realtime operating
-	    system OSE. The port supports both smp and non-smp
-	    emulator. For details around the port and how to started
-	    see the User's Guide in the <seealso
-	    marker="ose:ose_intro">ose</seealso> application. </p>
-          <p>
-	    Note that not all parts of Erlang/OTP has been ported. </p>
-          <p>
-	    Notable things that work are: non-smp and smp emulators,
-	    OSE signal interaction, crypto, asn1, run_erl/to_erl,
-	    tcp, epmd, distribution and most if not all non-os
-	    specific functionality of Erlang.</p>
-          <p>
-	    Notable things that does not work are: udp/sctp, os_mon,
-	    erl_interface, binding of schedulers.</p>
-          <p>
-	    Own Id: OTP-11334</p>
-        </item>
-      </list>
-    </section>
-
-</section>
-
-</chapter>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/ose_app.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_app.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/ose_app.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_app.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,38 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE appref SYSTEM "appref.dtd">
-
-<appref>
-  <header>
-    <copyright>
-      <year>2014</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>Enea OSE</title>
-    <prepared></prepared>
-    <docno></docno>
-    <date></date>
-    <rev></rev>
-  </header>
-  <app>ose</app>
-  <appsummary>The OSE Application</appsummary>
-  <description>
-    <p>The OSE application contains modules and documentation that only
-    applies when running Erlang/OTP on Enea OSE.</p>
-  </description>
-
-</appref>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/ose_erl_driver.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_erl_driver.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/ose_erl_driver.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_erl_driver.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,111 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE cref SYSTEM "cref.dtd">
-
-<cref>
-  <header>
-    <copyright>
-      <year>2013</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>erl_driver for Enea OSE</title>
-    <prepared>Lukas Larsson</prepared>
-    <docno></docno>
-    <date>2014-01-08</date>
-    <rev>A</rev>
-    <file>ose_erl_driver.xml</file>
-  </header>
-  <lib>ose_erl_driver</lib>
-  <libsummary>Linked-in drivers in Enea OSE</libsummary>
-  <description>
-    <p>Writing Linked-in drivers that also work on Enea OSE is very similar for
-    how you would do it for Unix. The difference from Unix is that
-    driver_select, ready_input and ready_output all work with signals
-    instead of file descriptors. This means that the driver_select is
-    used to specify which type of signal should trigger calls to
-    ready_input/ready_output. The functions described below are available
-    to driver programmers on Enea OSE to facilitate this.
-    </p>
-  </description>
-  <section>
-    <title>DATA TYPES</title>
-
-    <taglist>
-      <tag><marker id="union_SIGNAL"/>union SIGNAL</tag>
-      <item>See the Enea OSE SPI documentation for a description.</item>
-      <tag><marker id="SIGSELECT"/>SIGSELECT</tag>
-      <item>See the Enea OSE SPI documentation for a description.</item>
-      <tag><marker id="ErlDrvEvent"/>ErlDrvEvent</tag>
-      <item>The <c>ErlDrvEvent</c> is a handle to a signal number and id combination. It is passed to <seealso marker="erts:erl_driver#driver_select">driver_select(3)</seealso>.</item>
-      <tag><marker id="ErlDrvOseEventId"/>ErlDrvOseEventId</tag>
-      <item>This is the id used to associate a specific signal to a
-      certain driver instance. </item>
-    </taglist>
-  </section>
-  <funcs>
-    <func>
-      <name><ret>union SIGNAL *</ret><nametext>erl_drv_ose_get_signal(ErlDrvEvent drv_event)</nametext></name>
-      <desc>
-        <marker id="erl_drv_ose_get_signal"></marker>
-        <p>Fetch the next signal associated with <c>drv_event</c>.
-	Signals will be returned in the order which they were received and
-	when no more signals are available <c>NULL</c> will be returned.
-	Use this function in the ready_input/ready_output callbacks
-	to get signals.</p>
-      </desc>
-    </func>
-    <func>
-      <name><ret>ErlDrvEvent</ret><nametext>erl_drv_ose_event_alloc(SIGSELECT signo, ErlDrvOseEventId id, ErlDrvOseEventId (*resolve_signal)(union SIGNAL* sig), void *extra)</nametext></name>
-      <desc>
-        <marker id="erl_drv_ose_event_alloc"></marker>
-        <p>Create a new <c>ErlDrvEvent</c> associated with <c>signo</c>,
-	<c>id</c> and uses the <c>resolve_signal</c> function to extract
-	the <c>id</c> from a signal with <c>signo</c>. The <c>extra</c>
-	parameter can be used for additional data. See
-	<seealso marker="ose_signals_chapter#driver">
-	Signals in a Linked-in driver</seealso> in the OSE User's Guide.
-      </p>
-      </desc>
-    </func>
-    <func>
-      <name><ret>void</ret><nametext>erl_drv_ose_event_free(ErlDrvEvent drv_event)</nametext></name>
-      <desc>
-        <marker id="erl_drv_ose_event_free"></marker>
-        <p>Free a <c>ErlDrvEvent</c>. This should always be done in the
-	<seealso marker="erts:driver_entry#stop_select">stop_select</seealso>
-	callback when the event is no longer being used.</p>
-      </desc>
-    </func>
-    <func>
-      <name><ret>void</ret><nametext>erl_drv_ose_event_fetch(ErlDrvEvent drv_event, SIGSELECT *signo, ErlDrvOseEventId *id, void **extra)</nametext></name>
-      <desc>
-        <marker id="erl_drv_ose_event_fetch"></marker>
-        <p>Write the signal number, id and any extra data associated with <c>drv_event</c>
-	into <c>*signo</c> and <c>*id</c> respectively. <c>NULL</c> can be
-	also passed as <c>signo</c> or <c>id</c> in order to ignore that field.
-	</p>
-      </desc>
-    </func>
-  </funcs>
-  <section>
-    <title>SEE ALSO</title>
-    <p>
-      <seealso marker="erts:driver_entry">driver_entry(3)</seealso>,
-      <seealso marker="erts:erl_driver">erl_driver(3)</seealso>
-    </p>
-  </section>
-</cref>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/ose_intro.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_intro.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/ose_intro.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_intro.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,154 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE chapter SYSTEM "chapter.dtd">
-
-<chapter>
-  <header>
-    <copyright>
-      <year>2013</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>Introduction</title>
-    <prepared>Lukas Larsson</prepared>
-    <docno></docno>
-    <date>2014-01-08</date>
-    <rev>A</rev>
-    <file>ose_intro.xml</file>
-  </header>
-
-  <section>
-    <title>Features</title>
-  </section>
-
-  <section>
-    <title>Starting Erlang/OTP</title>
-    <p>
-      Starting Erlang/OTP on OSE is not as simple as on Unix/Windows (yet).
-      First of all you have to explicitly use the beam (or beam.smp) executables
-      found in erts-X.Y.Z/bin as the load module that you run. This in turn
-      means that you have to supply the raw beam arguments to the emulator
-      when starting. Fortunately <c>erl</c> on Unix/Windows has a
-      undocumented flag called <c>-emu_args_exit</c> that can be used to
-      figure out what the arguments to beam look like. For example:</p>
-      <code># erl +Mut false +A 10 +S 4:4 +Muycs256 +P 2096 +Q 2096 -emu_args_exit
--Mut
-false
--A
-10
--S
-4:4
--Muycs256
--P
-2096
--Q
-2096
---
--root
-/usr/local/lib/erlang
--progname
-erl
---
--home
-/home/erlang
---</code>
-    <p>
-      The arguments are printed on separate lines to make it possible to know
-      what has to be quoted with &quot;. Each line is one quotable unit.
-      So taking the arguments above you can supply them to pm_create or
-      just execute directly on the command line. For example:</p>
-      <code>rtose@acp3400> pm_install erlang /mst/erlang/erts-6.0/bin/beam.smp
-rtose@acp3400> pm_create -c ARGV="-Mut false -A 10 -S 4:4 -Muycs256 -P 2096 -Q 2099 -- -root /mst/erlang -progname erl -- -home /mst/erlang --" erlang
-pid: 0x110059
-rtose@acp3400> pm_start 0x110059</code>
-    <p>
-      Also note that since we are running erl to figure out the arguments on a
-      separate machine the paths have to be updated. In the example above
-      <c>/usr/local/lib/erlang</c> was replaced by <c>/mst/erlang/</c>. The
-      goal is to in future releases not have to do the special argument handling
-      but for now (OTP 17.0) you have to do it.
-    </p>
-    <note>
-      Because of a limitation in the way the OSE handles stdio when starting
-      load modules using pm_install/create the Erlang shell only reads every
-      other command from stdin. However if you start Erlang using run_erl
-      you do not have this problem. So it is highly recommended that you
-      start Erlang using run_erl.
-    </note>
-  </section>
-
-  <section>
-    <title>run_erl and to_erl</title>
-    <p>
-      In OSE run_erl and to_erl are combined into a single load module called
-      run_erl_lm. Installing and starting the load module will add two new
-      shell commands called run_erl and to_erl. They work in exactly the same
-      way as the unix variants of run_erl and to_erl, except that the read
-      and write pipes have to be placed under the /pipe vm. One additional
-      option also exists to run_erl on ose:
-      <taglist>
-	<tag><c>-block Name</c></tag>
-	<item>The name of the install handle and block that will be created/used by
-	installing and exectuting the first part of the command. If nothing
-	if given the basename of the load module will be used for this value.
-	Example:
-	<code>pm_install erlang /path/to/erlang/vm/beam.smp
-run_erl -daemon -block erlang /pipe/ /mst/erlang_logs/ "beam.smp -A 1 -- -root /mst/erlang -- -home /mst --"</code>
-	</item>
-      </taglist>
-      The same argument munching as when starting Erlang/OTP without run_erl
-      has to be done. If <c>-daemon</c> is given then all error printouts
-      are sent to the ramlog.
-      See also
-      <seealso marker="erts:run_erl">run_erl</seealso> for more details.
-    </p>
-    <p>
-      Below is an example of how to get started with <c>run_erl_lm</c>.
-      <code>rtose@acp3400> pm_install run_erl_lm /mst/erlang/erts-6.0/bin/run_erl_lm
-rtose@acp3400> pm_create run_erl_lm
-pid: 0x1c005d
-rtose@acp3400> pm_start 0x1c005d
-rtose@acp3400> mkdir /mst/erlang_log
-rtose@acp3400> run_erl -daemon /pipe/ /mst/erlang_log/ "/mst/erlang/erts-6.0/bin/beam.smp -A 1 -- -root /mst/erlang -- -home /mst --"
-rtose@acp3400> to_erl
-Attaching to /pipe/erlang.pipe.1 (^C to exit)
-os:type().
-{ose,release}
-2>
-'to_erl' terminated.</code>
-      Note that Ctrl-C is used instead of Ctrl-D to exit the to_erl shell.
-    </p>
-  </section>
-
-  <section>
-    <title>epmd</title>
-    <p>
-      In OSE epmd will not be started automatically so if you want to use
-      Erlang distribution you have to manually start epmd.
-    </p>
-  </section>
-
-  <section>
-    <title>VM Process Priorities</title>
-    <p>
-      It is possible to set the priorities you want for the OSE processes that
-      thr emulator creates in the lmconf. An example of how to do it can be
-      found in the default lmconf file in
-      $ERL_TOP/erts/emulator/sys/ose/beam.lmconf.
-    </p>
-  </section>
-
-</chapter>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/ose_signals_chapter.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_signals_chapter.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/ose_signals_chapter.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ose_signals_chapter.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,240 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE chapter SYSTEM "chapter.dtd">
-
-<chapter>
-  <header>
-    <copyright>
-      <year>2013</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>Interacting with Enea OSE</title>
-    <prepared>Lukas Larsson</prepared>
-    <docno></docno>
-    <date>2014-01-08</date>
-    <rev>A</rev>
-    <file>ose_signals_chapter.xml</file>
-  </header>
-
-  <marker id="introduction"></marker>
-  <section>
-    <title>Introduction</title>
-    <p>The main way which programs on Enea OSE interact is through the
-    usage of message passing, much the same way as Erlang processes
-    communicate. There are two ways in which an Erlang programmer can
-    interact with the signals sent from other Enea OSE processes; either
-    through the provided <c>ose</c> module, or by writing a custom linked-in
-    driver. This User's Guide describes and provides examples for both
-    approaches.
-    </p>
-  </section>
-
-  <marker id="erlang"></marker>
-  <section>
-    <title>Signals in Erlang</title>
-    <p>Erlang/OTP on OSE provides a erlang module called
-    <seealso marker="ose:ose">ose</seealso> that can be used to interact
-    with other OSE processes using message passing. The api in the module
-    is very similar to the native OSE api, so for details of how the
-    functions work please refer to the official OSE documenation. Below
-    is an example usage of the API.
-    </p>
-    <code>1> P1 = ose:open("p1").
-#Port&gt;0.344>
-2> ose:hunt(P1,"p2").
-{#Port&gt;0.344>,1}
-3> P2 = ose:open("p2").
-#Port&gt;0.355>
-4> flush().
-Shell got {mailbox_up,#Port&gt;0.344>,{#Port&gt;0.344>,1},852189}
-ok
-5> ose:listen(P1,[1234]).
-ok
-6> ose:send(P2,ose:get_id(P1),1234,&gt;&gt;"hello">>).
-ok
-7> flush().
-Shell got {message,#Port&gt;0.344>,{852189,1245316,1234,&gt;&gt;"hello">>}}
-ok</code>
-  </section>
-
-  <marker id="driver"></marker>
-  <section>
-    <title>Signals in a Linked-in driver</title>
-    <p>
-      Writing Linked-in drivers for OSE is very similar to how it is done
-      for Unix/Windows. It is only the way in which the driver subscribes
-      and consumed external events that is different. In Unix (and Windows)
-      file descriptiors (and Event Objects) are used to select on. On OSE
-      we use signals to deliver the same functionality. There are two large
-      differences between a signal and an fd.
-    </p>
-    <p>
-      In OSE it is not possible for a signal number to be a unique identifier
-      for a resource in the same way as an fd is. For example; let's say we
-      implement a driver that does an asynchronous hunt that uses signal
-      number 1234 as the hunt_sig. If we want to be able to have multiple
-      hunt ports running at the same time we have to have someway of routing
-      the signal to the correct port. This is achieved by supplying a secondary
-      id that can be retrieved through the meta-data or payload of the signal,
-      e.g:
-      <code>ErlDrvEvent event = erl_drv_ose_event_alloc(1234,port,resolver);</code>
-      The event you get back from
-      <seealso marker="ose_erl_driver#erl_drv_ose_event_alloc">
-      erl_drv_ose_event_alloc</seealso> can then be used by
-      <seealso marker="erts:erl_driver#driver_select">driver_select</seealso>
-      to subscribe to signals. The first argument is just the signal number
-      that we are interested in. The second is the id that we choose to use,
-      in this case the port id that we got in the
-      <seealso marker="erts:driver_entry#start">start</seealso> callback is
-      used. The third argument is a function pointer to a function that can
-      be used to figure out the id from a given signal. The fourth argument can
-      point to any additional data you might want to associate with the event.
-      There is a complete. You can examine the data contained in the event with
-      <seealso marker="ose_erl_driver#erl_drv_ose_event_fetch">erl_drv_ose_event_fetch</seealso>
-      , eg:
-      <code>erl_drv_ose_event_fetch(event, &amp;signal, &amp;port, (void **)&amp;extra);</code>
-      example of what this could look like in
-      <seealso marker="#example">the next section</seealso>.
-      <note>It is very important to issue the driver_select call before
-      any of the signals you are interested in are sent. If driver_select
-      is called after the signal is sent, there is a high probability that it
-      will be lost.</note>
-    </p>
-    <p>
-      The other difference from unix is that in OSE the payload of the event
-      (i.e. the signal data) is already received when the ready_output/input
-      callbacks are called. This means that you access the data of a signal
-      by calling <seealso marker="ose_erl_driver#erl_drv_ose_get_signal">
-      erl_drv_ose_get_signal</seealso>. Additionally multiple signals might be
-      associated with the event, so you should call
-      <seealso marker="ose_erl_driver#erl_drv_ose_get_signal">
-      erl_drv_ose_get_signal</seealso> until <c>NULL</c> is returned.
-    </p>
-  </section>
-
-  <marker id="example"></marker>
-  <section>
-    <title>Example Linked-in driver</title>
-<code>#include "erl_driver.h"
-#include "ose.h"
-
-struct huntsig {
-  SIGSELECT signo;
-  ErlDrvPort port;
-};
-
-union SIGNAL {
-  SIGSELECT signo;
-  struct huntsig;
-}
-
-/* Here we have to get the id from the signal. In this case we use the
-   port id since we have control over the data structure of the signal.
-   It is however possible to use anything in here. The only restriction
-   is that the same id has to be used for all signals of the same number.*/
-ErlDrvOseEventId resolver(union SIGNAL *sig) {
-  return (ErlDrvOseEventId)sig->huntsig.port;
-}
-
-static int drv_init(void) { return 0; };
-
-static ErlDrvData drv_start(ErlDrvPort port, char *command) {
-  return (ErlDrvData)port;
-}
-
-static ErlDrvSSizeT control(ErlDrvData driver_data, unsigned int cmd,
-                            char *buf, ErlDrvSizeT len,
-                            char **rbuf, ErlDrvSizeT rlen) {
-  ErlDrvPort port = (ErlDrvPort)driver_data;
-
-  /* An example of extra data to associate with the event */
-  char *extra_data = driver_alloc(80);
-  snprintf("extra_data, "Event, sig_no: 1234, and port: %d", port);
-
-  /* Create a new event to select on */
-  ErlDrvOseEvent evt = erl_drv_ose_event_alloc(1234,port,resolver, extra_data);
-
-  /* Make sure to do the select call _BEFORE_ the signal arrives.
-     The signal might get lost if the hunt call is done before the
-     select. */
-  driver_select(port,evt,ERL_DRV_READ|ERL_DRV_USE,1);
-
-  union SIGNAL *sig = alloc(sizeof(union SIGNAL),1234);
-  sig->huntsig.port = port;
-  hunt("testprocess",0,NULL,&amp;sig);
-  return 0;
-}
-
-static void ready_input(ErlDrvData driver_data, ErlDrvEvent evt) {
-  char *extra_data;
-  /* Get the first signal payload from the event */
-  union SIGNAL *sig = erl_drv_ose_get_signal(evt);
-  ErlDrvPort port = (ErlDrvPort)driver_data;
-  while (sig != NULL) {
-    if (sig->signo == 1234) {
-      /* Print out the string we added as the extra parameter */
-      erl_drv_ose_event_fetch(evt, NULL, NULL, (void **)&amp;extra_data);
-      printf("We've received: %s\n", extra_data);
-
-      /* If it is our signal we send a message with the sender of the signal
-         to the controlling erlang process */
-      ErlDrvTermData reply[] = { ERL_DRV_UINT, (ErlDrvUInt)sender(&amp;sig) };
-      erl_drv_send_term(port,reply,sizeof(reply) / sizeof(reply[0]));
-    }
-
-    /* Cleanup the signal and deselect on the event.
-       Note that the event itself has to be free'd in the stop_select
-       callback. */
-    free_buf(&amp;sig);
-    driver_select(port,evt,ERL_DRV_READ|ERL_DRV_USE,0);
-
-    /* There could be more than one signal waiting in this event, so
-       we have to loop until sig == NULL */
-    sig = erl_drv_ose_get_signal(evt);
-  }
-}
-
-static void stop_select(ErlDrvEvent event, void *reserved)
-{
-  /* Free the extra_data */
-  erl_drv_ose_event_fetch(evt, NULL, NULL, (void **)&amp;extra_data);
-  driver_free(extra_data);
-
-  /* Free the event itself */
-  erl_drv_ose_event_free(event);
-}
-
-/**
- * Setup the driver entry for the Erlang runtime
- **/
-ErlDrvEntry ose_signal_driver_entry = {
-  .init                         = drv_init,
-  .start                        = drv_start,
-  .stop                         = drv_stop,
-  .ready_input                  = ready_input,
-  .driver_name                  = DRIVER_NAME,
-  .control                      = control,
-  .extended_marker              = ERL_DRV_EXTENDED_MARKER,
-  .major_version                = ERL_DRV_EXTENDED_MAJOR_VERSION,
-  .minor_version                = ERL_DRV_EXTENDED_MINOR_VERSION,
-  .driver_flags                 = ERL_DRV_FLAG_USE_PORT_LOCKING,
-  .stop_select                  = stop_select
-};
-</code>
-  </section>
-
-</chapter>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/part.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/part.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/part.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/part.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,39 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE part SYSTEM "part.dtd">
-
-<part xmlns:xi="http://www.w3.org/2001/XInclude">
-  <header>
-    <copyright>
-      <year>2014</year>
-      <year>2014</year>
-      <holder>Ericsson AB, All Rights Reserved</holder>
-    </copyright>
-    <legalnotice>
-  Licensed under the Apache License, Version 2.0 (the "License");
-  you may not use this file except in compliance with the License.
-  You may obtain a copy of the License at
- 
-      http://www.apache.org/licenses/LICENSE-2.0
-
-  Unless required by applicable law or agreed to in writing, software
-  distributed under the License is distributed on an "AS IS" BASIS,
-  WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-  See the License for the specific language governing permissions and
-  limitations under the License.
-
-  The Initial Developer of the Original Code is Ericsson AB.
-    </legalnotice>
-
-    <title>OSE User's Guide</title>
-    <prepared>Lukas Larsson</prepared>
-    <docno></docno>
-    <date>2014-01-08</date>
-    <rev>1.0</rev>
-    <file>part.xml</file>
-  </header>
-  <description>
-    <p><em>OSE</em>.</p>
-  </description>
-  <xi:include href="ose_intro.xml"/>
-  <xi:include href="ose_signals_chapter.xml"/>
-</part>
diff -Ndurp otp_src_18.3.4.5/lib/ose/doc/src/ref_man.xml otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ref_man.xml
--- otp_src_18.3.4.5/lib/ose/doc/src/ref_man.xml	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/doc/src/ref_man.xml	1970-01-01 03:00:00.000000000 +0300
@@ -1,40 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE application SYSTEM "application.dtd">
-
-<application xmlns:xi="http://www.w3.org/2001/XInclude">
-  <header>
-    <copyright>
-      <year>2014</year><year>2014</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      Licensed under the Apache License, Version 2.0 (the "License");
-      you may not use this file except in compliance with the License.
-      You may obtain a copy of the License at
- 
-          http://www.apache.org/licenses/LICENSE-2.0
-
-      Unless required by applicable law or agreed to in writing, software
-      distributed under the License is distributed on an "AS IS" BASIS,
-      WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-      See the License for the specific language governing permissions and
-      limitations under the License.
-
-    </legalnotice>
-
-    <title>OSE Reference Manual</title>
-    <prepared>Lukas Larsson</prepared>
-    <docno></docno>
-    <date>2014-01-08</date>
-    <rev>1.0</rev>
-    <file>ref_man.xml</file>
-  </header>
-  <description>
-    <p>The Standard Erlang Libraries application, <em>STDLIB</em>,
-      contains modules for manipulating lists, strings and files etc.</p>
-    <br></br>
-  </description>
-  <xi:include href="ose_app.xml"/>
-  <xi:include href="ose.xml"/>
-  <xi:include href="ose_erl_driver.xml"/>
-</application>
diff -Ndurp otp_src_18.3.4.5/lib/ose/info otp_src_18.3.4.5-remove-OSE-port/lib/ose/info
--- otp_src_18.3.4.5/lib/ose/info	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/info	1970-01-01 03:00:00.000000000 +0300
@@ -1,2 +0,0 @@
-group: misc Miscellaneous Applications
-short: Description of Enea OSE specific functionality
diff -Ndurp otp_src_18.3.4.5/lib/ose/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/ose/Makefile
--- otp_src_18.3.4.5/lib/ose/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/Makefile	1970-01-01 03:00:00.000000000 +0300
@@ -1,37 +0,0 @@
-#
-# %CopyrightBegin%
-#
-# Copyright Ericsson AB 1996-2009. All Rights Reserved.
-#
-# Licensed under the Apache License, Version 2.0 (the "License");
-# you may not use this file except in compliance with the License.
-# You may obtain a copy of the License at
-#
-#     http://www.apache.org/licenses/LICENSE-2.0
-#
-# Unless required by applicable law or agreed to in writing, software
-# distributed under the License is distributed on an "AS IS" BASIS,
-# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-# See the License for the specific language governing permissions and
-# limitations under the License.
-#
-# %CopyrightEnd%
-#
-include $(ERL_TOP)/make/target.mk
-include $(ERL_TOP)/make/$(TARGET)/otp.mk
-
-#
-# Macros
-#
-
-SUB_DIRECTORIES = src doc/src
-
-include vsn.mk
-VSN = $(OSE_VSN)
-
-SPECIAL_TARGETS =
-
-#
-# Default Subdir Targets
-#
-include $(ERL_TOP)/make/otp_subdir.mk
diff -Ndurp otp_src_18.3.4.5/lib/ose/src/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/Makefile
--- otp_src_18.3.4.5/lib/ose/src/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/Makefile	1970-01-01 03:00:00.000000000 +0300
@@ -1,107 +0,0 @@
-#
-# %CopyrightBegin%
-#
-# Copyright Ericsson AB 1996-2013. All Rights Reserved.
-#
-# Licensed under the Apache License, Version 2.0 (the "License");
-# you may not use this file except in compliance with the License.
-# You may obtain a copy of the License at
-#
-#     http://www.apache.org/licenses/LICENSE-2.0
-#
-# Unless required by applicable law or agreed to in writing, software
-# distributed under the License is distributed on an "AS IS" BASIS,
-# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-# See the License for the specific language governing permissions and
-# limitations under the License.
-#
-# %CopyrightEnd%
-#
-
-include $(ERL_TOP)/make/target.mk
-include $(ERL_TOP)/make/$(TARGET)/otp.mk
-
-# ----------------------------------------------------
-# Application version
-# ----------------------------------------------------
-include ../vsn.mk
-VSN=$(OSE_VSN)
-
-# ----------------------------------------------------
-# Release directory specification
-# ----------------------------------------------------
-RELSYSDIR = $(RELEASE_PATH)/lib/ose-$(VSN)
-
-# ----------------------------------------------------
-# Target Specs
-# ----------------------------------------------------
-MODULES= \
-	ose
-
-HRL_FILES=
-
-INTERNAL_HRL_FILES=
-
-ERL_FILES= $(MODULES:%=%.erl)
-
-TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR)) $(APP_TARGET) $(APPUP_TARGET)
-
-APP_FILE= ose.app
-
-APP_SRC= $(APP_FILE).src
-APP_TARGET= $(EBIN)/$(APP_FILE)
-
-APPUP_FILE= ose.appup
-
-APPUP_SRC= $(APPUP_FILE).src
-APPUP_TARGET= $(EBIN)/$(APPUP_FILE)
-
-# ----------------------------------------------------
-# FLAGS
-# ----------------------------------------------------
-
-ifeq ($(NATIVE_LIBS_ENABLED),yes)
-ERL_COMPILE_FLAGS += +native
-endif
-ERL_COMPILE_FLAGS += -I../include -I../../kernel/include -Werror
-
-# ----------------------------------------------------
-# Targets
-# ----------------------------------------------------
-
-debug opt: $(TARGET_FILES)
-
-clean:
-	rm -f $(TARGET_FILES)
-	rm -f core
-	rm -f erl_parse.erl
-
-docs:
-
-# ----------------------------------------------------
-# Special Build Targets
-# ----------------------------------------------------
-
-$(APP_TARGET): $(APP_SRC) ../vsn.mk
-	$(vsn_verbose)sed -e 's;%VSN%;$(VSN);' $< > $@
-
-$(APPUP_TARGET): $(APPUP_SRC) ../vsn.mk
-	$(vsn_verbose)sed -e 's;%VSN%;$(VSN);' $< > $@
-
-# ----------------------------------------------------
-# Release Target
-# ----------------------------------------------------
-include $(ERL_TOP)/make/otp_release_targets.mk
-
-release_spec: opt
-	$(INSTALL_DIR) "$(RELSYSDIR)/src"
-	$(INSTALL_DATA) $(ERL_FILES) "$(RELSYSDIR)/src"
-	$(INSTALL_DIR) "$(RELSYSDIR)/include"
-	$(INSTALL_DIR) "$(RELSYSDIR)/ebin"
-	$(INSTALL_DATA) $(TARGET_FILES) "$(RELSYSDIR)/ebin"
-
-release_docs_spec:
-
-# ----------------------------------------------------
-# Dependencies -- alphabetically, please
-# ----------------------------------------------------
diff -Ndurp otp_src_18.3.4.5/lib/ose/src/ose.app.src otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/ose.app.src
--- otp_src_18.3.4.5/lib/ose/src/ose.app.src	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/ose.app.src	1970-01-01 03:00:00.000000000 +0300
@@ -1,28 +0,0 @@
-%% This is an -*- erlang -*- file.
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
-{application, ose,
- [{description, "Enea OSE specific modules"},
-  {vsn, "%VSN%"},
-  {modules, [ose]},
-  {registered,[]},
-  {applications, [stdlib,kernel]},
-  {env, []},
-  {runtime_dependencies, ["stdlib-2.0","erts-6.0"]}]}.
diff -Ndurp otp_src_18.3.4.5/lib/ose/src/ose.appup.src otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/ose.appup.src
--- otp_src_18.3.4.5/lib/ose/src/ose.appup.src	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/ose.appup.src	1970-01-01 03:00:00.000000000 +0300
@@ -1,23 +0,0 @@
-%% -*- erlang -*-
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1999-2013. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-{"%VSN%",
- [
- ],
- [
- ]}.
diff -Ndurp otp_src_18.3.4.5/lib/ose/src/ose.erl otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/ose.erl
--- otp_src_18.3.4.5/lib/ose/src/ose.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/src/ose.erl	1970-01-01 03:00:00.000000000 +0300
@@ -1,453 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2013. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
-%% @doc Interface module for OSE messaging and process monitoring from Erlang
-%%
-%% For each mailbox created through {@link open/1} a OSE phantom process with
-%% that name is started. Since phantom processes are used the memory footprint
-%% of each mailbox is quite small.
-%%
-%% To receive messages you first have to subscribe to the specific message
-%% numbers that you are interested in with {@link listen/2}. The messages
-%% will be sent to the Erlang process that created the mailbox.
-%%
-%% @end
-%%
--module(ose).
-
-%%==============================================================================
-%% Exported API
-%%==============================================================================
--export([open/1,
-         close/1,
-         get_id/1,
-         get_name/2,
-         hunt/2,
-         dehunt/2,
-         attach/2,
-         detach/2,
-         send/4,
-         send/5,
-	 listen/2
-	]).
-
-%%==============================================================================
-%% Types
-%%==============================================================================
--opaque mailbox() :: port().
-%% Mailbox handle.  Implemented as an erlang port.
-
--opaque mailbox_id() :: integer().
-%% Mailbox ID, this is the same as the process id of an OSE process.
-%% An integer.
-
--type message_number() :: 0..4294967295.
-%% OSE Signal number
-
--opaque hunt_ref() :: {mailbox(),integer()}.
-%% Reference from a hunt request.  This term will be included
-%% in a successful hunt response.
-
--opaque attach_ref() :: {mailbox(),integer()}.
-%% Reference from an attach request.  This term will be included
-%% in the term returned when the attached mailbox disappears.
-
--export_type([mailbox_id/0,
-	      message_number/0,
-	      mailbox/0,
-	      hunt_ref/0,
-	      attach_ref/0]).
-
-%%==============================================================================
-%% Defines
-%%==============================================================================
--define(DRIVER_NAME, "ose_signal_drv").
--define(GET_SPID, 1).
--define(GET_NAME, 2).
--define(HUNT, 100).
--define(DEHUNT, 101).
--define(ATTACH, 102).
--define(DETACH, 103).
--define(SEND, 104).
--define(SEND_W_S, 105).
--define(LISTEN, 106).
--define(OPEN, 200).
-
--define(INT_32BIT(Int),(is_integer(Int) andalso (Int >= 0) andalso (Int < (1 bsl 32)))).
-
-%%==============================================================================
-%% API functions
-%%==============================================================================
-
-%%------------------------------------------------------------------------------
-%% @doc Create a mailbox with the given name and return a port that handles
-%% the mailbox.
-%%
-%% An OSE phantom process with the given name will be created that will send any
-%% messages sent through this mailbox. Any messages sent to the new OSE process
-%% will automatically be converted to an Erlang message and sent to the Erlang
-%% process that calls this function. See {@link listen/2} for details about the
-%% format of the message sent.
-%%
-%% The caller gets linked to the created mailbox.
-%%
-%% raises: `badarg' | `system_limit'
-%%
-%% @see listen/2
-%% @end
-%%------------------------------------------------------------------------------
--spec open(Name) -> Port when
-      Name :: iodata(),
-      Port :: mailbox().
-open(Name) ->
-    try open_port({spawn_driver,?DRIVER_NAME}, [binary]) of
-	Port ->
-	    try port_command(Port,[?OPEN,Name]) of
-		true ->
-		    receive
-			{ose_drv_reply,Port,{error,Error}} ->
-			    close(Port),
-			    erlang:error(Error,[Name]);
-			{ose_drv_reply,Port,ok} ->
-			    Port
-		    end
-	    catch
-		error:badarg  -> close(Port),erlang:error(badarg,[Name])
-	    end
-    catch
-	error:badarg  -> erlang:error(badarg,[Name])
-    end.
-
-%%------------------------------------------------------------------------------
-%% @doc Close a mailbox
-%%
-%% This kills the OSE phantom process associated with this mailbox.
-%%
-%% Will also consume any ``{'EXIT',Port,_}'' message from the port that comes
-%% due to the port closing when the calling process traps exits.
-%%
-%% raises: `badarg'
-%% @end
-%%------------------------------------------------------------------------------
--spec close(Port) -> ok when
-      Port :: mailbox().
-close(Port) when is_port(Port) ->
-    %% Copied from prim_inet
-    case erlang:process_info(self(), trap_exit) of
-	{trap_exit,true} ->
-	    link(Port),
-	    catch erlang:port_close(Port),
-	    receive {'EXIT',Port,_} -> ok end;
-	{trap_exit,false} ->
-	    catch erlang:port_close(Port),
-	    ok
-    end;
-close(NotPort) ->
-    erlang:error(badarg,[NotPort]).
-
-%%------------------------------------------------------------------------------
-%% @doc Get the mailbox id for the given port.
-%%
-%% The mailbox id is the same as the OSE process id of the OSE phantom process
-%% that this mailbox represents.
-%%
-%% raises: `badarg'
-%% @end
-%%------------------------------------------------------------------------------
--spec get_id(Port) -> Pid when
-      Port :: mailbox(),
-      Pid :: mailbox_id().
-get_id(Port) ->
-    try port_control(Port, ?GET_SPID, <<>>) of
-	<<Spid:32>> -> Spid
-    catch error:_Error ->
-	    erlang:error(badarg,[Port])
-    end.
-
-%%------------------------------------------------------------------------------
-%% @doc Get the mailbox name for the given mailbox id.
-%%
-%% The mailbox name is the name of the OSE process with process id Pid.
-%%
-%% This call will fail with badarg if the underlying system does not support
-%% getting the name from a process id.
-%%
-%% raises: `badarg'
-%% @end
-%%------------------------------------------------------------------------------
--spec get_name(Port, Pid) -> Name | undefined when
-      Port :: mailbox(),
-      Pid :: mailbox_id(),
-      Name :: binary().
-get_name(Port, Pid) when ?INT_32BIT(Pid) ->
-    try port_control(Port, ?GET_NAME, <<Pid:32>>) of
-	[] -> undefined;
-	Res -> Res
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,Pid])
-    end;
-get_name(Port, Pid) ->
-    erlang:error(badarg,[Port,Pid]).
-
-
-%%------------------------------------------------------------------------------
-%% @doc Hunt for OSE process by name.
-%%
-%% Will send `{mailbox_up, Port, Ref, MboxId}'
-%% to the calling process when the OSE process becomes available.
-%%
-%% Returns a reference term that can be used to cancel the hunt
-%% using {@link dehunt/2}.
-%%
-%% raises: `badarg'
-%%
-%% @end
-%%------------------------------------------------------------------------------
--spec hunt(Port, HuntPath) -> Ref when
-      Port :: mailbox(),
-      HuntPath :: iodata(),
-      Ref :: hunt_ref().
-hunt(Port, HuntPath) ->
-    try port_command(Port, [?HUNT,HuntPath]) of
-	true ->
-	    receive
-		{ose_drv_reply,Port,{error,Error}} ->
-		    erlang:error(Error,[Port,HuntPath]);
-		{ose_drv_reply,Port,Ref} ->
-		    Ref
-	    end
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,HuntPath])
-    end.
-
-%%------------------------------------------------------------------------------
-%% @doc Stop hunting for OSE process.
-%%
-%% If a message for this hunt has been sent but not received
-%% by the calling process, it is removed from the message queue.
-%% Note that this only works if the same process that did
-%% the hunt does the dehunt.
-%%
-%% raises: `badarg'
-%%
-%% @see hunt/2
-%% @end
-%%------------------------------------------------------------------------------
--spec dehunt(Port, Ref) -> ok when
-      Port :: mailbox(),
-      Ref :: hunt_ref().
-dehunt(Port, {Port,Ref}) when ?INT_32BIT(Ref) ->
-    try port_command(Port, <<?DEHUNT:8, Ref:32>>) of
-	true ->
-	    receive
-		{ose_drv_reply,Port,{error,enoent}} ->
-		    %% enoent could mean that it is in the message queue
-		    receive
-			{mailbox_up, Port, {Port,Ref}, _} ->
-			    ok
-		    after 0 ->
-			    ok
-		    end;
-		{ose_drv_reply,Port,ok} ->
-		    ok
-	    end
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,{Port,Ref}])
-    end;
-dehunt(Port,Ref) ->
-    erlang:error(badarg,[Port,Ref]).
-
-%%------------------------------------------------------------------------------
-%% @doc Attach to an OSE process.
-%%
-%% Will send `{mailbox_down, Port, Ref, MboxId}'
-%% to the calling process if the OSE process exits.
-%%
-%% Returns a reference that can be used to cancel the attachment
-%% using {@link detach/2}.
-%%
-%% raises: `badarg' | `enomem'
-%%
-%% @end
-%%------------------------------------------------------------------------------
--spec attach(Port,Pid) -> Ref when
-      Port :: mailbox(),
-      Pid :: mailbox_id(),
-      Ref :: attach_ref().
-attach(Port, Spid) when ?INT_32BIT(Spid) ->
-    try port_command(Port, <<?ATTACH:8, Spid:32>>) of
-	true ->
-	    receive
-		{ose_drv_reply,Port,{error,Error}} ->
-		    erlang:error(Error,[Port,Spid]);
-		{ose_drv_reply,Port,Ref} ->
-		    Ref
-	    end
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,Spid])
-    end;
-attach(Port,Spid) ->
-    erlang:error(badarg,[Port,Spid]).
-
-
-%%------------------------------------------------------------------------------
-%% @doc Remove attachment to an OSE process.
-%%
-%% If a message for this monitor has been sent but not received
-%% by the calling process, it is removed from the message queue.
-%% Note that this only works of the same process
-%% that did the attach does the detach.
-%%
-%% raises: `badarg'
-%%
-%% @see attach/2
-%% @end
-%%------------------------------------------------------------------------------
--spec detach(Port,Ref) -> ok when
-      Port :: mailbox(),
-      Ref :: attach_ref().
-detach(Port, {Port,Ref} ) when ?INT_32BIT(Ref) ->
-    try port_command(Port, <<?DETACH:8, Ref:32>>) of
-	true ->
-	    receive
-		{ose_drv_reply,Port,{error,enoent}} ->
-		    %% enoent could mean that it is in the message queue
-		    receive
-			{mailbox_down,Port,{Port,Ref},_} ->
-			    ok
-		    after 0 ->
-			    ok
-		    end;
-		{ose_drv_reply,Port,ok} ->
-		    ok
-	    end
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,{Port,Ref}])
-    end;
-detach(Port,Ref) ->
-    erlang:error(badarg,[Port,Ref]).
-
-%%------------------------------------------------------------------------------
-%% @doc Send an OSE message.
-%%
-%% The message is sent from the OSE process' own ID that is: `get_id(Port)'.
-%%
-%% raises: `badarg'
-%%
-%% @see send/5
-%% @end
-%%------------------------------------------------------------------------------
--spec send(Port,Pid,SigNo,SigData) -> ok when
-      Port :: mailbox(),
-      Pid :: mailbox_id(),
-      SigNo :: message_number(),
-      SigData :: iodata().
-send(Port, Spid, SigNo, SigData) when ?INT_32BIT(Spid), ?INT_32BIT(SigNo) ->
-    try erlang:port_command(Port, [<<?SEND:8, Spid:32, SigNo:32>>, SigData]) of
-	true -> ok
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,Spid,SigNo,SigData])
-    end;
-send(Port,Spid,SigNo,SigData) ->
-    erlang:error(badarg,[Port,Spid,SigNo,SigData]).
-
-
-%%------------------------------------------------------------------------------
-%% @doc Send an OSE message with different sender.
-%%
-%% As {@link send/4} but the sender will be `SenderPid'.
-%%
-%% raises: `badarg'
-%%
-%% @see send/4
-%% @end
-%%------------------------------------------------------------------------------
--spec send(Port,Pid,SenderPid,SigNo,SigData) -> ok when
-      Port :: mailbox(),
-      Pid :: mailbox_id(),
-      SenderPid :: mailbox_id(),
-      SigNo :: message_number(),
-      SigData :: iodata().
-send(Port, Spid, SenderPid, SigNo, SigData)
-  when ?INT_32BIT(Spid), ?INT_32BIT(SenderPid), ?INT_32BIT(SigNo) ->
-    try erlang:port_command(Port, [<<?SEND_W_S:8, Spid:32, SenderPid:32,
-				     SigNo:32>>, SigData]) of
-	true -> ok
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,Spid,SenderPid,SigNo,SigData])
-    end;
-send(Port,Spid,SenderPid,SigNo,SigData) ->
-    erlang:error(badarg,[Port,Spid,SenderPid,SigNo,SigData]).
-
-%%------------------------------------------------------------------------------
-%% @doc Start listening for specified OSE signal numbers.
-%%
-%% The mailbox will send `{message,Port,{FromMboxId,ToMboxId,MsgNo,MsgData}}'
-%% to the process that created the mailbox when an OSE message with any
-%% of the specified `SigNos' arrives.
-%%
-%% Repeated calls to listen will replace the current set of signal numbers to
-%% listen to. i.e
-%%
-%% ```1>ose:listen(MsgB,[1234,12345]).
-%%  ok
-%%  2> ose:listen(MsgB,[1234,123456]).
-%%  ok.'''
-%%
-%% The above will first listen for signals with numbers 1234 and 12345, and then
-%% replace that with only listening to 1234 and 123456.
-%%
-%% With the current implementation it is not possible to listen to all signal
-%% numbers.
-%%
-%% raises: `badarg' | `enomem'
-%%
-%% @end
-%%------------------------------------------------------------------------------
--spec listen(Port, SigNos) -> ok when
-      Port :: mailbox(),
-      SigNos :: list(message_number()).
-listen(Port, SigNos) when is_list(SigNos) ->
-    USSigNos = lists:usort(SigNos),
-    BinSigNos = try
-		    << <<SigNo:32>> ||
-			SigNo <- USSigNos,
-			?INT_32BIT(SigNo) orelse erlang:error(badarg)
-		    >>
-		catch _:_ ->
-			erlang:error(badarg,[Port,SigNos])
-		end,
-    try port_command(Port, [?LISTEN, BinSigNos]) of
-	true ->
-	    receive
-		{ose_drv_reply,Port,{error,Error}} ->
-		    erlang:error(Error,[Port,SigNos]);
-		{ose_drv_reply,Port,Else} ->
-		    Else
-	    end
-    catch error:_Error ->
-	    erlang:error(badarg,[Port,SigNos])
-    end;
-listen(Port, SigNos) ->
-    erlang:error(badarg,[Port,SigNos]).
-
-
-%%%=============================================================================
-%%% Internal functions
-%%%=============================================================================
diff -Ndurp otp_src_18.3.4.5/lib/ose/test/Makefile otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/Makefile
--- otp_src_18.3.4.5/lib/ose/test/Makefile	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/Makefile	1970-01-01 03:00:00.000000000 +0300
@@ -1,67 +0,0 @@
-include $(ERL_TOP)/make/target.mk
-include $(ERL_TOP)/make/$(TARGET)/otp.mk
-
-# ----------------------------------------------------
-# Target Specs
-# ----------------------------------------------------
-
-MODULES= \
-	ose_SUITE
-
-ERL_FILES= $(MODULES:%=%.erl)
-
-TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR))
-
-INSTALL_PROGS= $(TARGET_FILES)
-
-# ----------------------------------------------------
-# Release directory specification
-# ----------------------------------------------------
-RELSYSDIR = $(RELEASE_PATH)/ose_test
-
-# ----------------------------------------------------
-# FLAGS
-# ----------------------------------------------------
-
-ERL_MAKE_FLAGS +=
-ERL_COMPILE_FLAGS += -I$(ERL_TOP)/lib/test_server/include \
-		-I$(ERL_TOP)/lib/kernel/include
-
-EBIN = .
-
-EMAKEFILE=Emakefile
-COVERFILE=ose.cover
-
-# ----------------------------------------------------
-# Targets
-# ----------------------------------------------------
-
-make_emakefile:
-	$(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) $(MODULES) \
-	> $(EMAKEFILE)
-
-tests debug opt: make_emakefile
-	erl $(ERL_MAKE_FLAGS) -make
-
-clean:
-	rm -f $(EMAKEFILE)
-	rm -f $(TARGET_FILES)
-	rm -f core
-
-docs:
-
-# ----------------------------------------------------
-# Release Target
-# ----------------------------------------------------
-include $(ERL_TOP)/make/otp_release_targets.mk
-
-release_spec: opt
-
-release_tests_spec: make_emakefile
-	$(INSTALL_DIR) "$(RELSYSDIR)"
-	$(INSTALL_DATA) ose.spec $(EMAKEFILE) \
-		$(ERL_FILES) $(COVERFILE) "$(RELSYSDIR)"
-	chmod -R u+w "$(RELSYSDIR)"
-	@tar cf - *_SUITE_data | (cd "$(RELSYSDIR)"; tar xf -)
-
-release_docs_spec:
diff -Ndurp otp_src_18.3.4.5/lib/ose/test/ose.cover otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/ose.cover
--- otp_src_18.3.4.5/lib/ose/test/ose.cover	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/ose.cover	1970-01-01 03:00:00.000000000 +0300
@@ -1,2 +0,0 @@
-%% -*- erlang -*-
-{incl_app,ose,details}.
diff -Ndurp otp_src_18.3.4.5/lib/ose/test/ose.spec otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/ose.spec
--- otp_src_18.3.4.5/lib/ose/test/ose.spec	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/ose.spec	1970-01-01 03:00:00.000000000 +0300
@@ -1 +0,0 @@
-{suites,"../ose_test",all}.
diff -Ndurp otp_src_18.3.4.5/lib/ose/test/ose_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/ose_SUITE.erl
--- otp_src_18.3.4.5/lib/ose/test/ose_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/test/ose_SUITE.erl	1970-01-01 03:00:00.000000000 +0300
@@ -1,766 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1998-2013. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
--module(ose_SUITE).
-
-%-compile(export_all).
-
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
-	 init_per_group/2,end_per_group/2,init_per_testcase/2,
-	 end_per_testcase/2]).
--export([
-	 basic/1,stress/1,multi_msg_numbers/1,multi_mailboxes/1,
-	 hunt/1,multi_hunt/1,dehunt/1,multi_dehunt/1,
-	 attach/1,multi_attach/1,detach/1,multi_detach/1,
-	 open_errors/1,close_errors/1,get_id_errors/1,get_name_errors/1,
-	 hunt_errors/1,dehunt_errors/1,attach_errors/1,detach_errors/1,
-	 send_errors/1,send_w_s_errors/1,listen_errors/1
-	]).
-
--define(INTERFACE,ose).
-
-
-init_per_testcase(_Func, Config) ->
-    Config.
-end_per_testcase(_Func, _Config) ->
-    ok.
-
-suite() -> [{timeout,{30,seconds}}].
-
-all() ->
-    [
-     basic,stress,multi_msg_numbers,multi_mailboxes,
-     hunt,multi_hunt,dehunt,multi_dehunt,
-     attach,multi_attach,detach,multi_detach,
-
-     open_errors,close_errors,get_id_errors,get_name_errors,
-     hunt_errors,dehunt_errors,attach_errors,detach_errors,
-     send_errors,send_w_s_errors,listen_errors
-    ].
-
-groups() ->
-    [].
-
-init_per_suite(Config) ->
-    case os:type() of
-	{ose,_} ->
-	    Config;
-	_Else ->
-	    {skip,"Only run on OSE"}
-    end.
-
-end_per_suite(_Config) ->
-    ok.
-
-init_per_group(_GroupName, Config) ->
-    Config.
-
-end_per_group(_GroupName, Config) ->
-    Config.
-
-basic(_Config) ->
-
-    [P1,P2] = multi_open(2,[42]),
-    P1Id = ?INTERFACE:get_id(P1),
-    P2Id = ?INTERFACE:get_id(P2),
-
-    ok = ?INTERFACE:send(P2,P1Id,42,<<"ping">>),
-    receive
-	{message,P1,V1} ->
-	    {P2Id,P1Id,42,<<"ping">>} = V1,
-	    ?INTERFACE:send(P1,P2Id,42,<<"pong">>);
-	Else1 ->
-	    ct:fail({got_wrong_message,Else1})
-    end,
-
-    receive
-	{message,P2,V2} ->
-	    {P1Id,P2Id,42,<<"pong">>} = V2;
-	Else2 ->
-	    ct:fail({got_wrong_message,Else2})
-    end,
-
-    ?INTERFACE:close(P1),
-    ?INTERFACE:close(P2).
-
-%% Send 1000 messages and see if we can cope and that msg order is preserved
-stress(_Config) ->
-
-    Iterations = 1000,
-
-    [P1,P2] = multi_open(2,[42]),
-    P1Id = ?INTERFACE:get_id(P1),
-    P2Id = ?INTERFACE:get_id(P2),
-
-    spawn(fun() ->
-		  n(fun(N) ->
-			    Msg = [<<"ping">>|integer_to_list(N)],
-			    ?INTERFACE:send(P2,P1Id,42,Msg)
-		    end,Iterations)
-	  end),
-    timer:sleep(100),
-    n(fun(N) ->
-	      receive
-		  {message,P1,Value} ->
-		      Int = integer_to_binary(N),
-		      {P2Id,P1Id,42,<<"ping",Int/binary>>} = Value,
-		      ok;
-		  Else ->
-		      ct:fail({got_wrong_message,Else})
-	      end
-      end,Iterations),
-
-    ?INTERFACE:close(P1),
-    ?INTERFACE:close(P2).
-
-%% Listen to 1000 different message numbers and send some random messages
-multi_msg_numbers(_Config) ->
-
-    Iterations = 100,
-
-    [P1,P2] = multi_open(2,lists:seq(2000,3000)),
-    P1Id = ?INTERFACE:get_id(P1),
-
-    n(fun(_) ->
-	      Num = random:uniform(1000)+2000,
-	      ?INTERFACE:send(P2,P1Id,Num,<<"ping",(integer_to_binary(Num))/binary>>)
-      end,Iterations),
-
-    n(fun(_) ->
-	      receive
-		  {message,P1,{_,_,Id,<<"ping",Num/binary>>}} when Id > 2000;
-								   Id =< 3000 ->
-		      Id = binary_to_integer(Num),
-		      ok;
-		  Else ->
-		      ct:fail({got_wrong_message,Else})
-	      end
-      end,Iterations),
-
-    ?INTERFACE:close(P1),
-    ?INTERFACE:close(P2).
-
-
-%% Create 100 mailboxes and send messages to them
-multi_mailboxes(_Config) ->
-
-    Mailboxes = 100,
-
-    [P1|MBs] = multi_open(Mailboxes,[42]),
-
-    [?INTERFACE:send(P1,?INTERFACE:get_id(P),42,[<<"ping">>,?INTERFACE:get_name(P,?INTERFACE:get_id(P))]) || P <- MBs],
-
-    [receive
-	 {message,P,Value} ->
-	     Name = ?INTERFACE:get_name(P,?INTERFACE:get_id(P)),
-	     {_,_,42,<<"ping",Name/binary>>} = Value,
-	     ok
-     end || P <- MBs],
-
-    [?INTERFACE:close(P) || P <- [P1|MBs]],
-    ok.
-
-hunt(_Config) ->
-    [P1,P2] = multi_open(2,[]),
-
-    Ref = ?INTERFACE:hunt(P1,"p2"),
-    receive
-	{mailbox_up,P1,Ref,Pid} ->
-	    Pid = ?INTERFACE:get_id(P2),
-	    ?INTERFACE:close(P1),
-	    ?INTERFACE:close(P2);
-	Else ->
-	    ct:fail({got_wrong_message,Else,Ref})
-    end.
-
-multi_hunt(_Config) ->
-
-    Iterations = 100,
-
-    P = ?INTERFACE:open("p"),
-
-    Refs = [?INTERFACE:hunt(P,"p"++integer_to_list(N))|| N <- lists:seq(1,Iterations)],
-
-    Pids = [begin
-		Prt = ?INTERFACE:open("p"++integer_to_list(N)),
-		Pid = ?INTERFACE:get_id(Prt),
-		?INTERFACE:close(Prt),
-		Pid
-	    end || N <- lists:seq(1,Iterations)],
-
-    [receive
-	 {mailbox_up,P,Ref,Pid} ->
-	     ok
-     after 10 ->
-	     ct:fail({did_not_get,Pid,Ref})
-     end || {Pid,Ref} <- lists:zip(Pids,Refs)],
-    ?INTERFACE:close(P).
-
-
-dehunt(_Config)  ->
-    [P1] = multi_open(1,[]),
-    Ref = ?INTERFACE:hunt(P1,"p2"),
-    receive
-	_Else -> ct:fail({got,_Else})
-    after 1000 ->
-	    ok
-    end,
-    P2 = ?INTERFACE:open("p2"),
-
-    % Make sure any messages are sent
-    receive after 10 -> ok end,
-
-    ok = ?INTERFACE:dehunt(P1,Ref),
-
-    % Make sure no messages are received
-    receive
-	_Else2 -> ct:fail({got,_Else2})
-    after 1000 ->
-	    ?INTERFACE:close(P1),
-	    ?INTERFACE:close(P2)
-    end.
-
-%%%
-%%% This testcase basically:
-%%%  spawn 10 processes that in parallel
-%%%        adds some hunts for different OSE processes
-%%%        maybe create hunted OSE process
-%%%        dehunt half of the hunts
-%%%        create more hunts
-%%%        if not created create hunted OSE process
-%%%        veryify that all expected hunt messages are received
-%%%  verify that all processes exited correctly
-%%%
-%%% This complex test is done to make sure that the internal handling
-%%% of dehunt works as expected.
-%%%
-multi_dehunt(_Config) ->
-    [P1] = multi_open(1,[]),
-
-    Scenario =
-	fun(Iterations) ->
-
-	      Hunted = "p"++integer_to_list(Iterations),
-	      %% Start a couple of hunts
-	      Refs = [?INTERFACE:hunt(P1,Hunted) || _ <- lists:seq(1,Iterations)],
-
-	      %% We alternate if the process is opened before or after the dehunt
-	      P2O = if Iterations rem 2 == 0 ->
-			    ?INTERFACE:open(Hunted);
-		       true ->
-			    undefined
-		    end,
-
-	      %% Remove half of them
-	      {RemRefs,_} = lists:mapfoldl(fun(Ref,Acc) when Acc rem 2 == 0 ->
-						   ok = ?INTERFACE:dehunt(P1,Ref),
-						   {[],Acc+1};
-					      (Ref,Acc) ->
-						   {Ref,Acc+1}
-					   end,0,Refs),
-
-	      %% Add some new ones
-	      NewRefs = [?INTERFACE:hunt(P1,Hunted)
-			 || _ <- lists:seq(1,Iterations div 4)]
-		    ++ lists:flatten(RemRefs),
-
-	      P2 = if P2O == undefined ->
-			   ?INTERFACE:open(Hunted);
-		      true ->
-			   P2O
-		   end,
-	      P2Id = ?INTERFACE:get_id(P2),
-
-	      %% Receive all the expected ones
-	      lists:foreach(fun(Ref) ->
-				    receive
-					{mailbox_up,P1,Ref,P2Id} ->
-					    ok
-				    after 1000 ->
-					    io:format("Flush: ~p~n",[flush()]),
-					    io:format("~p~n",[{Iterations,{did_not_get, Ref}}]),
-					    ok = Ref
-				    end
-			    end,NewRefs),
-
-	      %% Check that no other have arrived
-	      receive
-		  _Else ->
-		      io:format("Flush: ~p~n",[flush()]),
-		      io:format("~p~n",[{Iterations,{got, _Else}}]),
-		      ok = _Else
-	      after 100 ->
-		      ok
-	      end,
-	      ?INTERFACE:close(P2)
-      end,
-
-    Self = self(),
-
-    n(fun(N) ->
-	      spawn(fun() -> Self !
-				 Scenario(N*25)
-		    end),
-	      ok
-      end,10),
-
-    n(fun(_N) ->
-	      receive ok -> ok
-	      after 60000 -> ct:fail(failed)
-	      end
-      end,10),
-    ?INTERFACE:close(P1).
-
-attach(_Config) ->
-    [P1,P2] = multi_open(2,[]),
-
-    P2Id = ?INTERFACE:get_id(P2),
-    Ref = ?INTERFACE:attach(P1,P2Id),
-    ?INTERFACE:close(P2),
-    receive
-	{mailbox_down,P1,Ref,P2Id} ->
-	    ?INTERFACE:close(P1);
-	_Else ->
-	    ct:fail({got,_Else, {P1,Ref,P2Id}})
-    after 1000 ->
-	    ct:fail({did_not_get,P1,Ref,P2Id})
-    end.
-
-multi_attach(_Config) ->
-
-    Iterations = 100,
-
-    [P1|Pids] = multi_open(Iterations,[]),
-
-    Refs = [{?INTERFACE:get_id(Pid),?INTERFACE:attach(P1,?INTERFACE:get_id(Pid))} || Pid <- Pids],
-
-    [?INTERFACE:close(Pid) || Pid <- Pids],
-
-    [receive
-	 {mailbox_down,P1,Ref,Pid} ->
-	     ok
-     after 10000 ->
-	     ct:fail({did_not_get,Pid,Ref})
-     end || {Pid,Ref} <- Refs],
-    ?INTERFACE:close(P1).
-
-detach(_Config)  ->
-    [P1,P2] = multi_open(2,[]),
-    P2Id = ?INTERFACE:get_id(P2),
-    Ref = ?INTERFACE:attach(P1,P2Id),
-    receive
-	_Else -> ct:fail({got,_Else})
-    after 100 ->
-	    ok
-    end,
-
-    ?INTERFACE:close(P2),
-
-    % Make sure any messages are sent
-    receive after 10 -> ok end,
-
-    ?INTERFACE:detach(P1,Ref),
-
-    % Make sure no messages are received
-    receive
-	_Else2 -> ct:fail({got,_Else2})
-    after 1000 ->
-	    ?INTERFACE:close(P1)
-    end.
-
-%%%
-%%% This testcase basically:
-%%%  spawn 10 processes that in parallel
-%%%        adds some attach for different OSE processes
-%%%        maybe close OSE process
-%%%        dehunt half of the hunts
-%%%        create more hunts
-%%%        if not closed close attached OSE process
-%%%        veryify that all expected attach messages are received
-%%%  verify that all processes exited correctly
-%%%
-%%% This complex test is done to make sure that the internal handling
-%%% of dehunt works as expected.
-%%%
-multi_detach(_Config) ->
-    [P1] = multi_open(1,[]),
-
-    Scenario =
-	fun(Iterations) ->
-
-	      Attached = ?INTERFACE:open("p"++integer_to_list(Iterations)),
-	      AttachedId = ?INTERFACE:get_id(Attached),
-	      %% Start a couple of attachs
-	      Refs = [?INTERFACE:attach(P1,AttachedId) || _ <- lists:seq(1,Iterations)],
-
-	      %% We alternate if the process is closed before or after the detach
-	      P2O = if Iterations rem 2 == 0 ->
-			    ?INTERFACE:close(Attached);
-		       true ->
-			    undefined
-		    end,
-
-	      %% Remove half of them
-	      {RemRefs,_} = lists:mapfoldl(fun(Ref,Acc) when Acc rem 2 == 0 ->
-						   ok = ?INTERFACE:detach(P1,Ref),
-						   {[],Acc+1};
-					      (Ref,Acc) ->
-						   {Ref,Acc+1}
-					   end,0,Refs),
-
-	      %% Add some new ones
-	      NewRefs = [?INTERFACE:attach(P1,AttachedId)
-			 || _ <- lists:seq(1,Iterations div 4)]
-		    ++ lists:flatten(RemRefs),
-
-	      if P2O == undefined ->
-		      ?INTERFACE:close(Attached);
-		 true ->
-		      P2O
-	      end,
-
-	      %% Receive all the expected ones
-	      lists:foreach(fun(Ref) ->
-				    receive
-					{mailbox_down,P1,Ref,AttachedId} ->
-					    ok
-				    after 1000 ->
-					    io:format("Flush: ~p~n",[flush()]),
-					    io:format("~p~n",[{Iterations,{did_not_get, Ref}}]),
-					    ok = Ref
-				    end
-			    end,NewRefs),
-
-	      %% Check that no other have arrived
-	      receive
-		  _Else ->
-		      io:format("Flush: ~p~n",[flush()]),
-		      io:format("~p~n",[{Iterations,{got, _Else}}]),
-		      ok = _Else
-	      after 100 ->
-		      ok
-	      end
-      end,
-
-    Self = self(),
-
-    n(fun(N) ->
-	      spawn(fun() -> Self !
-				 Scenario(N*5)
-		    end),
-	      ok
-      end,10),
-
-    n(fun(_N) ->
-	      receive ok -> ok
-	      after 60000 -> ct:fail(failed)
-	      end
-      end,10),
-    ?INTERFACE:close(P1).
-
-
-open_errors(_Config) ->
-    {'EXIT',{badarg,[{?INTERFACE,open,[inval],_}|_]}} =
-	(catch ?INTERFACE:open(inval)),
-    {'EXIT',{badarg,[{?INTERFACE,open,[["p"|1]],_}|_]}} =
-	(catch ?INTERFACE:open(["p"|1])),
-    {'EXIT',{badarg,[{?INTERFACE,open,[["p",1234]],_}|_]}} =
-	(catch ?INTERFACE:open(["p",1234])),
-
-    ok.
-
-close_errors(_Config) ->
-    {'EXIT',{badarg,[{?INTERFACE,close,[inval],_}|_]}} =
-	(catch ?INTERFACE:close(inval)),
-
-    P1 = ?INTERFACE:open("p1"),
-    ok = ?INTERFACE:close(P1),
-    ok = ?INTERFACE:close(P1).
-
-
-get_id_errors(_Config) ->
-    {'EXIT',{badarg,[{?INTERFACE,get_id,[inval],_}|_]}} =
-	(catch ?INTERFACE:get_id(inval)),
-
-    P1 = ?INTERFACE:open("p1"),
-    ok = ?INTERFACE:close(P1),
-    {'EXIT',{badarg,[{?INTERFACE,get_id,[P1],_}|_]}} =
-	(catch ?INTERFACE:get_id(P1)),
-
-    ok.
-
-get_name_errors(_Config) ->
-    P1 = ?INTERFACE:open("p1"),
-    {'EXIT',{badarg,[{?INTERFACE,get_name,[P1,inval],_}|_]}} =
-	(catch ?INTERFACE:get_name(P1,inval)),
-
-    undefined = ?INTERFACE:get_name(P1,1234),
-
-    P2 = ?INTERFACE:open("p2"),
-    P2Id = ?INTERFACE:get_id(P2),
-    ok = ?INTERFACE:close(P1),
-    {'EXIT',{badarg,[{?INTERFACE,get_name,[P1,P2Id],_}|_]}} =
-	(catch ?INTERFACE:get_name(P1,P2Id)),
-    ?INTERFACE:close(P2),
-
-    P3 = ?INTERFACE:open([255]),
-    <<255>> = ?INTERFACE:get_name(P3, ?INTERFACE:get_id(P3)),
-    ?INTERFACE:close(P3),
-
-    ok.
-
-hunt_errors(_Config) ->
-
-    {'EXIT',{badarg,[{?INTERFACE,hunt,[inval,"hello"],_}|_]}} =
-	(catch ?INTERFACE:hunt(inval,"hello")),
-
-    P1 = ?INTERFACE:open("p1"),
-    {'EXIT',{badarg,[{?INTERFACE,hunt,[P1,["hello",12345]],_}|_]}} =
-	(catch ?INTERFACE:hunt(P1,["hello",12345])),
-
-    P2 = ?INTERFACE:open(<<255>>),
-    P2Pid = ?INTERFACE:get_id(P2),
-    Ref = ?INTERFACE:hunt(P1,[255]),
-    receive
-	{mailbox_up,P1,Ref,P2Pid} ->
-	    ok;
-	Else ->
-	    ct:fail({got,Else,{mailbox_up,P1,Ref,P2Pid}})
-    after 150 ->
-	    ct:fail({did_not_get,{mailbox_up,P1,Ref,P2Pid}})
-    end,
-
-    ok = ?INTERFACE:close(P1),
-    ok = ?INTERFACE:close(P2),
-    {'EXIT',{badarg,[{?INTERFACE,hunt,[P1,["hello"]],_}|_]}} =
-	(catch ?INTERFACE:hunt(P1,["hello"])),
-
-    ok.
-
-dehunt_errors(_Config) ->
-    P1 = ?INTERFACE:open("p1"),
-    Ref = ?INTERFACE:hunt(P1,"p2"),
-
-    {'EXIT',{badarg,[{?INTERFACE,dehunt,[inval,Ref],_}|_]}} =
-	(catch ?INTERFACE:dehunt(inval,Ref)),
-
-    {'EXIT',{badarg,[{?INTERFACE,dehunt,[P1,inval],_}|_]}} =
-	(catch ?INTERFACE:dehunt(P1,inval)),
-
-    ok = ?INTERFACE:dehunt(P1,Ref),
-    ok = ?INTERFACE:dehunt(P1,Ref),
-
-    ok = ?INTERFACE:close(P1),
-
-    {'EXIT',{badarg,[{?INTERFACE,dehunt,[P1,Ref],_}|_]}} =
-	(catch ?INTERFACE:dehunt(P1,Ref)),
-
-    case ?INTERFACE of
-	ose -> ok;
-	_ ->
-	    P2 = ?INTERFACE:open("p2"),
-	    ok = ?INTERFACE:close(P2)
-    end,
-
-    receive
-	Else -> ct:fail({got,Else})
-    after 100 ->
-	    ok
-    end.
-
-attach_errors(_Config) ->
-    P1 = ?INTERFACE:open("p1"),
-    P2 = ?INTERFACE:open("p2"),
-    P2Id = ?INTERFACE:get_id(P2),
-
-    {'EXIT',{badarg,[{?INTERFACE,attach,[inval,P2Id],_}|_]}} =
-	(catch ?INTERFACE:attach(inval,P2Id)),
-
-    {'EXIT',{badarg,[{?INTERFACE,attach,[P1,[12345]],_}|_]}} =
-	(catch ?INTERFACE:attach(P1,[12345])),
-
-    ok = ?INTERFACE:close(P1),
-    ok = ?INTERFACE:close(P2),
-    {'EXIT',{badarg,[{?INTERFACE,attach,[P1,P2Id],_}|_]}} =
-	(catch ?INTERFACE:attach(P1,P2Id)),
-
-    ok.
-
-detach_errors(_Config) ->
-    P1 = ?INTERFACE:open("p1"),
-    P2 = ?INTERFACE:open("p2"),
-    P2Id = ?INTERFACE:get_id(P2),
-
-    Ref = ?INTERFACE:attach(P1,P2Id),
-
-    {'EXIT',{badarg,[{?INTERFACE,detach,[inval,Ref],_}|_]}} =
-	(catch ?INTERFACE:detach(inval,Ref)),
-
-    {'EXIT',{badarg,[{?INTERFACE,detach,[P1,inval],_}|_]}} =
-	(catch ?INTERFACE:detach(P1,inval)),
-
-    ok = ?INTERFACE:detach(P1,Ref),
-    ok = ?INTERFACE:detach(P1,Ref),
-
-    case ?INTERFACE of
-	ose -> ok;
-	_ ->
-	    ok = ?INTERFACE:close(P1)
-    end,
-
-    ok = ?INTERFACE:close(P2),
-    ok = ?INTERFACE:close(P1),
-
-    {'EXIT',{badarg,[{?INTERFACE,detach,[P1,Ref],_}|_]}} =
-	(catch ?INTERFACE:detach(P1,Ref)),
-
-    receive
-	Else -> ct:fail({got,Else})
-    after 100 ->
-	    ok
-    end.
-
-send_errors(_Config) ->
-    P1 = ?INTERFACE:open("p1"),
-    P2 = ?INTERFACE:open("p2"),
-    P2Id = ?INTERFACE:get_id(P2),
-
-    {'EXIT',{badarg,[{?INTERFACE,send,[inval,P2Id,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(inval,P2Id,42,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P1,inval,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P1,inval,42,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P1,P2Id,inval,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P1,P2Id,inval,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P1,P2Id,42,inval],_}|_]}} =
-	(catch ?INTERFACE:send(P1,P2Id,42,inval)),
-
-    ok = ?INTERFACE:close(P2),
-    ok = ?INTERFACE:send(P1,P2Id,42,"hello"),
-    ok = ?INTERFACE:close(P1),
-
-    {'EXIT',{badarg,[{?INTERFACE,send,[P1,P2Id,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P1,P2Id,42,"hello")),
-
-    receive
-	Else -> ct:fail({got,Else})
-    after 100 ->
-	    ok
-    end.
-
-send_w_s_errors(_Config) ->
-    P1 = ?INTERFACE:open("p1"),
-    P1Id = ?INTERFACE:get_id(P1),
-    P2 = ?INTERFACE:open("p2"),
-    P2Id = ?INTERFACE:get_id(P2),
-    P3 = ?INTERFACE:open("p3"),
-    P3Id = ?INTERFACE:get_id(P3),
-
-    {'EXIT',{badarg,[{?INTERFACE,send,[inval,P2Id,P1Id,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(inval,P2Id,P1Id,42,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P2,-1,P1Id,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P2,-1,P1Id,42,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P2,P2Id,1 bsl 32,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P2,P2Id,1 bsl 32,42,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P2,P2Id,P1Id,inval,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P2,P2Id,P1Id,inval,"hello")),
-    {'EXIT',{badarg,[{?INTERFACE,send,[P2,P2Id,P1Id,42,inval],_}|_]}} =
-	(catch ?INTERFACE:send(P2,P2Id,P1Id,42,inval)),
-
-    ok = ?INTERFACE:close(P3),
-    ok = ?INTERFACE:send(P2,P3Id,P1Id,42,"hello"),
-
-    ok = ?INTERFACE:close(P1),
-    ok = ?INTERFACE:send(P2,P2Id,P1Id,42,"hello"),
-    ok = ?INTERFACE:close(P2),
-
-    {'EXIT',{badarg,[{?INTERFACE,send,[P1,P2Id,P1Id,42,"hello"],_}|_]}} =
-	(catch ?INTERFACE:send(P1,P2Id,P1Id,42,"hello")),
-
-    receive
-	Else -> ct:fail({got,Else})
-    after 100 ->
-	    ok
-    end.
-
-listen_errors(_Config) ->
-
-    P1 = ?INTERFACE:open("p1"),
-    P1Id = ?INTERFACE:get_id(P1),
-
-    {'EXIT',{badarg,[{?INTERFACE,listen,[inval,[42]],_}|_]}} =
-	(catch ?INTERFACE:listen(inval,[42])),
-    {'EXIT',{badarg,[{?INTERFACE,listen,[P1,inval],_}|_]}} =
-	(catch ?INTERFACE:listen(P1,inval)),
-    {'EXIT',{badarg,[{?INTERFACE,listen,[P1,[1 bsl 33]],_}|_]}} =
-	(catch ?INTERFACE:listen(P1,[1 bsl 33])),
-
-    ok = ?INTERFACE:listen(P1,[42,42,42,42,42,42,42,42,42,42,42,42,42]),
-
-    case ?INTERFACE of
-	ose -> ok;
-	_ ->
-	    ?INTERFACE:send(P1,P1Id,42,"hello"),
-	    timer:sleep(50),
-	    ?INTERFACE:listen(P1,[]),
-	    ?INTERFACE:send(P1,P1Id,42,"hello2"),
-
-	    receive
-		{message,P1,42,"hello"} -> ok
-	    end,
-
-	    receive
-		Else -> ct:fail({got,Else})
-	    after 100 ->
-		    ok
-	    end
-    end,
-
-    ok = ?INTERFACE:close(P1),
-    {'EXIT',{badarg,[{?INTERFACE,listen,[P1,[42]],_}|_]}} =
-	(catch ?INTERFACE:listen(P1,[42])),
-
-    ok.
-
-%%
-%% Internal functions
-%%
-multi_open(N,ListenNums) ->
-    multi_open(N,ListenNums,[]).
-
-multi_open(0,_,Acc) ->
-    Acc;
-multi_open(N,ListenNums,Acc) ->
-    P = ?INTERFACE:open("p"++integer_to_list(N)),
-    ok = ?INTERFACE:listen(P,ListenNums),
-    multi_open(N-1,ListenNums,[P|Acc]).
-
-n(_F,0) ->
-    ok;
-n(F,N) ->
-    ok = F(N),
-    n(F,N-1).
-
-
-flush() ->
-    receive
-	Msg ->
-	    [Msg|flush()]
-    after 0 ->
-	    []
-    end.
diff -Ndurp otp_src_18.3.4.5/lib/ose/vsn.mk otp_src_18.3.4.5-remove-OSE-port/lib/ose/vsn.mk
--- otp_src_18.3.4.5/lib/ose/vsn.mk	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/ose/vsn.mk	1970-01-01 03:00:00.000000000 +0300
@@ -1 +0,0 @@
-OSE_VSN = 1.1
diff -Ndurp otp_src_18.3.4.5/lib/runtime_tools/c_src/Makefile.in otp_src_18.3.4.5-remove-OSE-port/lib/runtime_tools/c_src/Makefile.in
--- otp_src_18.3.4.5/lib/runtime_tools/c_src/Makefile.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/runtime_tools/c_src/Makefile.in	2017-02-03 21:52:59.171950956 +0200
@@ -102,12 +102,7 @@ endif
 
 _create_dirs := $(shell mkdir -p $(OBJDIR) $(LIBDIR))
 
-ifneq ($(findstring ose,$(TARGET)),ose)
 debug opt valgrind: $(SOLIBS) $(OBJDIR) $(LIBDIR) $(NIF_LIB)
-else
-# We do not build this on OSE
-debug opt valgrind:
-endif
 
 DYNTRACE_OBJS = $(before_DTrace_OBJS)
 
@@ -159,10 +154,8 @@ include $(ERL_TOP)/make/otp_release_targ
 release_spec: opt
 	$(INSTALL_DIR) "$(RELSYSDIR)/priv/obj"
 	$(INSTALL_DIR) "$(RELSYSDIR)/priv/lib"
-ifneq ($(findstring ose,$(TARGET)),ose)
 	$(INSTALL_PROGRAM) $(DYNTRACE_OBJS) "$(RELSYSDIR)/priv/obj"
 	$(INSTALL_PROGRAM) $(NIF_LIB) $(SOLIBS) "$(RELSYSDIR)/priv/lib"
-endif
 
 release_docs_spec:
 
diff -Ndurp otp_src_18.3.4.5/lib/stdlib/src/slave.erl otp_src_18.3.4.5-remove-OSE-port/lib/stdlib/src/slave.erl
--- otp_src_18.3.4.5/lib/stdlib/src/slave.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/stdlib/src/slave.erl	2017-02-03 21:52:59.171950956 +0200
@@ -289,10 +289,7 @@ register_unique_name(Number) ->
 %% no need to use rsh.
 
 mk_cmd(Host, Name, Args, Waiter, Prog0) ->
-    Prog = case os:type() of
-	       {ose,_} -> mk_ose_prog(Prog0);
-	       _ -> quote_progname(Prog0)
-	   end,
+    Prog = quote_progname(Prog0),
     BasicCmd = lists:concat([Prog,
 			     " -detached -noinput -master ", node(),
 			     " ", long_or_short(), Name, "@", Host,
@@ -312,24 +309,6 @@ mk_cmd(Host, Name, Args, Waiter, Prog0)
 	    end
     end.
 
-%% On OSE we have to pass the beam arguments directory to the slave
-%% process. To find out what arguments that should be passed on we
-%% make an assumption. All arguments after the last "--" should be
-%% skipped. So given these arguments:
-%%     -Muycs256 -A 1 -- -root /mst/ -progname beam.debug.smp -- -home /mst/ -- -kernel inetrc '"/mst/inetrc.conf"' -- -name test@localhost
-%% we send
-%%     -Muycs256 -A 1 -- -root /mst/ -progname beam.debug.smp -- -home /mst/ -- -kernel inetrc '"/mst/inetrc.conf"' --
-%% to the slave with whatever other args that are added in mk_cmd.
-mk_ose_prog(Prog) ->
-    SkipTail = fun("--",[]) ->
-		       ["--"];
-		  (_,[]) ->
-		       [];
-		  (Arg,Args) ->
-		       [Arg," "|Args]
-	       end,
-    [Prog,tl(lists:foldr(SkipTail,[],erlang:system_info(emu_args)))].
-
 %% This is an attempt to distinguish between spaces in the program
 %% path and spaces that separate arguments. The program is quoted to
 %% allow spaces in the path.
diff -Ndurp otp_src_18.3.4.5/lib/stdlib/test/filename_SUITE.erl otp_src_18.3.4.5-remove-OSE-port/lib/stdlib/test/filename_SUITE.erl
--- otp_src_18.3.4.5/lib/stdlib/test/filename_SUITE.erl	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/stdlib/test/filename_SUITE.erl	2017-02-03 21:52:59.171950956 +0200
@@ -97,20 +97,11 @@ absname(Config) when is_list(Config) ->
 	    
 	    ?line file:set_cwd(Cwd),
 	    ok;
-	Type ->
-	    case Type of
-		{unix, _} ->
-		    ?line ok = file:set_cwd("/usr"),
-		    ?line "/usr/foo" = filename:absname(foo),
-		    ?line "/usr/foo" = filename:absname("foo"),
-		    ?line "/usr/../ebin" = filename:absname("../ebin");
-		{ose, _} ->
-		    ?line ok = file:set_cwd("/romfs"),
-		    ?line "/romfs/foo" = filename:absname(foo),
-		    ?line "/romfs/foo" = filename:absname("foo"),
-		    ?line "/romfs/../ebin" = filename:absname("../ebin")
-	    end,
-	    
+	{unix, _} ->
+            ?line ok = file:set_cwd("/usr"),
+            ?line "/usr/foo" = filename:absname(foo),
+            ?line "/usr/foo" = filename:absname("foo"),
+            ?line "/usr/../ebin" = filename:absname("../ebin"),
 	    ?line file:set_cwd("/"),
 	    ?line "/foo" = filename:absname(foo),
 	    ?line "/foo" = filename:absname("foo"),
@@ -494,18 +485,10 @@ absname_bin(Config) when is_list(Config)
 	    
 	    ?line file:set_cwd(Cwd),
 	    ok;
-	Type ->
-	    case Type of
-		{unix,_} ->
-		    ?line ok = file:set_cwd(<<"/usr">>),
-		    ?line <<"/usr/foo">> = filename:absname(<<"foo">>),
-		    ?line <<"/usr/../ebin">> = filename:absname(<<"../ebin">>);
-		{ose,_} ->
-		    ?line ok = file:set_cwd(<<"/romfs">>),
-		    ?line <<"/romfs/foo">> = filename:absname(<<"foo">>),
-		    ?line <<"/romfs/../ebin">> = filename:absname(<<"../ebin">>)
-	    end,
-	    
+	{unix, _} ->
+            ?line ok = file:set_cwd(<<"/usr">>),
+            ?line <<"/usr/foo">> = filename:absname(<<"foo">>),
+            ?line <<"/usr/../ebin">> = filename:absname(<<"../ebin">>),
 	    ?line file:set_cwd(<<"/">>),
 	    ?line <<"/foo">> = filename:absname(<<"foo">>),
 	    ?line <<"/../ebin">> = filename:absname(<<"../ebin">>),
diff -Ndurp otp_src_18.3.4.5/lib/tools/c_src/Makefile.in otp_src_18.3.4.5-remove-OSE-port/lib/tools/c_src/Makefile.in
--- otp_src_18.3.4.5/lib/tools/c_src/Makefile.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/lib/tools/c_src/Makefile.in	2017-02-03 21:52:59.171950956 +0200
@@ -97,11 +97,8 @@ DRIVERS=
 
 ifneq ($(strip $(ETHR_LIB_NAME)),)
 # Need ethread package for emem
-ifneq ($(findstring ose,$(TARGET)),ose)
-# Do not build on OSE
 PROGS += $(BIN_DIR)/emem$(TYPEMARKER)@EXEEXT@
 endif
-endif
 
 EMEM_OBJ_DIR=$(OBJ_DIR)/emem
 CREATE_DIRS += $(EMEM_OBJ_DIR)
@@ -152,12 +149,7 @@ ERTS_LIB = $(ERL_TOP/erts/lib_src/obj/$(
 
 _create_dirs := $(shell mkdir -p $(CREATE_DIRS))
 
-ifneq ($(findstring ose,$(TARGET)),ose)
 all: $(PROGS) $(DRIVERS)
-else
-# Do not build dynamic files on OSE
-all:
-endif
 
 $(ERTS_LIB):
 	$(make_verbose)cd $(ERL_TOP)/erts/lib_src && $(MAKE) $(TYPE)
diff -Ndurp otp_src_18.3.4.5/make/ose_lm.mk.in otp_src_18.3.4.5-remove-OSE-port/make/ose_lm.mk.in
--- otp_src_18.3.4.5/make/ose_lm.mk.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/make/ose_lm.mk.in	1970-01-01 03:00:00.000000000 +0300
@@ -1,76 +0,0 @@
-#-*-makefile-*-   ; force emacs to enter makefile-mode
-# ----------------------------------------------------
-# Template target for generating an OSE5 load module
-#
-# %CopyrightBegin%
-#
-# Copyright Ericsson AB 2013. All Rights Reserved.
-#
-# Licensed under the Apache License, Version 2.0 (the "License");
-# you may not use this file except in compliance with the License.
-# You may obtain a copy of the License at
-#
-#     http://www.apache.org/licenses/LICENSE-2.0
-#
-# Unless required by applicable law or agreed to in writing, software
-# distributed under the License is distributed on an "AS IS" BASIS,
-# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-# See the License for the specific language governing permissions and
-# limitations under the License.
-#
-# %CopyrightEnd%
-#
-# Author: Petre Pircalabu
-# ----------------------------------------------------
-
-# ----------------------------------------------------
-# 	build-ose-load-module
-#	Creates an OSE5 load module
-#	params:
-#		$(1) - The output target
-#		$(2) - Objects
-#		$(3) - Libraries
-#		$(4) - LM configuration file
-# ----------------------------------------------------
-
-ifeq ($(findstring ose,$(TARGET)),ose)
-LDR1FLAGS    = @erl_xcomp_ose_ldflags_pass1@
-LDR2FLAGS    = @erl_xcomp_ose_ldflags_pass2@
-OSEROOT	     = @erl_xcomp_ose_OSEROOT@
-LCF	     = @erl_xcomp_ose_LM_LCF@
-BEAM_LMCONF  = @erl_xcomp_ose_BEAM_LM_CONF@
-EPMD_LMCONF  = @erl_xcomp_ose_EPMD_LM_CONF@
-RUN_ERL_LMCONF = @erl_xcomp_ose_RUN_ERL_LM_CONF@
-STRIP	     = @erl_xcomp_ose_STRIP@
-LM_POST_LINK = @erl_xcomp_ose_LM_POST_LINK@
-LM_SET_CONF  = @erl_xcomp_ose_LM_SET_CONF@
-LM_ELF_SIZE  = @erl_xcomp_ose_LM_ELF_SIZE@
-OSE_CONFD    = @erl_xcomp_ose_CONFD@
-CRT0_LM      = @erl_xcomp_ose_CRT0_LM@
-endif
-
-define build-ose-load-module
-	@echo " --- Linking $(1)"
-
-	@echo " --- Linking $(1) (pass 1)"
-	$(ld_verbose)$(PURIFY) $(LD) -o $(1)_unconfigured_ro -r \
-	$(2) --start-group $(3) --end-group --cref --discard-none -M >  $(1)_1.map
-
-	@echo " --- Linking $(1) (pass 2)"
-	$(ld_verbose)$(PURIFY) $(LD) -o $(1)_unconfigured \
-	$(1)_unconfigured_ro -T $(LCF) -n --emit-relocs -e crt0_lm --cref \
-	--discard-none -M >  $(1)_2.map
-
-	@echo " --- Inserting configuration"
-	$(ld_verbose) $(LM_SET_CONF) $(1)_unconfigured < $(4)
-
-	@echo " --- Striping $(1)"
-#	$(ld_verbose) $(STRIP) $(1)_unconfigured
-
-	@echo " --- Postlinking $(1)"
-	$(ld_verbose) $(LM_POST_LINK) $(1)_unconfigured
-
-	@echo " --- Sizing $(1)"
-	$(ld_verbose) $(LM_ELF_SIZE) $(1)_unconfigured
-	mv $(1)_unconfigured $(1)
-endef
diff -Ndurp otp_src_18.3.4.5/make/otp.mk.in otp_src_18.3.4.5-remove-OSE-port/make/otp.mk.in
--- otp_src_18.3.4.5/make/otp.mk.in	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/make/otp.mk.in	2017-02-03 21:52:59.171950956 +0200
@@ -90,14 +90,10 @@ OTP_RELEASE = @OTP_RELEASE@
 #	Erlang language section
 # ----------------------------------------------------
 EMULATOR = beam
-ifeq ($(findstring ose_ppc750,$(TARGET)),ose_ppc750)
-ERL_COMPILE_FLAGS += +compressed
+ifdef BOOTSTRAP
+  ERL_COMPILE_FLAGS += +slim
 else
-  ifdef BOOTSTRAP
-    ERL_COMPILE_FLAGS += +slim
-  else
-    ERL_COMPILE_FLAGS += +debug_info
-  endif
+  ERL_COMPILE_FLAGS += +debug_info
 endif
 ERLC_WFLAGS = -W
 ERLC = erlc $(ERLC_WFLAGS) $(ERLC_FLAGS)
diff -Ndurp otp_src_18.3.4.5/xcomp/erl-xcomp-powerpc-ose5.conf otp_src_18.3.4.5-remove-OSE-port/xcomp/erl-xcomp-powerpc-ose5.conf
--- otp_src_18.3.4.5/xcomp/erl-xcomp-powerpc-ose5.conf	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/xcomp/erl-xcomp-powerpc-ose5.conf	1970-01-01 03:00:00.000000000 +0300
@@ -1,358 +0,0 @@
-## -*-shell-script-*-
-##
-## %CopyrightBegin%
-##
-## Copyright Ericsson AB 2009-2012. All Rights Reserved.
-##
-## Licensed under the Apache License, Version 2.0 (the "License");
-## you may not use this file except in compliance with the License.
-## You may obtain a copy of the License at
-##
-##     http://www.apache.org/licenses/LICENSE-2.0
-##
-## Unless required by applicable law or agreed to in writing, software
-## distributed under the License is distributed on an "AS IS" BASIS,
-## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-## See the License for the specific language governing permissions and
-## limitations under the License.
-##
-## %CopyrightEnd%
-##
-## File: erl-xcomp-sfk-linux-ose5.conf
-## Author: Petre Pircalabu
-##
-## -----------------------------------------------------------------------------
-## When cross compiling Erlang/OTP using `otp_build', copy this file and set
-## the variables needed below. Then pass the path to the copy of this file as
-## an argument to `otp_build' in the configure stage:
-##   `otp_build configure --xcomp-conf=<FILE>'
-## -----------------------------------------------------------------------------
-
-## Note that you cannot define arbitrary variables in a cross compilation
-## configuration file. Only the ones listed below will be guaranteed to be
-## visible throughout the whole execution of all `configure' scripts. Other
-## variables needs to be defined as arguments to `configure' or exported in
-## the environment.
-
-## -- Variables needed for an OSE5 build ---------------------------------------
-OSEROOT="/vobs/ose5/system"
-HOST="linux"
-
-GCCVERSION="4.4.3"
-GCCROOT="${OSEROOT}/gcc_linux_powerpc_${GCCVERSION}"
-
-OSEDEBUG="no"
-OSESSL="no"
-
-case ${GCCVERSION} in
-4.4.3)
-   GCCTARGET="powerpc-eabi"
-   ;;
-4.6.3)
-   GCCTARGET="powerpc-ose-eabi"
-   ;;
-*)
-   echo "Error: Unknown GCCVERSION: ${GCCVERSION}"
-   exit 1
-esac
-
-if [ ${OSEDEBUG} != "yes" ];
-then
-OPT_LEVEL="-O2"
-else
-OPT_LEVEL=""
-fi
-
-if [ ${OSESSL} = "yes" ];
-then
-## If your crypto is not in OSEROOT then you have to use --with-ssl to
-## point to the correct place. Also CRYPTO_LIB_PATH has to be modified to
-## point there as well.
-CRYPTO_CONFIG_OPTION="--disable-dynamic-ssl-lib"
-CRYPTO_NIF_PATH=",$ERL_TOP/lib/crypto/priv/lib/powerpc-unknown-ose/crypto.a"
-CRYPTO_LIB_PATH="${OSEROOT}/lib/powerpc/libsslcrypto.a"
-else
-CRYPTO_CONFIG_OPTION="--without-ssl"
-CRYPTO_NIF_PATH=""
-CRYPTO_LIB_PATH=""
-fi
-
-
-## -- Variables for `otp_build' Only -------------------------------------------
-
-## Variables in this section are only used, when configuring Erlang/OTP for
-## cross compilation using `$ERL_TOP/otp_build configure'.
-
-## *NOTE*! These variables currently have *no* effect if you configure using
-## the `configure' script directly.
-
-# * `erl_xcomp_build' - The build system used. This value will be passed as
-#   `--build=$erl_xcomp_build' argument to the `configure' script. It does
-#   not have to be a full `CPU-VENDOR-OS' triplet, but can be. The full
-#   `CPU-VENDOR-OS' triplet will be created by
-#   `$ERL_TOP/erts/autoconf/config.sub $erl_xcomp_build'. If set to `guess',
-#   the build system will be guessed using
-#   `$ERL_TOP/erts/autoconf/config.guess'.
-erl_xcomp_build=guess
-
-# * `erl_xcomp_host' - Cross host/target system to build for. This value will
-#   be passed as `--host=$erl_xcomp_host' argument to the `configure' script.
-#   It does not have to be a full `CPU-VENDOR-OS' triplet, but can be. The
-#   full `CPU-VENDOR-OS' triplet will be created by
-#   `$ERL_TOP/erts/autoconf/config.sub $erl_xcomp_host'.
-erl_xcomp_host="powerpc-ose"
-
-disabled_apps="--without-erl_interface --without-os_mon --without-megaco --without-observer --without-wx --without-appmon --without-cosEvent --without-cosEventDomain --without-cosFileTransfer --without-cosNotification --without-cosProperty --without-cosTime --without-cosTransactions --without-debugger --without-dialyzer --without-edoc --without-erl_docgen --without-eunit --without-gs --without-hipe --without-ic --without-orber --without-pman --without-toolbar --without-tv --without-webtool --without-typer"
-
-# * `erl_xcomp_configure_flags' - Extra configure flags to pass to the
-#   `configure' script.
-erl_xcomp_configure_flags="${CRYPTO_CONFIG_OPTION} --disable-kernel-poll --disable-hipe --without-termcap --without-javac ${disabled_apps} --enable-static-nifs=$ERL_TOP/lib/asn1/priv/lib/powerpc-unknown-ose/asn1rt_nif.a${CRYPTO_NIF_PATH}"
-
-## -- Cross Compiler and Other Tools -------------------------------------------
-
-## If the cross compilation tools are prefixed by `<HOST>-' you probably do
-## not need to set these variables (where `<HOST>' is what has been passed as
-## `--host=<HOST>' argument to `configure').
-
-## All variables in this section can also be used when native compiling.
-
-# * `CC' - C compiler.
-CC="$GCCROOT/bin/$GCCTARGET-gcc"
-
-# * `CFLAGS' - C compiler flags.
-CFLAGS="-msoft-float -g -fno-strict-aliasing -fno-builtin -fshort-wchar -Wall -Wno-unknown-pragmas -mpowerpc -nostdlib -I$GCCROOT/include/c++/$GCCVERSION -I$OSEROOT/include -I$OSEROOT/include/ose_spi -I$OSEROOT/include/gcc -MD -MP -D__OSE__ -DBIG_ENDIAN  -DCF_CONF_SIZE=0x800 ${OPT_LEVEL}"
-
-
-# * `STATIC_CFLAGS' - Static C compiler flags.
-#STATIC_CFLAGS=
-
-# * `CFLAG_RUNTIME_LIBRARY_PATH' - This flag should set runtime library
-#   search path for the shared libraries. Note that this actually is a
-#   linker flag, but it needs to be passed via the compiler.
-#CFLAG_RUNTIME_LIBRARY_PATH=
-
-# * `CPP' - C pre-processor.
-CPP="$GCCROOT/bin/$GCCTARGET-cpp"
-
-# * `CPPFLAGS' - C pre-processor flags.
-CPPFLAGS="-msoft-float -g -fno-strict-aliasing -fno-builtin -fshort-wchar -Wall -Wno-unknown-pragmas -mpowerpc -nostdlib -I$GCCROOT/include/c++/$GCCVERSION -I$OSEROOT/include -I$OSEROOT/include/ose_spi -I$OSEROOT/include/gcc -MD -MP -D__OSE__ -DBIG_ENDIAN -DCF_CONF_SIZE=0x800 ${OPT_LEVEL}"
-
-
-# * `CXX' - C++ compiler.
-CXX="$GCCROOT/bin/$GCCTARGET-g++"
-
-# * `CXXFLAGS' - C++ compiler flags.
-CXXFLAGS="-msoft-float -g -fno-strict-aliasing -ansi -I$GCCROOT/include/c++/$GCCVERSION -I$OSEROOT/include -I$OSEROOT/include/gcc ${OPT_LEVEL}"
-
-# * `LD' - Linker.
-LD="${GCCROOT}/bin/${GCCTARGET}-ld"
-
-# * `LDFLAGS' - Linker flags.
-LDFLAGS="-Wl,-ecrt0_lm -Wl,-T,${ERL_TOP}/erts/emulator/sys/ose/gcc_${GCCVERSION}_lm_ppc.lcf"
-
-# * `LIBS' - Libraries.
-LIBS="${OSEROOT}/lib/powerpc/libcrt.a ${OSEROOT}/lib/powerpc/libm.a ${GCCROOT}/lib/gcc/${GCCTARGET}/${GCCVERSION}/nof/libgcc.a ${CRYPTO_LIB_PATH}"
-
-## -- *D*ynamic *E*rlang *D*river Linking --
-
-## *NOTE*! Either set all or none of the `DED_LD*' variables.
-
-# * `DED_LD' - Linker for Dynamically loaded Erlang Drivers.
-DED_LD=
-
-# * `DED_LDFLAGS' - Linker flags to use with `DED_LD'.
-DED_LDFLAGS=
-
-# * `DED_LD_FLAG_RUNTIME_LIBRARY_PATH' - This flag should set runtime library
-#   search path for shared libraries when linking with `DED_LD'.
-DED_LD_FLAG_RUNTIME_LIBRARY_PATH=
-
-## -- Large File Support --
-
-## *NOTE*! Either set all or none of the `LFS_*' variables.
-
-# * `LFS_CFLAGS' - Large file support C compiler flags.
-#LFS_CFLAGS=
-
-# * `LFS_LDFLAGS' - Large file support linker flags.
-#LFS_LDFLAGS=
-
-# * `LFS_LIBS' - Large file support libraries.
-#LFS_LIBS=
-
-## -- Other Tools --
-
-# * `RANLIB' - `ranlib' archive index tool.
-RANLIB="$GCCROOT/bin/$GCCTARGET-ranlib"
-
-# * `AR' - `ar' archiving tool.
-AR="$GCCROOT/bin/$GCCTARGET-ar"
-
-# * `STRIP' - `strip
-STRIP="$GCCROOT/bin/$GCCTARGET-strip"
-
-# * `GETCONF' - `getconf' system configuration inspection tool. `getconf' is
-#   currently used for finding out large file support flags to use, and
-#   on Linux systems for finding out if we have an NPTL thread library or
-#   not.
-#GETCONF=
-
-## -- Cross System Root Locations ----------------------------------------------
-
-# * `erl_xcomp_sysroot' - The absolute path to the system root of the cross
-#   compilation environment. Currently, the `crypto', `odbc', `ssh' and
-#   `ssl' applications need the system root. These applications will be
-#   skipped if the system root has not been set. The system root might be
-#   needed for other things too. If this is the case and the system root
-#   has not been set, `configure' will fail and request you to set it.
-erl_xcomp_sysroot="$OSEROOT"
-
-# * `erl_xcomp_isysroot' - The absolute path to the system root for includes
-#   of the cross compilation environment. If not set, this value defaults
-#   to `$erl_xcomp_sysroot', i.e., only set this value if the include system
-#   root path is not the same as the system root path.
-#erl_xcomp_isysroot="$OSEROOT"
-
-## -- Optional Feature, and Bug Tests ------------------------------------------
-
-## These tests cannot (always) be done automatically when cross compiling. You
-## usually do not need to set these variables. Only set these if you really
-## know what you are doing.
-
-## Note that some of these values will override results of tests performed
-## by `configure', and some will not be used until `configure' is sure that
-## it cannot figure the result out.
-
-## The `configure' script will issue a warning when a default value is used.
-## When a variable has been set, no warning will be issued.
-
-# * `erl_xcomp_after_morecore_hook' - `yes|no'. Defaults to `no'. If `yes',
-#   the target system must have a working `__after_morecore_hook' that can be
-#   used for tracking used `malloc()' implementations core memory usage.
-#   This is currently only used by unsupported features.
-#erl_xcomp_after_morecore_hook=
-
-# * `erl_xcomp_bigendian' - `yes|no'. No default. If `yes', the target system
-#   must be big endian. If `no', little endian. This can often be
-#   automatically detected, but not always. If not automatically detected,
-#   `configure' will fail unless this variable is set. Since no default
-#   value is used, `configure' will try to figure this out automatically.
-#erl_xcomp_bigendian=
-
-# * `erl_xcomp_double_middle` - `yes|no`. No default. If `yes`, the
-#   target system must have doubles in "middle-endian" format. If
-#   `no`, it has "regular" endianness. This can often be automatically
-#   detected, but not always. If not automatically detected,
-#   `configure` will fail unless this variable is set. Since no
-#   default value is used, `configure` will try to figure this out
-#   automatically.
-#erl_xcomp_double_middle_endian
-
-# * `erl_xcomp_clock_gettime_cpu_time' - `yes|no'. Defaults to `no'. If `yes',
-#   the target system must have a working `clock_gettime()' implementation
-#   that can be used for retrieving process CPU time.
-#erl_xcomp_clock_gettime_cpu_time=
-
-# * `erl_xcomp_getaddrinfo' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have a working `getaddrinfo()' implementation that can
-#   handle both IPv4 and IPv6.
-#erl_xcomp_getaddrinfo=
-
-# * `erl_xcomp_gethrvtime_procfs_ioctl' - `yes|no'. Defaults to `no'. If `yes',
-#   the target system must have a working `gethrvtime()' implementation and
-#   is used with procfs `ioctl()'.
-#erl_xcomp_gethrvtime_procfs_ioctl=
-
-# * `erl_xcomp_dlsym_brk_wrappers' - `yes|no'. Defaults to `no'. If `yes', the
-#   target system must have a working `dlsym(RTLD_NEXT, <S>)' implementation
-#   that can be used on `brk' and `sbrk' symbols used by the `malloc()'
-#   implementation in use, and by this track the `malloc()' implementations
-#   core memory usage. This is currently only used by unsupported features.
-#erl_xcomp_dlsym_brk_wrappers=
-
-# * `erl_xcomp_kqueue' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have a working `kqueue()' implementation that returns a file
-#   descriptor which can be used by `poll()' and/or `select()'. If `no' and
-#   the target system has not got `epoll()' or `/dev/poll', the kernel-poll
-#   feature will be disabled.
-#erl_xcomp_kqueue=
-
-# * `erl_xcomp_linux_clock_gettime_correction' - `yes|no'. Defaults to `yes' on
-#   Linux; otherwise, `no'. If `yes', `clock_gettime(CLOCK_MONOTONIC, _)' on
-#   the target system must work. This variable is recommended to be set to
-#   `no' on Linux systems with kernel versions less than 2.6.
-#erl_xcomp_linux_clock_gettime_correction=
-
-# * `erl_xcomp_linux_nptl' - `yes|no'. Defaults to `yes' on Linux; otherwise,
-#   `no'. If `yes', the target system must have NPTL (Native POSIX Thread
-#   Library). Older Linux systems have LinuxThreads instead of NPTL (Linux
-#   kernel versions typically less than 2.6).
-#erl_xcomp_linux_nptl=
-
-# * `erl_xcomp_linux_usable_sigaltstack' - `yes|no'. Defaults to `yes' on Linux;
-#   otherwise, `no'. If `yes', `sigaltstack()' must be usable on the target
-#   system. `sigaltstack()' on Linux kernel versions less than 2.4 are
-#   broken.
-#erl_xcomp_linux_usable_sigaltstack=
-
-# * `erl_xcomp_linux_usable_sigusrx' - `yes|no'. Defaults to `yes'. If `yes',
-#   the `SIGUSR1' and `SIGUSR2' signals must be usable by the ERTS. Old
-#   LinuxThreads thread libraries (Linux kernel versions typically less than
-#   2.2) used these signals and made them unusable by the ERTS.
-#erl_xcomp_linux_usable_sigusrx=
-
-# * `erl_xcomp_poll' - `yes|no'. Defaults to `no' on Darwin/MacOSX; otherwise,
-#   `yes'. If `yes', the target system must have a working `poll()'
-#   implementation that also can handle devices. If `no', `select()' will be
-#   used instead of `poll()'.
-erl_xcomp_poll=no
-
-# * `erl_xcomp_putenv_copy' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have a `putenv()' implementation that stores a copy of the
-#   key/value pair.
-#erl_xcomp_putenv_copy=
-
-# * `erl_xcomp_reliable_fpe' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have reliable floating point exceptions.
-#erl_xcomp_reliable_fpe=
-# * `erl_xcomp_ose_ldflags_pass1` - Linker flags for the OSE module (pass 1)
-erl_xcomp_ose_ldflags_pass1="-r --no-omagic"
-
-# * `erl_xcomp_ose_ldflags_pass2` - Linker flags for the OSE module (pass 2)
-erl_xcomp_ose_ldflags_pass2="-n --emit-relocs -ecrt0_lm --no-omagic"
-
-# * `erl_xcomp_ose_OSEROOT` - OSE installation root directory
-erl_xcomp_ose_OSEROOT="${OSEROOT}"
-
-# * `erl_xcomp_ose_STRIP` - Strip utility shipped with the OSE distribution
-erl_xcomp_ose_STRIP="${GCCROOT}/bin/${GCCTARGET}-strip"
-
-# * `erl_xcomp_ose_LM_POST_LINK` - OSE postlink tool
-erl_xcomp_ose_LM_POST_LINK="${OSEROOT}/bin/${HOST}/lm_post_link"
-
-# * `erl_xcomp_ose_LM_SET_CONF` - Sets the configuration for an OSE load module
-erl_xcomp_ose_LM_SET_CONF="${OSEROOT}/bin/${HOST}/lm_set_conf"
-
-# * `erl_xcomp_ose_LM_ELF_SIZE` - OSE load module elf size tool
-erl_xcomp_ose_LM_ELF_SIZE="${OSEROOT}/bin/${HOST}/lm_elf_size"
-
-# * `erl_xcomp_ose_LM_LCF` - OSE load module linker configuration file
-erl_xcomp_ose_LM_LCF="${ERL_TOP}/erts/emulator/sys/ose/gcc_${GCCVERSION}_lm_ppc.lcf"
-
-# * `erl_xcomp_ose_BEAM_LM_CONF` - beam OSE load module configuration file
-erl_xcomp_ose_BEAM_LM_CONF="${ERL_TOP}/erts/emulator/sys/ose/beam.lmconf"
-
-# * `erl_xcomp_ose_RUN_ERL_LM_CONF` - run_erl_lm OSE load module configuration file
-erl_xcomp_ose_RUN_ERL_LM_CONF="${ERL_TOP}/erts/etc/ose/etc.lmconf"
-
-# * `erl_xcomp_ose_EPMD_LM_CONF` - epmd OSE load module configuration file
-erl_xcomp_ose_EPMD_LM_CONF="${ERL_TOP}/erts/etc/ose/etc.lmconf"
-
-# * `erl_xcomp_ose_CONFD` - OSE confd source file
-erl_xcomp_ose_CONFD="${OSEROOT}/src/ose_confd.c"
-
-# * `erl_xcomp_ose_CRT0_LM` - OSE crt0 lm source file
-erl_xcomp_ose_CRT0_LM="${OSEROOT}/src/crt0_lm.c"
-
-
-## -----------------------------------------------------------------------------
diff -Ndurp otp_src_18.3.4.5/xcomp/erl-xcomp-sfk-linux-ose5.conf otp_src_18.3.4.5-remove-OSE-port/xcomp/erl-xcomp-sfk-linux-ose5.conf
--- otp_src_18.3.4.5/xcomp/erl-xcomp-sfk-linux-ose5.conf	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/xcomp/erl-xcomp-sfk-linux-ose5.conf	1970-01-01 03:00:00.000000000 +0300
@@ -1,305 +0,0 @@
-## -*-shell-script-*-
-##
-## %CopyrightBegin%
-##
-## Copyright Ericsson AB 2009-2012. All Rights Reserved.
-##
-## Licensed under the Apache License, Version 2.0 (the "License");
-## you may not use this file except in compliance with the License.
-## You may obtain a copy of the License at
-##
-##     http://www.apache.org/licenses/LICENSE-2.0
-##
-## Unless required by applicable law or agreed to in writing, software
-## distributed under the License is distributed on an "AS IS" BASIS,
-## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-## See the License for the specific language governing permissions and
-## limitations under the License.
-##
-## %CopyrightEnd%
-##
-## File: erl-xcomp-sfk-linux-ose5.conf
-## Author: Petre Pircalabu
-##
-## -----------------------------------------------------------------------------
-## When cross compiling Erlang/OTP using `otp_build', copy this file and set
-## the variables needed below. Then pass the path to the copy of this file as
-## an argument to `otp_build' in the configure stage:
-##   `otp_build configure --xcomp-conf=<FILE>'
-## -----------------------------------------------------------------------------
-
-## Note that you cannot define arbitrary variables in a cross compilation
-## configuration file. Only the ones listed below will be guaranteed to be
-## visible throughout the whole execution of all `configure' scripts. Other
-## variables needs to be defined as arguments to `configure' or exported in
-## the environment.
-
-## -- Variables needed for an OSE5 build ---------------------------------------
-OSEROOT="/vobs/ose5/system"
-HOST="linux"
-GCCVERSION="4.6.3"
-GCCROOT="${OSEROOT}/gcc_linux_x86_${GCCVERSION}"
-GCCTARGET="i386-elf"
-
-## -- Variables for `otp_build' Only -------------------------------------------
-
-## Variables in this section are only used, when configuring Erlang/OTP for
-## cross compilation using `$ERL_TOP/otp_build configure'.
-
-## *NOTE*! These variables currently have *no* effect if you configure using
-## the `configure' script directly.
-
-# * `erl_xcomp_build' - The build system used. This value will be passed as
-#   `--build=$erl_xcomp_build' argument to the `configure' script. It does
-#   not have to be a full `CPU-VENDOR-OS' triplet, but can be. The full
-#   `CPU-VENDOR-OS' triplet will be created by
-#   `$ERL_TOP/erts/autoconf/config.sub $erl_xcomp_build'. If set to `guess',
-#   the build system will be guessed using
-#   `$ERL_TOP/erts/autoconf/config.guess'.
-erl_xcomp_build=guess
-
-# * `erl_xcomp_host' - Cross host/target system to build for. This value will
-#   be passed as `--host=$erl_xcomp_host' argument to the `configure' script.
-#   It does not have to be a full `CPU-VENDOR-OS' triplet, but can be. The
-#   full `CPU-VENDOR-OS' triplet will be created by
-#   `$ERL_TOP/erts/autoconf/config.sub $erl_xcomp_host'.
-erl_xcomp_host="$GCCTARGET-ose"
-
-# * `erl_xcomp_configure_flags' - Extra configure flags to pass to the
-#   `configure' script.
-erl_xcomp_configure_flags="--disable-threads --disable-smp-support --disable-kernel-poll --disable-hipe --without-termcap --without-javac --disable-dynamic-ssl-lib --disable-shared-zlib --without-ssl --enable-static-nifs --enable-static-nifs=$ERL_TOP/lib/asn1/priv/lib/powerpc-unknown-ose/asn1rt_nif.a"
-
-## -- Cross Compiler and Other Tools -------------------------------------------
-
-## If the cross compilation tools are prefixed by `<HOST>-' you probably do
-## not need to set these variables (where `<HOST>' is what has been passed as
-## `--host=<HOST>' argument to `configure').
-
-## All variables in this section can also be used when native compiling.
-
-# * `CC' - C compiler.
-CC="$GCCROOT/bin/$GCCTARGET-gcc"
-
-# * `CFLAGS' - C compiler flags.
-CFLAGS="-g -fno-strict-aliasing -fno-builtin -fshort-wchar -Wall -Wno-unknown-pragmas -I$GCCROOT/include/c++/$GCCVERSION -I$OSEROOT/include -I$OSEROOT/include/ose_spi -I$OSEROOT/include/gcc -MD -MP -D__OSE__ -DLITTLE_ENDIAN -DCF_CONF_SIZE=0x800"
-
-# * `STATIC_CFLAGS' - Static C compiler flags.
-#STATIC_CFLAGS=
-
-# * `CFLAG_RUNTIME_LIBRARY_PATH' - This flag should set runtime library
-#   search path for the shared libraries. Note that this actually is a
-#   linker flag, but it needs to be passed via the compiler.
-#CFLAG_RUNTIME_LIBRARY_PATH=
-
-# * `CPP' - C pre-processor.
-#CPP=
-
-# * `CPPFLAGS' - C pre-processor flags.
-CPPFLAGS="-g -fno-strict-aliasing -fno-builtin -fshort-wchar -Wall -Wno-unknown-pragmas -I$GCCROOT/include/c++/$GCCVERSION -I$OSEROOT/include -I$OSEROOT/include/ose_spi -I$OSEROOT/include/gcc -MD -MP -D__OSE__ -DLITTLE_ENDIAN -DCF_CONF_SIZE=0x800"
-
-# * `CXX' - C++ compiler.
-#CXX=
-
-# * `CXXFLAGS' - C++ compiler flags.
-CXXFLAGS="-g -fno-strict-aliasing -ansi -I$GCCROOT/include/c++/$GCCVERSION -I$OSEROOT/include -I$OSEROOT/include/gcc "
-
-# * `LD' - Linker.
-LD="$GCCROOT/bin/$GCCTARGET-ld"
-
-# * `LDFLAGS' - Linker flags.
-LDFLAGS="-Wl,-ecrt0_lm -Wl,-T,$ERL_TOP/erts/emulator/sys/ose/gcc_lm_x86_$GCCVERSION.lcf"
-
-# * `LIBS' - Libraries.
-LIBS="$OSEROOT/lib/x86/libcrt.a $OSEROOT/lib/x86/libm.a $GCCROOT/lib/gcc/$GCCTARGET/$GCCVERSION/libgcc.a"
-
-## -- *D*ynamic *E*rlang *D*river Linking --
-
-## *NOTE*! Either set all or none of the `DED_LD*' variables.
-
-# * `DED_LD' - Linker for Dynamically loaded Erlang Drivers.
-#DED_LD=
-
-# * `DED_LDFLAGS' - Linker flags to use with `DED_LD'.
-#DED_LDFLAGS=
-
-# * `DED_LD_FLAG_RUNTIME_LIBRARY_PATH' - This flag should set runtime library
-#   search path for shared libraries when linking with `DED_LD'.
-#DED_LD_FLAG_RUNTIME_LIBRARY_PATH=
-
-## -- Large File Support --
-
-## *NOTE*! Either set all or none of the `LFS_*' variables.
-
-# * `LFS_CFLAGS' - Large file support C compiler flags.
-#LFS_CFLAGS=
-
-# * `LFS_LDFLAGS' - Large file support linker flags.
-#LFS_LDFLAGS=
-
-# * `LFS_LIBS' - Large file support libraries.
-#LFS_LIBS=
-
-## -- Other Tools --
-
-# * `RANLIB' - `ranlib' archive index tool.
-RANLIB="$GCCROOT/bin/$GCCTARGET-ranlib"
-
-# * `AR' - `ar' archiving tool.
-AR="$GCCROOT/bin/$GCCTARGET-ar"
-
-# * `STRIP' - `strip
-STRIP="$GCCROOT/bin/$GCCTARGET-strip"
-
-# * `GETCONF' - `getconf' system configuration inspection tool. `getconf' is
-#   currently used for finding out large file support flags to use, and
-#   on Linux systems for finding out if we have an NPTL thread library or
-#   not.
-#GETCONF=
-
-## -- Cross System Root Locations ----------------------------------------------
-
-# * `erl_xcomp_sysroot' - The absolute path to the system root of the cross
-#   compilation environment. Currently, the `crypto', `odbc', `ssh' and
-#   `ssl' applications need the system root. These applications will be
-#   skipped if the system root has not been set. The system root might be
-#   needed for other things too. If this is the case and the system root
-#   has not been set, `configure' will fail and request you to set it.
-erl_xcomp_sysroot="$OSEROOT"
-
-# * `erl_xcomp_isysroot' - The absolute path to the system root for includes
-#   of the cross compilation environment. If not set, this value defaults
-#   to `$erl_xcomp_sysroot', i.e., only set this value if the include system
-#   root path is not the same as the system root path.
-erl_xcomp_isysroot="$OSEROOT/include"
-
-## -- Optional Feature, and Bug Tests ------------------------------------------
-
-## These tests cannot (always) be done automatically when cross compiling. You
-## usually do not need to set these variables. Only set these if you really
-## know what you are doing.
-
-## Note that some of these values will override results of tests performed
-## by `configure', and some will not be used until `configure' is sure that
-## it cannot figure the result out.
-
-## The `configure' script will issue a warning when a default value is used.
-## When a variable has been set, no warning will be issued.
-
-# * `erl_xcomp_after_morecore_hook' - `yes|no'. Defaults to `no'. If `yes',
-#   the target system must have a working `__after_morecore_hook' that can be
-#   used for tracking used `malloc()' implementations core memory usage.
-#   This is currently only used by unsupported features.
-#erl_xcomp_after_morecore_hook=
-
-# * `erl_xcomp_bigendian' - `yes|no'. No default. If `yes', the target system
-#   must be big endian. If `no', little endian. This can often be
-#   automatically detected, but not always. If not automatically detected,
-#   `configure' will fail unless this variable is set. Since no default
-#   value is used, `configure' will try to figure this out automatically.
-#erl_xcomp_bigendian=
-
-# * `erl_xcomp_double_middle` - `yes|no`. No default. If `yes`, the
-#   target system must have doubles in "middle-endian" format. If
-#   `no`, it has "regular" endianness. This can often be automatically
-#   detected, but not always. If not automatically detected,
-#   `configure` will fail unless this variable is set. Since no
-#   default value is used, `configure` will try to figure this out
-#   automatically.
-#erl_xcomp_double_middle_endian
-
-# * `erl_xcomp_clock_gettime_cpu_time' - `yes|no'. Defaults to `no'. If `yes',
-#   the target system must have a working `clock_gettime()' implementation
-#   that can be used for retrieving process CPU time.
-#erl_xcomp_clock_gettime_cpu_time=
-
-# * `erl_xcomp_getaddrinfo' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have a working `getaddrinfo()' implementation that can
-#   handle both IPv4 and IPv6.
-#erl_xcomp_getaddrinfo=
-
-# * `erl_xcomp_gethrvtime_procfs_ioctl' - `yes|no'. Defaults to `no'. If `yes',
-#   the target system must have a working `gethrvtime()' implementation and
-#   is used with procfs `ioctl()'.
-#erl_xcomp_gethrvtime_procfs_ioctl=
-
-# * `erl_xcomp_dlsym_brk_wrappers' - `yes|no'. Defaults to `no'. If `yes', the
-#   target system must have a working `dlsym(RTLD_NEXT, <S>)' implementation
-#   that can be used on `brk' and `sbrk' symbols used by the `malloc()'
-#   implementation in use, and by this track the `malloc()' implementations
-#   core memory usage. This is currently only used by unsupported features.
-#erl_xcomp_dlsym_brk_wrappers=
-
-# * `erl_xcomp_kqueue' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have a working `kqueue()' implementation that returns a file
-#   descriptor which can be used by `poll()' and/or `select()'. If `no' and
-#   the target system has not got `epoll()' or `/dev/poll', the kernel-poll
-#   feature will be disabled.
-#erl_xcomp_kqueue=
-
-# * `erl_xcomp_linux_clock_gettime_correction' - `yes|no'. Defaults to `yes' on
-#   Linux; otherwise, `no'. If `yes', `clock_gettime(CLOCK_MONOTONIC, _)' on
-#   the target system must work. This variable is recommended to be set to
-#   `no' on Linux systems with kernel versions less than 2.6.
-#erl_xcomp_linux_clock_gettime_correction=
-
-# * `erl_xcomp_linux_nptl' - `yes|no'. Defaults to `yes' on Linux; otherwise,
-#   `no'. If `yes', the target system must have NPTL (Native POSIX Thread
-#   Library). Older Linux systems have LinuxThreads instead of NPTL (Linux
-#   kernel versions typically less than 2.6).
-#erl_xcomp_linux_nptl=
-
-# * `erl_xcomp_linux_usable_sigaltstack' - `yes|no'. Defaults to `yes' on Linux;
-#   otherwise, `no'. If `yes', `sigaltstack()' must be usable on the target
-#   system. `sigaltstack()' on Linux kernel versions less than 2.4 are
-#   broken.
-#erl_xcomp_linux_usable_sigaltstack=
-
-# * `erl_xcomp_linux_usable_sigusrx' - `yes|no'. Defaults to `yes'. If `yes',
-#   the `SIGUSR1' and `SIGUSR2' signals must be usable by the ERTS. Old
-#   LinuxThreads thread libraries (Linux kernel versions typically less than
-#   2.2) used these signals and made them unusable by the ERTS.
-#erl_xcomp_linux_usable_sigusrx=
-
-# * `erl_xcomp_poll' - `yes|no'. Defaults to `no' on Darwin/MacOSX; otherwise,
-#   `yes'. If `yes', the target system must have a working `poll()'
-#   implementation that also can handle devices. If `no', `select()' will be
-#   used instead of `poll()'.
-erl_xcomp_poll=no
-
-# * `erl_xcomp_putenv_copy' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have a `putenv()' implementation that stores a copy of the
-#   key/value pair.
-#erl_xcomp_putenv_copy=
-
-# * `erl_xcomp_reliable_fpe' - `yes|no'. Defaults to `no'. If `yes', the target
-#   system must have reliable floating point exceptions.
-#erl_xcomp_reliable_fpe=
-
-# * `erl_xcomp_ose_ldflags_pass1` - Linker flags for the OSE module (pass 1)
-erl_xcomp_ose_ldflags_pass1="-r --no-omagic"
-
-# * `erl_xcomp_ose_ldflags_pass2` - Linker flags for the OSE module (pass 2)
-erl_xcomp_ose_ldflags_pass2="-n --emit-relocs -ecrt0_lm --no-omagic"
-
-# * `erl_xcomp_ose_OSEROOT` - OSE installation root directory
-erl_xcomp_ose_OSEROOT="$OSEROOT"
-
-# * `erl_xcomp_ose_STRIP` - Strip utility shipped with the OSE distribution
-erl_xcomp_ose_STRIP="$GCCROOT/bin/$GCCTARGET-strip"
-
-# * `erl_xcomp_ose_LM_POST_LINK` - OSE postlink tool
-erl_xcomp_ose_LM_POST_LINK="$OSEROOT/bin/$HOST/lm_post_link"
-
-# * `erl_xcomp_ose_LM_SET_CONF` - OSE load module configuration tool
-erl_xcomp_ose_LM_SET_CONF="$OSEROOT/bin/$HOST/lm_set_conf"
-
-# * `erl_xcomp_ose_LM_GET_CONF` - OSE load module elf size tool
-erl_xcomp_ose_LM_ELF_SIZE="$OSEROOT/bin/$HOST/lm_elf_size"
-
-# * `erl_xcomp_ose_LM_LCF` - OSE load module linker configuration file
-erl_xcomp_ose_LM_LCF="${ERL_TOP}/erts/emulator/sys/ose/gcc_lm_x86_$GCCVERSION.lcf"
-
-# * `erl_xcomp_ose_LM_CONF` - OSE load module default configuration file
-erl_xcomp_ose_LM_CONF="${ERL_TOP}/erts/emulator/sys/ose/default.lmconf"
-
-## -----------------------------------------------------------------------------
diff -Ndurp otp_src_18.3.4.5/xcomp/erl-xcomp-vars.sh otp_src_18.3.4.5-remove-OSE-port/xcomp/erl-xcomp-vars.sh
--- otp_src_18.3.4.5/xcomp/erl-xcomp-vars.sh	2017-02-01 19:32:59.000000000 +0200
+++ otp_src_18.3.4.5-remove-OSE-port/xcomp/erl-xcomp-vars.sh	2017-02-03 21:52:59.175950800 +0200
@@ -27,4 +27,4 @@
 #    and precious variables in $ERL_TOP/erts/aclocal.m4.
 #
 
-erl_xcomp_vars="erl_xcomp_sysroot erl_xcomp_isysroot erl_xcomp_bigendian erl_xcomp_double_middle_endian erl_xcomp_linux_clock_gettime_correction erl_xcomp_linux_nptl erl_xcomp_linux_usable_sigusrx erl_xcomp_linux_usable_sigaltstack erl_xcomp_poll erl_xcomp_kqueue erl_xcomp_putenv_copy erl_xcomp_reliable_fpe erl_xcomp_getaddrinfo erl_xcomp_gethrvtime_procfs_ioctl erl_xcomp_clock_gettime_cpu_time erl_xcomp_after_morecore_hook erl_xcomp_dlsym_brk_wrappers erl_xcomp_posix_memalign erl_xcomp_ose_ldflags_pass1 erl_xcomp_ose_ldflags_pass2 erl_xcomp_ose_OSEROOT erl_xcomp_ose_STRIP erl_xcomp_ose_LM_POST_LINK erl_xcomp_ose_LM_SET_CONF erl_xcomp_ose_LM_GET_CONF erl_xcomp_ose_LM_ELF_SIZE erl_xcomp_ose_LM_LCF erl_xcomp_ose_BEAM_LM_CONF erl_xcomp_ose_EPMD_LM_CONF erl_xcomp_ose_RUN_ERL_LM_CONF erl_xcomp_ose_CONFD erl_xcomp_ose_CRT0_LM"
+erl_xcomp_vars="erl_xcomp_sysroot erl_xcomp_isysroot erl_xcomp_bigendian erl_xcomp_double_middle_endian erl_xcomp_linux_clock_gettime_correction erl_xcomp_linux_nptl erl_xcomp_linux_usable_sigusrx erl_xcomp_linux_usable_sigaltstack erl_xcomp_poll erl_xcomp_kqueue erl_xcomp_putenv_copy erl_xcomp_reliable_fpe erl_xcomp_getaddrinfo erl_xcomp_gethrvtime_procfs_ioctl erl_xcomp_clock_gettime_cpu_time erl_xcomp_after_morecore_hook erl_xcomp_dlsym_brk_wrappers erl_xcomp_posix_memalign"
openSUSE Build Service is sponsored by