summaryrefslogtreecommitdiffstats
path: root/stdlib/header.c
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1998-06-01 14:53:28 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1998-06-01 14:53:28 +0000
commit4cdadc0c6d7982aeafe8b55b0e7773a35c2d9d7d (patch)
treea919b1a77cff616067ff8b3429b77ce61745f81d /stdlib/header.c
parent55ef09aba4ea9c7f7e444aa0dcbc8c4b807c591a (diff)
Revu la gestion du camlheader pour que l'install par defaut marche meme sans faire un tour de bootstrap
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1974 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/header.c')
-rw-r--r--stdlib/header.c19
1 files changed, 11 insertions, 8 deletions
diff --git a/stdlib/header.c b/stdlib/header.c
index 6166aa965..8daa22fdc 100644
--- a/stdlib/header.c
+++ b/stdlib/header.c
@@ -24,6 +24,8 @@
#include <sys/stat.h>
#include "../byterun/exec.h"
+char * default_runtime_path = RUNTIME_NAME;
+
#define MAXPATHLEN 1024
#ifndef S_ISREG
@@ -69,27 +71,29 @@ static unsigned long read_size(char * ptr)
((unsigned long) p[2] << 8) + p[3];
}
-static int read_runtime_path(int fd, char *runtime_path)
+static char * read_runtime_path(int fd)
{
char buffer[TRAILER_SIZE];
+ static char runtime_path[MAXPATHLEN];
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;
+ if (read(fd, buffer, TRAILER_SIZE) < TRAILER_SIZE) return NULL;
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;
+ if (path_size > MAXPATHLEN) return NULL;
+ if (path_size == 0) return default_runtime_path;
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;
+ if (read(fd, runtime_path, path_size) != path_size) return NULL;
runtime_path[path_size - 1] = 0;
- return 0;
+ return runtime_path;
}
static void errwrite(char * msg)
@@ -99,13 +103,12 @@ static void errwrite(char * msg)
int main(int argc, char ** argv)
{
- char * truename;
+ char * truename, * runtime_path;
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) {
+ if (fd == -1 || (runtime_path = read_runtime_path(fd)) == NULL) {
errwrite(truename);
errwrite(" not found or is not a bytecode executable file\n");
return 2;