Skip to content

Commit

Permalink
Improving reporting of exception and version number
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Aug 31, 2021
1 parent 3b734ef commit 95af58b
Show file tree
Hide file tree
Showing 4 changed files with 43 additions and 41 deletions.
10 changes: 5 additions & 5 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,13 @@ cmake_policy(SET CMP0053 NEW)

include(macros.cmake)

# Extract VCS information
include(cmake/versionExtraction.cmake)
extractVCSInformation(GIT_COMMIT_HASH GIT_DESCRIBE GIT_COMMIT_DATE)

set(VERSION_MAJOR 9)
set(VERSION_MINOR 0)
set(VERSION_PATCH 7)
set(VERSION_PATCH "8-${GIT_COMMIT_HASH}")

message("CMAKE_GENERATOR=${CMAKE_GENERATOR}")

Expand Down Expand Up @@ -75,10 +79,6 @@ endif()
# Configure CMake to load our modules
list(APPEND CMAKE_MODULE_PATH "${CMAKE_CURRENT_SOURCE_DIR}/cmake")

# Extract VCS information
include(cmake/versionExtraction.cmake)
extractVCSInformation(GIT_COMMIT_HASH GIT_DESCRIBE GIT_COMMIT_DATE)

#Variable used to set the VM date
set(BUILT_FROM "${GIT_DESCRIBE} - Commit: ${GIT_COMMIT_HASH} - Date: ${GIT_COMMIT_DATE}")
message(STATUS ${BUILT_FROM})
Expand Down
14 changes: 7 additions & 7 deletions src/client.c
Original file line number Diff line number Diff line change
Expand Up @@ -99,23 +99,23 @@ vm_main_with_parameters(VMParameters *parameters)
return 1;
}

