1996-12-03 05:40:28 -08:00
|
|
|
/***********************************************************************/
|
|
|
|
/* */
|
|
|
|
/* Objective Caml */
|
|
|
|
/* */
|
|
|
|
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
|
|
|
|
/* */
|
|
|
|
/* 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. */
|
1996-12-03 05:40:28 -08:00
|
|
|
/* */
|
|
|
|
/***********************************************************************/
|
|
|
|
|
|
|
|
/* $Id$ */
|
|
|
|
|
2010-04-20 08:47:15 -07:00
|
|
|
/* Interface with the byte-code debugger */
|
1996-12-03 05:40:28 -08:00
|
|
|
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
#include <io.h>
|
|
|
|
#endif /* _WIN32 */
|
|
|
|
|
1996-12-11 08:29:28 -08:00
|
|
|
#include <string.h>
|
|
|
|
|
1996-12-03 05:40:28 -08:00
|
|
|
#include "config.h"
|
|
|
|
#include "debugger.h"
|
|
|
|
#include "misc.h"
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
int caml_debugger_in_use = 0;
|
2005-09-22 07:21:50 -07:00
|
|
|
uintnat caml_event_count;
|
2010-04-20 08:47:15 -07:00
|
|
|
int caml_debugger_fork_mode = 1; /* parent by default */
|
1996-12-03 05:40:28 -08:00
|
|
|
|
2010-04-20 08:47:15 -07:00
|
|
|
#if !defined(HAS_SOCKETS) || defined(NATIVE_CODE)
|
1996-12-03 05:40:28 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_debugger_init(void)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_debugger(enum event_kind event)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
|
|
|
}
|
|
|
|
|
2010-04-20 08:47:15 -07:00
|
|
|
void caml_debugger_cleanup_fork(void)
|
|
|
|
{
|
|
|
|
}
|
|
|
|
|
1996-12-03 05:40:28 -08:00
|
|
|
#else
|
|
|
|
|
|
|
|
#ifdef HAS_UNISTD
|
|
|
|
#include <unistd.h>
|
|
|
|
#endif
|
2007-10-08 05:29:22 -07:00
|
|
|
#include <errno.h>
|
1996-12-03 05:40:28 -08:00
|
|
|
#include <sys/types.h>
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifndef _WIN32
|
1996-12-03 05:40:28 -08:00
|
|
|
#include <sys/wait.h>
|
|
|
|
#include <sys/socket.h>
|
|
|
|
#include <sys/un.h>
|
|
|
|
#include <netinet/in.h>
|
|
|
|
#include <arpa/inet.h>
|
|
|
|
#include <netdb.h>
|
2008-07-29 01:31:41 -07:00
|
|
|
#else
|
|
|
|
#define ATOM ATOM_WS
|
|
|
|
#include <winsock.h>
|
|
|
|
#undef ATOM
|
|
|
|
#include <process.h>
|
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
|
2010-04-20 08:47:15 -07:00
|
|
|
#include "fail.h"
|
|
|
|
#include "fix_code.h"
|
|
|
|
#include "instruct.h"
|
|
|
|
#include "intext.h"
|
|
|
|
#include "io.h"
|
|
|
|
#include "mlvalues.h"
|
|
|
|
#include "stacks.h"
|
|
|
|
#include "sys.h"
|
|
|
|
|
1996-12-03 05:40:28 -08:00
|
|
|
static int sock_domain; /* Socket domain for the debugger */
|
|
|
|
static union { /* Socket address for the debugger */
|
|
|
|
struct sockaddr s_gen;
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifndef _WIN32
|
1996-12-03 05:40:28 -08:00
|
|
|
struct sockaddr_un s_unix;
|
2010-01-22 04:48:24 -08:00
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
struct sockaddr_in s_inet;
|
|
|
|
} sock_addr;
|
|
|
|
static int sock_addr_len; /* Length of sock_addr */
|
|
|
|
|
|
|
|
static int dbg_socket = -1; /* The socket connected to the debugger */
|
|
|
|
static struct channel * dbg_in; /* Input channel on the socket */
|
|
|
|
static struct channel * dbg_out;/* Output channel on the socket */
|
|
|
|
|
2007-10-08 05:29:22 -07:00
|
|
|
static char *dbg_addr = "(none)";
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void open_connection(void)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
/* Set socket to synchronous mode so that file descriptor-oriented
|
|
|
|
functions (read()/write() etc.) can be used */
|
|
|
|
|
|
|
|
int oldvalue, oldvaluelen, newvalue, retcode;
|
|
|
|
oldvaluelen = sizeof(oldvalue);
|
|
|
|
retcode = getsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
|
|
|
|
(char *) &oldvalue, &oldvaluelen);
|
|
|
|
if (retcode == 0) {
|
|
|
|
newvalue = SO_SYNCHRONOUS_NONALERT;
|
|
|
|
setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
|
|
|
|
(char *) &newvalue, sizeof(newvalue));
|
|
|
|
}
|
2010-01-22 04:48:24 -08:00
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
dbg_socket = socket(sock_domain, SOCK_STREAM, 0);
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
if (retcode == 0) {
|
|
|
|
/* Restore initial mode */
|
|
|
|
setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
|
|
|
|
(char *) &oldvalue, oldvaluelen);
|
|
|
|
}
|
2010-01-22 04:48:24 -08:00
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
if (dbg_socket == -1 ||
|
2007-10-08 05:29:22 -07:00
|
|
|
connect(dbg_socket, &sock_addr.s_gen, sock_addr_len) == -1){
|
2010-04-20 08:47:15 -07:00
|
|
|
caml_fatal_error_arg2 ("cannot connect to debugger at %s\n", dbg_addr,
|
2007-10-08 05:29:22 -07:00
|
|
|
"error: %s\n", strerror (errno));
|
|
|
|
}
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
dbg_socket = _open_osfhandle(dbg_socket, 0);
|
|
|
|
if (dbg_socket == -1)
|
|
|
|
caml_fatal_error("_open_osfhandle failed");
|
|
|
|
#endif
|
2003-12-29 14:15:02 -08:00
|
|
|
dbg_in = caml_open_descriptor_in(dbg_socket);
|
|
|
|
dbg_out = caml_open_descriptor_out(dbg_socket);
|
2004-01-01 08:42:43 -08:00
|
|
|
if (!caml_debugger_in_use) caml_putword(dbg_out, -1); /* first connection */
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
caml_putword(dbg_out, _getpid());
|
|
|
|
#else
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_putword(dbg_out, getpid());
|
2008-07-29 01:31:41 -07:00
|
|
|
#endif
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void close_connection(void)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_close_channel(dbg_in);
|
|
|
|
caml_close_channel(dbg_out);
|
|
|
|
dbg_socket = -1; /* was closed by caml_close_channel */
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
|
|
|
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
static void winsock_startup(void)
|
|
|
|
{
|
|
|
|
WSADATA wsaData;
|
|
|
|
int err = WSAStartup(MAKEWORD(2, 0), &wsaData);
|
|
|
|
if (err) caml_fatal_error("WSAStartup failed");
|
|
|
|
}
|
|
|
|
|
|
|
|
static void winsock_cleanup(void)
|
|
|
|
{
|
|
|
|
WSACleanup();
|
|
|
|
}
|
|
|
|
#endif
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_debugger_init(void)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
|
|
|
char * address;
|
|
|
|
char * port, * p;
|
|
|
|
struct hostent * host;
|
|
|
|
int n;
|
|
|
|
|
|
|
|
address = getenv("CAML_DEBUG_SOCKET");
|
|
|
|
if (address == NULL) return;
|
2007-10-08 05:29:22 -07:00
|
|
|
dbg_addr = address;
|
1996-12-03 05:40:28 -08:00
|
|
|
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifdef _WIN32
|
|
|
|
winsock_startup();
|
|
|
|
(void)atexit(winsock_cleanup);
|
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
/* Parse the address */
|
|
|
|
port = NULL;
|
|
|
|
for (p = address; *p != 0; p++) {
|
|
|
|
if (*p == ':') { *p = 0; port = p+1; break; }
|
|
|
|
}
|
|
|
|
if (port == NULL) {
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifndef _WIN32
|
1996-12-03 05:40:28 -08:00
|
|
|
/* Unix domain */
|
|
|
|
sock_domain = PF_UNIX;
|
|
|
|
sock_addr.s_unix.sun_family = AF_UNIX;
|
|
|
|
strncpy(sock_addr.s_unix.sun_path, address,
|
|
|
|
sizeof(sock_addr.s_unix.sun_path));
|
2007-10-08 05:29:22 -07:00
|
|
|
sock_addr_len =
|
1996-12-03 05:40:28 -08:00
|
|
|
((char *)&(sock_addr.s_unix.sun_path) - (char *)&(sock_addr.s_unix))
|
|
|
|
+ strlen(address);
|
2008-07-29 01:31:41 -07:00
|
|
|
#else
|
|
|
|
caml_fatal_error("Unix sockets not supported");
|
2010-01-22 04:48:24 -08:00
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
} else {
|
|
|
|
/* Internet domain */
|
|
|
|
sock_domain = PF_INET;
|
|
|
|
for (p = (char *) &sock_addr.s_inet, n = sizeof(sock_addr.s_inet);
|
|
|
|
n > 0; n--) *p++ = 0;
|
|
|
|
sock_addr.s_inet.sin_family = AF_INET;
|
|
|
|
sock_addr.s_inet.sin_addr.s_addr = inet_addr(address);
|
|
|
|
if (sock_addr.s_inet.sin_addr.s_addr == -1) {
|
|
|
|
host = gethostbyname(address);
|
|
|
|
if (host == NULL)
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_fatal_error_arg("Unknown debugging host %s\n", address);
|
2000-10-12 11:05:42 -07:00
|
|
|
memmove(&sock_addr.s_inet.sin_addr, host->h_addr, host->h_length);
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
|
|
|
sock_addr.s_inet.sin_port = htons(atoi(port));
|
|
|
|
sock_addr_len = sizeof(sock_addr.s_inet);
|
|
|
|
}
|
|
|
|
open_connection();
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_debugger_in_use = 1;
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_trap_barrier = caml_stack_high;
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static value getval(struct channel *chan)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
|
|
|
value res;
|
2003-12-29 14:15:02 -08:00
|
|
|
if (caml_really_getblock(chan, (char *) &res, sizeof(res)) == 0)
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_raise_end_of_file(); /* Bad, but consistent with caml_getword */
|
1996-12-03 05:40:28 -08:00
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void putval(struct channel *chan, value val)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_really_putblock(chan, (char *) &val, sizeof(val));
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
|
|
|
|
1997-09-02 05:55:01 -07:00
|
|
|
static void safe_output_value(struct channel *chan, value val)
|
1997-06-13 08:49:36 -07:00
|
|
|
{
|
|
|
|
struct longjmp_buffer raise_buf, * saved_external_raise;
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
/* Catch exceptions raised by [caml_output_val] */
|
|
|
|
saved_external_raise = caml_external_raise;
|
1999-06-05 05:02:48 -07:00
|
|
|
if (sigsetjmp(raise_buf.buf, 0) == 0) {
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_external_raise = &raise_buf;
|
|
|
|
caml_output_val(chan, val, Val_unit);
|
1997-06-13 08:49:36 -07:00
|
|
|
} else {
|
2004-01-01 08:42:43 -08:00
|
|
|
/* Send wrong magic number, will cause [caml_input_value] to fail */
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_really_putblock(chan, "\000\000\000\000", 4);
|
1997-06-13 08:49:36 -07:00
|
|
|
}
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_external_raise = saved_external_raise;
|
1997-06-13 08:49:36 -07:00
|
|
|
}
|
|
|
|
|
2001-08-13 06:53:51 -07:00
|
|
|
#define Pc(sp) ((code_t)((sp)[0]))
|
|
|
|
#define Env(sp) ((sp)[1])
|
|
|
|
#define Extra_args(sp) (Long_val(((sp)[2])))
|
|
|
|
#define Locals(sp) ((sp) + 3)
|
1996-12-03 05:40:28 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_debugger(enum event_kind event)
|
1996-12-03 05:40:28 -08:00
|
|
|
{
|
|
|
|
int frame_number;
|
|
|
|
value * frame;
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat i, pos;
|
1996-12-03 05:40:28 -08:00
|
|
|
value val;
|
|
|
|
|
|
|
|
if (dbg_socket == -1) return; /* Not connected to a debugger. */
|
|
|
|
|
|
|
|
/* Reset current frame */
|
|
|
|
frame_number = 0;
|
2003-12-31 06:20:40 -08:00
|
|
|
frame = caml_extern_sp + 1;
|
1996-12-03 05:40:28 -08:00
|
|
|
|
|
|
|
/* Report the event to the debugger */
|
|
|
|
switch(event) {
|
|
|
|
case PROGRAM_START: /* Nothing to report */
|
|
|
|
goto command_loop;
|
|
|
|
case EVENT_COUNT:
|
|
|
|
putch(dbg_out, REP_EVENT);
|
|
|
|
break;
|
|
|
|
case BREAKPOINT:
|
|
|
|
putch(dbg_out, REP_BREAKPOINT);
|
|
|
|
break;
|
|
|
|
case PROGRAM_EXIT:
|
|
|
|
putch(dbg_out, REP_EXITED);
|
|
|
|
break;
|
|
|
|
case TRAP_BARRIER:
|
|
|
|
putch(dbg_out, REP_TRAP);
|
|
|
|
break;
|
|
|
|
case UNCAUGHT_EXC:
|
|
|
|
putch(dbg_out, REP_UNCAUGHT_EXC);
|
|
|
|
break;
|
|
|
|
}
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_putword(dbg_out, caml_event_count);
|
1997-06-13 08:49:36 -07:00
|
|
|
if (event == EVENT_COUNT || event == BREAKPOINT) {
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_putword(dbg_out, caml_stack_high - frame);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_putword(dbg_out, (Pc(frame) - caml_start_code) * sizeof(opcode_t));
|
1997-06-13 08:49:36 -07:00
|
|
|
} else {
|
|
|
|
/* No PC and no stack frame associated with other events */
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_putword(dbg_out, 0);
|
|
|
|
caml_putword(dbg_out, 0);
|
1997-06-13 08:49:36 -07:00
|
|
|
}
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
|
|
|
|
command_loop:
|
2007-10-08 05:29:22 -07:00
|
|
|
|
1996-12-03 05:40:28 -08:00
|
|
|
/* Read and execute the commands sent by the debugger */
|
|
|
|
while(1) {
|
|
|
|
switch(getch(dbg_in)) {
|
|
|
|
case REQ_SET_EVENT:
|
2003-12-29 14:15:02 -08:00
|
|
|
pos = caml_getword(dbg_in);
|
2000-08-23 10:10:03 -07:00
|
|
|
Assert (pos >= 0);
|
2004-01-02 11:23:29 -08:00
|
|
|
Assert (pos < caml_code_size);
|
|
|
|
caml_set_instruction(caml_start_code + pos / sizeof(opcode_t), EVENT);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_SET_BREAKPOINT:
|
2003-12-29 14:15:02 -08:00
|
|
|
pos = caml_getword(dbg_in);
|
2000-08-23 10:10:03 -07:00
|
|
|
Assert (pos >= 0);
|
2004-01-02 11:23:29 -08:00
|
|
|
Assert (pos < caml_code_size);
|
|
|
|
caml_set_instruction(caml_start_code + pos / sizeof(opcode_t), BREAK);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_RESET_INSTR:
|
2003-12-29 14:15:02 -08:00
|
|
|
pos = caml_getword(dbg_in);
|
2000-08-23 10:10:03 -07:00
|
|
|
Assert (pos >= 0);
|
2004-01-02 11:23:29 -08:00
|
|
|
Assert (pos < caml_code_size);
|
1996-12-03 05:40:28 -08:00
|
|
|
pos = pos / sizeof(opcode_t);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_set_instruction(caml_start_code + pos, caml_saved_code[pos]);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_CHECKPOINT:
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifndef _WIN32
|
1996-12-03 05:40:28 -08:00
|
|
|
i = fork();
|
|
|
|
if (i == 0) {
|
1997-05-19 08:42:21 -07:00
|
|
|
close_connection(); /* Close parent connection. */
|
|
|
|
open_connection(); /* Open new connection with debugger */
|
1996-12-03 05:40:28 -08:00
|
|
|
} else {
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_putword(dbg_out, i);
|
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
2008-07-29 01:31:41 -07:00
|
|
|
#else
|
|
|
|
caml_fatal_error("error: REQ_CHECKPOINT command");
|
|
|
|
exit(-1);
|
2010-01-22 04:48:24 -08:00
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GO:
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_event_count = caml_getword(dbg_in);
|
1996-12-03 05:40:28 -08:00
|
|
|
return;
|
|
|
|
case REQ_STOP:
|
|
|
|
exit(0);
|
|
|
|
break;
|
|
|
|
case REQ_WAIT:
|
2008-07-29 01:31:41 -07:00
|
|
|
#ifndef _WIN32
|
1996-12-03 05:40:28 -08:00
|
|
|
wait(NULL);
|
2008-07-29 01:31:41 -07:00
|
|
|
#else
|
|
|
|
caml_fatal_error("Fatal error: REQ_WAIT command");
|
|
|
|
exit(-1);
|
2010-01-22 04:48:24 -08:00
|
|
|
#endif
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_INITIAL_FRAME:
|
2003-12-31 06:20:40 -08:00
|
|
|
frame = caml_extern_sp + 1;
|
1996-12-03 05:40:28 -08:00
|
|
|
/* Fall through */
|
|
|
|
case REQ_GET_FRAME:
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_putword(dbg_out, caml_stack_high - frame);
|
|
|
|
if (frame < caml_stack_high){
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_putword(dbg_out, (Pc(frame) - caml_start_code) * sizeof(opcode_t));
|
2002-10-22 05:30:03 -07:00
|
|
|
}else{
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_putword (dbg_out, 0);
|
2002-10-22 05:30:03 -07:00
|
|
|
}
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_SET_FRAME:
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
2003-12-31 06:20:40 -08:00
|
|
|
frame = caml_stack_high - i;
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_UP_FRAME:
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
2003-12-31 06:20:40 -08:00
|
|
|
if (frame + Extra_args(frame) + i + 3 >= caml_stack_high) {
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_putword(dbg_out, -1);
|
1996-12-03 05:40:28 -08:00
|
|
|
} else {
|
1997-06-18 13:18:41 -07:00
|
|
|
frame += Extra_args(frame) + i + 3;
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_putword(dbg_out, caml_stack_high - frame);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_putword(dbg_out, (Pc(frame) - caml_start_code) * sizeof(opcode_t));
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_SET_TRAP_BARRIER:
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_trap_barrier = caml_stack_high - i;
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_LOCAL:
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
1996-12-03 05:40:28 -08:00
|
|
|
putval(dbg_out, Locals(frame)[i]);
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_ENVIRONMENT:
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
1996-12-03 05:40:28 -08:00
|
|
|
putval(dbg_out, Field(Env(frame), i));
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_GLOBAL:
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
2003-12-31 06:20:40 -08:00
|
|
|
putval(dbg_out, Field(caml_global_data, i));
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_ACCU:
|
2003-12-31 06:20:40 -08:00
|
|
|
putval(dbg_out, *caml_extern_sp);
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_HEADER:
|
|
|
|
val = getval(dbg_in);
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_putword(dbg_out, Hd_val(val));
|
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_FIELD:
|
|
|
|
val = getval(dbg_in);
|
2003-12-29 14:15:02 -08:00
|
|
|
i = caml_getword(dbg_in);
|
1999-05-15 08:07:44 -07:00
|
|
|
if (Tag_val(val) != Double_array_tag) {
|
|
|
|
putch(dbg_out, 0);
|
|
|
|
putval(dbg_out, Field(val, i));
|
|
|
|
} else {
|
1999-05-15 10:01:27 -07:00
|
|
|
double d = Double_field(val, i);
|
1999-05-15 08:07:44 -07:00
|
|
|
putch(dbg_out, 1);
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_really_putblock(dbg_out, (char *) &d, 8);
|
1999-05-15 08:07:44 -07:00
|
|
|
}
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_MARSHAL_OBJ:
|
|
|
|
val = getval(dbg_in);
|
1997-06-13 08:49:36 -07:00
|
|
|
safe_output_value(dbg_out, val);
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
|
|
|
case REQ_GET_CLOSURE_CODE:
|
|
|
|
val = getval(dbg_in);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_putword(dbg_out, (Code_val(val)-caml_start_code) * sizeof(opcode_t));
|
2003-12-29 14:15:02 -08:00
|
|
|
caml_flush(dbg_out);
|
1996-12-03 05:40:28 -08:00
|
|
|
break;
|
2010-04-20 08:47:15 -07:00
|
|
|
case REQ_SET_FORK_MODE:
|
|
|
|
caml_debugger_fork_mode = caml_getword(dbg_in);
|
|
|
|
break;
|
1996-12-03 05:40:28 -08:00
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2010-04-20 08:47:15 -07:00
|
|
|
void caml_debugger_cleanup_fork(void)
|
|
|
|
{
|
|
|
|
/* We could remove all of the breakpoints, but closing the connection
|
|
|
|
* means that they'll just be skipped anyway. */
|
|
|
|
close_connection();
|
|
|
|
caml_debugger_in_use = 0;
|
|
|
|
}
|
|
|
|
|
1996-12-03 05:40:28 -08:00
|
|
|
#endif
|