summaryrefslogtreecommitdiffstats
path: root/stdlib/header.c
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/header.c')
-rw-r--r--stdlib/header.c106
1 files changed, 101 insertions, 5 deletions
diff --git a/stdlib/header.c b/stdlib/header.c
index 6e86ab551..6166aa965 100644
--- a/stdlib/header.c
+++ b/stdlib/header.c
@@ -4,19 +4,115 @@
/* */
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
-/* Copyright 1996 Institut National de Recherche en Informatique et */
+/* Copyright 1998 Institut National de Recherche en Informatique et */
/* Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
/* $Id$ */
-char runtime_name [] = RUNTIME_NAME;
-char errmsg [] = "Cannot exec ocamlrun.\n";
+/* The launcher for bytecode executables (if #! is not working) */
+
+#include <stdlib.h>
+#include <string.h>
+#include "../config/s.h"
+#ifdef HAS_UNISTD
+#include <unistd.h>
+#endif
+#include <fcntl.h>
+#include <sys/types.h>
+#include <sys/stat.h>
+#include "../byterun/exec.h"
+
+#define MAXPATHLEN 1024
+
+#ifndef S_ISREG
+#define S_ISREG(mode) (((mode) & S_IFMT) == S_IFREG)
+#endif
+
+#ifndef SEEK_END
+#define SEEK_END 2
+#endif
+
+static char * searchpath(char * name)
+{
+ static char fullname[MAXPATHLEN + 1];
+ char * path;
+ char * p;
+ char * q;
+ struct stat st;
+
+ for (p = name; *p != 0; p++) {
+ if (*p == '/') return name;
+ }
+ path = getenv("PATH");
+ if (path == NULL) return name;
+ while(1) {
+ for (p = fullname; *path != 0 && *path != ':'; p++, path++)
+ if (p < fullname + MAXPATHLEN) *p = *path;
+ if (p != fullname && p < fullname + MAXPATHLEN)
+ *p++ = '/';
+ for (q = name; *q != 0; p++, q++)
+ if (p < fullname + MAXPATHLEN) *p = *q;
+ *p = 0;
+ if (stat(fullname, &st) == 0 && S_ISREG(st.st_mode)) break;
+ if (*path == 0) return name;
+ path++;
+ }
+ return fullname;
+}
+
+static unsigned long read_size(char * ptr)
+{
+ unsigned char * p = (unsigned char *) ptr;
+ return ((unsigned long) p[0] << 24) + ((unsigned long) p[1] << 16) +
+ ((unsigned long) p[2] << 8) + p[3];
+}
+
+static int read_runtime_path(int fd, char *runtime_path)
+{
+ char buffer[TRAILER_SIZE];
+ unsigned path_size, code_size, prim_size, data_size;
+ unsigned symbol_size, debug_size, size;
+
+ lseek(fd, (long) -TRAILER_SIZE, SEEK_END);
+ if (read(fd, buffer, TRAILER_SIZE) < TRAILER_SIZE) return -1;
+ path_size = read_size(buffer);
+ code_size = read_size(buffer + 4);
+ prim_size = read_size(buffer + 8);
+ data_size = read_size(buffer + 12);
+ symbol_size = read_size(buffer + 16);
+ debug_size = read_size(buffer + 20);
+ if (path_size > MAXPATHLEN) return -1;
+ size = path_size + code_size + prim_size +
+ data_size + symbol_size + debug_size + TRAILER_SIZE;
+ lseek(fd, -size, SEEK_END);
+ if (read(fd, runtime_path, path_size) != path_size) return -1;
+ runtime_path[path_size - 1] = 0;
+ return 0;
+}
+
+static void errwrite(char * msg)
+{
+ write(2, msg, strlen(msg));
+}
int main(int argc, char ** argv)
{
- execv(runtime_name, argv);
- write(2, errmsg, sizeof(errmsg)-1);
+ char * truename;
+ int fd;
+ char runtime_path[MAXPATHLEN];
+
+ truename = searchpath(argv[0]);
+ fd = open(truename, O_RDONLY);
+ if (fd == -1 || read_runtime_path(fd, runtime_path) == -1) {
+ errwrite(truename);
+ errwrite(" not found or is not a bytecode executable file\n");
+ return 2;
+ }
+ execv(runtime_path, argv);
+ errwrite("Cannot exec ");
+ errwrite(runtime_path);
+ errwrite("\n");
return 2;
}