if(parameters->isDefaultImage && !parameters->defaultImageFound)
{
if(parameters->isDefaultImage && !parameters->defaultImageFound){
////logError("No image has been specified, and no default image has been found.\n");
vm_printUsageTo(stdout);
return 0;
}

installErrorHandlers();

setProcessArguments(parameters->processArgc, parameters->processArgv);
setProcessEnvironmentVector(parameters->environmentVector);

logInfo("Opening Image: %s\n", parameters->imageFileName);

//This initialization is required because it makes awful, awful, awful code to calculate
//the location of the machine code.
//Luckily, it can be cached.
osCogStackPageHeadroom();
//This initialization is required because it makes awful, awful, awful code to calculate
//the location of the machine code.
//Luckily, it can be cached.
osCogStackPageHeadroom();

// Retrieve the working directory.
char *workingDirectoryBuffer = (char*)calloc(1, FILENAME_MAX+1);
Expand Down Expand Up @@ -169,7 +169,7 @@ vm_main(int argc, const char** argv, const char** env)
parameters.maxStackFramesToPrint = 0;
parameters.maxCodeSize = 0;
parameters.maxOldSpaceSize = 0;
parameters.edenSize = 0;
parameters.edenSize = 0;

// Did we succeed on parsing the parameters?
VMErrorCode error = vm_parameters_parse(argc, argv, &parameters);
Expand Down
59 changes: 30 additions & 29 deletions src/debugUnix.c
Original file line number Diff line number Diff line change
Expand Up @@ -46,10 +46,10 @@ void doReport(char* fault, ucontext_t *uap){
char crashdumpFileName[PATH_MAX+1];
FILE *crashDumpFile;


ctime_r(&now,ctimebuf);

//This is awful but replace the stdout to print all the messages in the file.
crashdumpFileName[0] = 0;
getCrashDumpFilenameInto(crashdumpFileName);
crashDumpFile = fopen(crashdumpFileName, "a+");
vm_setVMOutputStream(crashDumpFile);
Expand Down Expand Up @@ -79,12 +79,9 @@ void sigsegv(int sig, siginfo_t *info, ucontext_t *uap)
{
char *fault = strsignal(sig);

if (!inFault) {
inFault = 1;
doReport(fault, uap);
}

abort();
doReport(fault, uap);

exit(-1);
}

void terminateHandler(int sig, siginfo_t *info, ucontext_t *uap)
Expand Down Expand Up @@ -115,27 +112,39 @@ EXPORT(void) installErrorHandlers(){
sigsegv_handler_action.sa_sigaction = (void (*)(int, siginfo_t *, void *))sigsegv;
sigsegv_handler_action.sa_flags = SA_NODEFER | SA_SIGINFO;
sigemptyset(&sigsegv_handler_action.sa_mask);


sigaction(SIGEMT, &sigsegv_handler_action, 0);
sigaction(SIGFPE, &sigsegv_handler_action, 0);

sigaction(SIGTRAP, &sigsegv_handler_action, 0);
sigaction(SIGQUIT, &sigsegv_handler_action, 0);

sigaction(SIGBUS, &sigsegv_handler_action, 0);
sigaction(SIGILL, &sigsegv_handler_action, 0);
sigaction(SIGSEGV, &sigsegv_handler_action, 0);
sigaction(SIGSYS, &sigsegv_handler_action, 0);
sigaction(SIGALRM, &sigsegv_handler_action, 0);
sigaction(SIGABRT, &sigsegv_handler_action, 0);

term_handler_action.sa_sigaction = (void (*)(int, siginfo_t *, void *))terminateHandler;
term_handler_action.sa_flags = SA_NODEFER | SA_SIGINFO;

sigaction(SIGHUP, &term_handler_action, 0);
sigaction(SIGTERM, &term_handler_action, 0);

sigaction(SIGKILL, &term_handler_action, 0);
sigaction(SIGHUP, &term_handler_action, 0);

//Ignore all broken pipe signals. They will be reported as normal errors by send() and write()
//Otherwise SIGPIPE kill the process without allowing any recovery or treatment
sigpipe_handler_action.sa_sigaction = (void (*)(int, siginfo_t *, void *))SIG_IGN;
sigpipe_handler_action.sa_flags = SA_NODEFER | SA_SIGINFO;
sigaction(SIGPIPE, &sigpipe_handler_action, 0);

//Ignore all broken pipe signals. They will be reported as normal errors by send() and write()
//Otherwise SIGPIPE kill the process without allowing any recovery or treatment
sigpipe_handler_action.sa_sigaction = (void (*)(int, siginfo_t *, void *))SIG_IGN;
sigpipe_handler_action.sa_flags = SA_NODEFER | SA_SIGINFO;
sigaction(SIGPIPE, &sigpipe_handler_action, 0);

sigusr1_handler_action.sa_sigaction = (void (*)(int, siginfo_t *, void *))sigusr1;
sigusr1_handler_action.sa_flags = SA_NODEFER | SA_SIGINFO;
sigemptyset(&sigusr1_handler_action.sa_mask);
(void)sigaction(SIGUSR1, &sigusr1_handler_action, 0);
sigaction(SIGUSR1, &sigusr1_handler_action, 0);
}

void * printRegisterState(ucontext_t *uap, FILE* output)
Expand Down Expand Up @@ -349,6 +358,8 @@ static int runningInVMThread(){

}

static sqInt printingStack = false;

void reportStackState(const char *msg, char *date, int printAll, ucontext_t *uap, FILE* output)
{
#if !defined(NOEXECINFO)
Expand All @@ -357,7 +368,6 @@ void reportStackState(const char *msg, char *date, int printAll, ucontext_t *uap
int depth;
#endif
/* flag prevents recursive error when trying to print a broken stack */
static sqInt printingStack = false;

#if COGVM
/* Testing stackLimit tells us whether the VM is initialized. */
Expand Down Expand Up @@ -387,7 +397,7 @@ void reportStackState(const char *msg, char *date, int printAll, ucontext_t *uap
fflush(output); /* backtrace_symbols_fd uses unbuffered i/o */
backtrace_symbols_fd(addrs, depth + 1, fileno(output));
#endif

if (runningInVMThread()) {
if (!printingStack) {
#if COGVM
Expand Down Expand Up @@ -454,18 +464,9 @@ void reportStackState(const char *msg, char *date, int printAll, ucontext_t *uap
#endif
}
}
else
fprintf(output,"\nNot in VM thread. Smalltalk stack might not be updated\n");

printingStack = true;
if (printAll) {
fprintf(output, "\n\nAll Smalltalk process stacks (active first):\n");
printAllStacks();
} else {
fprintf(output,"\n\nSmalltalk stack dump:\n");
printCallStack();
}
printingStack = false;
else {
fprintf(output,"\nNot in VM thread.\n");
}

#if STACKVM
fprintf(output, "\nMost recent primitives\n");
Expand Down
1 change: 1 addition & 0 deletions src/debugWin.c
Original file line number Diff line number Diff line change
Expand Up @@ -125,6 +125,7 @@ EXPORT(void) printCrashDebugInformation(LPEXCEPTION_POINTERS exp){


//This is awful but replace the stdout to print all the messages in the file.
crashdumpFileName[0] = 0;
getCrashDumpFilenameInto(crashdumpFileName);
crashDumpFile = fopen(crashdumpFileName, "a+");
vm_setVMOutputStream(crashDumpFile);
Expand Down

0 comments on commit 95af58b

Please sign in to comment.