1995-08-09 08:06:35 -07:00
|
|
|
/***********************************************************************/
|
|
|
|
/* */
|
1996-04-30 07:53:58 -07:00
|
|
|
/* Objective Caml */
|
1995-08-09 08:06:35 -07:00
|
|
|
/* */
|
|
|
|
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
|
|
|
|
/* */
|
1996-04-30 07:53:58 -07:00
|
|
|
/* Copyright 1996 Institut National de Recherche en Informatique et */
|
1999-11-17 10:59:06 -08:00
|
|
|
/* en Automatique. All rights reserved. This file is distributed */
|
2001-12-07 05:41:02 -08:00
|
|
|
/* under the terms of the GNU Library General Public License, with */
|
|
|
|
/* the special exception on linking described in file ../LICENSE. */
|
1995-08-09 08:06:35 -07:00
|
|
|
/* */
|
|
|
|
/***********************************************************************/
|
|
|
|
|
|
|
|
/* $Id$ */
|
|
|
|
|
1996-11-29 10:36:42 -08:00
|
|
|
/* Handling of blocks of bytecode (endianness switch, threading). */
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
#include "config.h"
|
2002-03-06 05:32:30 -08:00
|
|
|
|
|
|
|
#ifdef HAS_UNISTD
|
|
|
|
#include <unistd.h>
|
|
|
|
#endif
|
|
|
|
|
1996-11-29 10:36:42 -08:00
|
|
|
#include "debugger.h"
|
1995-05-04 03:15:53 -07:00
|
|
|
#include "fix_code.h"
|
1996-12-11 11:57:35 -08:00
|
|
|
#include "instruct.h"
|
1997-07-02 11:16:15 -07:00
|
|
|
#include "md5.h"
|
1996-11-29 10:36:42 -08:00
|
|
|
#include "memory.h"
|
1995-05-04 03:15:53 -07:00
|
|
|
#include "misc.h"
|
|
|
|
#include "mlvalues.h"
|
|
|
|
#include "reverse.h"
|
1996-11-29 10:36:42 -08:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
code_t caml_start_code;
|
|
|
|
asize_t caml_code_size;
|
|
|
|
unsigned char * caml_saved_code;
|
|
|
|
unsigned char caml_code_md5[16];
|
1996-11-29 10:36:42 -08:00
|
|
|
|
|
|
|
/* Read the main bytecode block from a file */
|
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
void caml_load_code(int fd, asize_t len)
|
1996-11-29 10:36:42 -08:00
|
|
|
{
|
|
|
|
int i;
|
1997-07-02 11:16:15 -07:00
|
|
|
struct MD5Context ctx;
|
1996-11-29 10:36:42 -08:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_code_size = len;
|
|
|
|
caml_start_code = (code_t) caml_stat_alloc(caml_code_size);
|
|
|
|
if (read(fd, (char *) caml_start_code, caml_code_size) != caml_code_size)
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_fatal_error("Fatal error: truncated bytecode file.\n");
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_MD5Init(&ctx);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_MD5Update(&ctx, (unsigned char *) caml_start_code, caml_code_size);
|
|
|
|
caml_MD5Final(caml_code_md5, &ctx);
|
1996-12-11 11:57:35 -08:00
|
|
|
#ifdef ARCH_BIG_ENDIAN
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_fixup_endianness(caml_start_code, caml_code_size);
|
1996-11-29 10:36:42 -08:00
|
|
|
#endif
|
2004-01-01 08:42:43 -08:00
|
|
|
if (caml_debugger_in_use) {
|
1996-11-29 10:36:42 -08:00
|
|
|
len /= sizeof(opcode_t);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_saved_code = (unsigned char *) caml_stat_alloc(len);
|
|
|
|
for (i = 0; i < len; i++) caml_saved_code[i] = caml_start_code[i];
|
1996-11-29 10:36:42 -08:00
|
|
|
}
|
|
|
|
#ifdef THREADED_CODE
|
2004-01-01 08:42:43 -08:00
|
|
|
/* Better to thread now than at the beginning of [caml_interprete],
|
1996-11-29 10:36:42 -08:00
|
|
|
since the debugger interface needs to perform SET_EVENT requests
|
|
|
|
on the code. */
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_thread_code(caml_start_code, caml_code_size);
|
1996-11-29 10:36:42 -08:00
|
|
|
#endif
|
|
|
|
}
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
/* This code is needed only if the processor is big endian */
|
|
|
|
|
1996-07-01 05:43:28 -07:00
|
|
|
#ifdef ARCH_BIG_ENDIAN
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
void caml_fixup_endianness(code_t code, asize_t len)
|
1995-05-04 03:15:53 -07:00
|
|
|
{
|
|
|
|
code_t p;
|
|
|
|
len /= sizeof(opcode_t);
|
|
|
|
for (p = code; p < code + len; p++) {
|
2000-02-10 06:04:59 -08:00
|
|
|
Reverse_32(p, p);
|
1995-05-04 03:15:53 -07:00
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
#endif
|
|
|
|
|
|
|
|
/* This code is needed only if we're using threaded code */
|
|
|
|
|
|
|
|
#ifdef THREADED_CODE
|
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
char ** caml_instr_table;
|
|
|
|
char * caml_instr_base;
|
1996-05-28 05:41:37 -07:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
void caml_thread_code (code_t code, asize_t len)
|
1996-11-02 10:00:46 -08:00
|
|
|
{
|
|
|
|
code_t p;
|
|
|
|
int l [STOP + 1];
|
|
|
|
int i;
|
|
|
|
|
1996-11-08 06:46:01 -08:00
|
|
|
for (i = 0; i <= STOP; i++) {
|
1996-11-02 10:00:46 -08:00
|
|
|
l [i] = 0;
|
|
|
|
}
|
1996-11-08 06:46:01 -08:00
|
|
|
/* Instructions with one operand */
|
1996-11-02 10:00:46 -08:00
|
|
|
l[PUSHACC] = l[ACC] = l[POP] = l[ASSIGN] =
|
|
|
|
l[PUSHENVACC] = l[ENVACC] = l[PUSH_RETADDR] = l[APPLY] =
|
|
|
|
l[APPTERM1] = l[APPTERM2] = l[APPTERM3] = l[RETURN] =
|
|
|
|
l[GRAB] = l[PUSHGETGLOBAL] = l[GETGLOBAL] = l[SETGLOBAL] =
|
|
|
|
l[PUSHATOM] = l[ATOM] = l[MAKEBLOCK1] = l[MAKEBLOCK2] =
|
1998-04-06 02:15:55 -07:00
|
|
|
l[MAKEBLOCK3] = l[MAKEFLOATBLOCK] = l[GETFIELD] =
|
|
|
|
l[GETFLOATFIELD] = l[SETFIELD] = l[SETFLOATFIELD] =
|
1996-11-02 10:00:46 -08:00
|
|
|
l[BRANCH] = l[BRANCHIF] = l[BRANCHIFNOT] = l[PUSHTRAP] =
|
|
|
|
l[C_CALL1] = l[C_CALL2] = l[C_CALL3] = l[C_CALL4] = l[C_CALL5] =
|
1998-04-06 02:15:55 -07:00
|
|
|
l[CONSTINT] = l[PUSHCONSTINT] = l[OFFSETINT] =
|
|
|
|
l[OFFSETREF] = l[OFFSETCLOSURE] = l[PUSHOFFSETCLOSURE] = 1;
|
1996-11-02 10:00:46 -08:00
|
|
|
|
1996-11-08 06:46:01 -08:00
|
|
|
/* Instructions with two operands */
|
1998-04-06 02:15:55 -07:00
|
|
|
l[APPTERM] = l[CLOSURE] = l[PUSHGETGLOBALFIELD] =
|
2000-10-02 07:18:05 -07:00
|
|
|
l[GETGLOBALFIELD] = l[MAKEBLOCK] = l[C_CALLN] =
|
|
|
|
l[BEQ] = l[BNEQ] = l[BLTINT] = l[BLEINT] = l[BGTINT] = l[BGEINT] =
|
|
|
|
l[BULTINT] = l[BUGEINT] = 2;
|
1996-11-02 10:00:46 -08:00
|
|
|
len /= sizeof(opcode_t);
|
|
|
|
for (p = code; p < code + len; /*nothing*/) {
|
|
|
|
opcode_t instr = *p;
|
1996-11-08 06:46:01 -08:00
|
|
|
if (instr < 0 || instr > STOP){
|
2003-12-29 14:15:02 -08:00
|
|
|
/* FIXME -- should Assert(false) ?
|
|
|
|
caml_fatal_error_arg ("Fatal error in fix_code: bad opcode (%lx)\n",
|
|
|
|
(char *)(long)instr);
|
2001-02-19 12:27:52 -08:00
|
|
|
*/
|
|
|
|
instr = STOP;
|
1996-11-02 10:00:46 -08:00
|
|
|
}
|
2004-01-02 11:23:29 -08:00
|
|
|
*p++ = (opcode_t)(caml_instr_table[instr] - caml_instr_base);
|
1996-11-08 06:46:01 -08:00
|
|
|
if (instr == SWITCH) {
|
|
|
|
uint32 sizes = *p++;
|
|
|
|
uint32 const_size = sizes & 0xFFFF;
|
|
|
|
uint32 block_size = sizes >> 16;
|
|
|
|
p += const_size + block_size;
|
1998-04-06 02:15:55 -07:00
|
|
|
} else if (instr == CLOSUREREC) {
|
|
|
|
uint32 nfuncs = *p++;
|
|
|
|
p++; /* skip nvars */
|
|
|
|
p += nfuncs;
|
1996-11-08 06:46:01 -08:00
|
|
|
} else {
|
|
|
|
p += l[instr];
|
1995-05-04 03:15:53 -07:00
|
|
|
}
|
|
|
|
}
|
1996-05-28 05:41:37 -07:00
|
|
|
Assert(p == code + len);
|
1995-05-04 03:15:53 -07:00
|
|
|
}
|
|
|
|
|
1996-11-29 10:36:42 -08:00
|
|
|
#endif /* THREADED_CODE */
|
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
void caml_set_instruction(code_t pos, opcode_t instr)
|
1996-11-29 10:36:42 -08:00
|
|
|
{
|
|
|
|
#ifdef THREADED_CODE
|
2004-01-02 11:23:29 -08:00
|
|
|
*pos = (opcode_t)(caml_instr_table[instr] - caml_instr_base);
|
1996-11-29 10:36:42 -08:00
|
|
|
#else
|
|
|
|
*pos = instr;
|
|
|
|
#endif
|
|
|
|
}
|
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
int caml_is_instruction(opcode_t instr1, opcode_t instr2)
|
2001-02-19 04:29:00 -08:00
|
|
|
{
|
|
|
|
#ifdef THREADED_CODE
|
2004-01-02 11:23:29 -08:00
|
|
|
return instr1 == (opcode_t)(caml_instr_table[instr2] - caml_instr_base);
|
2001-02-19 04:29:00 -08:00
|
|
|
#else
|
|
|
|
return instr1 == instr2;
|
|
|
|
#endif
|
|
|
|
}
|