#include "RtsFlags.h"
#include "sm/OSMem.h"
#include "hooks/Hooks.h"
+#include "Capability.h"
-#ifdef HAVE_CTYPE_H
+#if defined(HAVE_CTYPE_H)
#include <ctype.h>
#endif
#include <string.h>
-#ifdef HAVE_UNISTD_H
+#if defined(HAVE_UNISTD_H)
#include <unistd.h>
#endif
-#ifdef HAVE_SYS_TYPES_H
+#if defined(HAVE_SYS_TYPES_H)
#include <sys/types.h>
#endif
+#include <fs_rts.h>
+
// Flag Structure
RTS_FLAGS RtsFlags;
char **rts_argv = NULL;
int rts_argv_size = 0;
#if defined(mingw32_HOST_OS)
-// On Windows, we want to use GetCommandLineW rather than argc/argv,
-// but we need to mutate the command line arguments for withProgName and
-// friends. The System.Environment module achieves that using this bit of
-// shared state:
-int win32_prog_argc = 0;
-wchar_t **win32_prog_argv = NULL;
+// On Windows hs_main uses GetCommandLineW to get Unicode arguments and
+// passes them along UTF8 encoded as argv. We store them here in order to
+// free them on exit.
+int win32_full_utf8_argc = 0;
+char** win32_utf8_argv = NULL;
#endif
// The global rtsConfig, set from the RtsConfig supplied by the call
const RtsConfig defaultRtsConfig = {
.rts_opts_enabled = RtsOptsSafeOnly,
- .rts_opts_suggestions = rtsTrue,
+ .rts_opts_suggestions = true,
.rts_opts = NULL,
- .rts_hs_main = rtsFalse,
- .keep_cafs = rtsFalse,
+ .rts_hs_main = false,
+ .keep_cafs = false,
+ .eventlog_writer = &FileEventLogWriter,
.defaultsHook = FlagDefaultsHook,
.onExitHook = OnExitHook,
.stackOverflowHook = StackOverflowHook,
.outOfHeapHook = OutOfHeapHook,
.mallocFailHook = MallocFailHook,
- .gcDoneHook = NULL
+ .gcDoneHook = NULL,
+ .longGCSync = LongGCSync,
+ .longGCSyncEnd = LongGCSyncEnd
};
/*
char *filename, const char *FILENAME_FMT, FILE **file_ret);
static StgWord64 decodeSize (
- const char *flag, nat offset, StgWord64 min, StgWord64 max);
+ const char *flag, uint32_t offset, StgWord64 min, StgWord64 max);
static void bad_option (const char *s);
-#ifdef DEBUG
+#if defined(DEBUG)
static void read_debug_flags(const char *arg);
#endif
-#ifdef PROFILING
-static rtsBool read_heap_profiling_flag(const char *arg);
+#if defined(PROFILING)
+static bool read_heap_profiling_flag(const char *arg);
#endif
-#ifdef TRACING
+#if defined(TRACING)
static void read_trace_flags(const char *arg);
#endif
static void errorUsage (void) GNU_ATTRIBUTE(__noreturn__);
+#if defined(mingw32_HOST_OS)
+static char** win32_full_utf8_argv;
+#endif
static char * copyArg (char *arg);
static char ** copyArgv (int argc, char *argv[]);
static void freeArgv (int argc, char *argv[]);
RtsFlags.GcFlags.stkChunkSize = (32 * 1024) / sizeof(W_);
RtsFlags.GcFlags.stkChunkBufferSize = (1 * 1024) / sizeof(W_);
- RtsFlags.GcFlags.minAllocAreaSize = (512 * 1024) / BLOCK_SIZE;
+ RtsFlags.GcFlags.minAllocAreaSize = (1024 * 1024) / BLOCK_SIZE;
+ RtsFlags.GcFlags.largeAllocLim = 0; /* defaults to minAllocAreasize */
RtsFlags.GcFlags.nurseryChunkSize = 0;
RtsFlags.GcFlags.minOldGenSize = (1024 * 1024) / BLOCK_SIZE;
RtsFlags.GcFlags.maxHeapSize = 0; /* off by default */
+ RtsFlags.GcFlags.heapLimitGrace = (1024 * 1024);
RtsFlags.GcFlags.heapSizeSuggestion = 0; /* none */
- RtsFlags.GcFlags.heapSizeSuggestionAuto = rtsFalse;
+ RtsFlags.GcFlags.heapSizeSuggestionAuto = false;
RtsFlags.GcFlags.pcFreeHeap = 3; /* 3% */
RtsFlags.GcFlags.oldGenFactor = 2;
RtsFlags.GcFlags.generations = 2;
- RtsFlags.GcFlags.squeezeUpdFrames = rtsTrue;
- RtsFlags.GcFlags.compact = rtsFalse;
+ RtsFlags.GcFlags.squeezeUpdFrames = true;
+ RtsFlags.GcFlags.compact = false;
RtsFlags.GcFlags.compactThreshold = 30.0;
- RtsFlags.GcFlags.sweep = rtsFalse;
+ RtsFlags.GcFlags.sweep = false;
RtsFlags.GcFlags.idleGCDelayTime = USToTime(300000); // 300ms
-#ifdef THREADED_RTS
- RtsFlags.GcFlags.doIdleGC = rtsTrue;
+#if defined(THREADED_RTS)
+ RtsFlags.GcFlags.doIdleGC = true;
#else
- RtsFlags.GcFlags.doIdleGC = rtsFalse;
+ RtsFlags.GcFlags.doIdleGC = false;
#endif
RtsFlags.GcFlags.heapBase = 0; /* means don't care */
RtsFlags.GcFlags.allocLimitGrace = (100*1024) / BLOCK_SIZE;
-
-#ifdef DEBUG
- RtsFlags.DebugFlags.scheduler = rtsFalse;
- RtsFlags.DebugFlags.interpreter = rtsFalse;
- RtsFlags.DebugFlags.weak = rtsFalse;
- RtsFlags.DebugFlags.gccafs = rtsFalse;
- RtsFlags.DebugFlags.gc = rtsFalse;
- RtsFlags.DebugFlags.block_alloc = rtsFalse;
- RtsFlags.DebugFlags.sanity = rtsFalse;
- RtsFlags.DebugFlags.stable = rtsFalse;
- RtsFlags.DebugFlags.stm = rtsFalse;
- RtsFlags.DebugFlags.prof = rtsFalse;
- RtsFlags.DebugFlags.apply = rtsFalse;
- RtsFlags.DebugFlags.linker = rtsFalse;
- RtsFlags.DebugFlags.squeeze = rtsFalse;
- RtsFlags.DebugFlags.hpc = rtsFalse;
- RtsFlags.DebugFlags.sparks = rtsFalse;
-#endif
+ RtsFlags.GcFlags.numa = false;
+ RtsFlags.GcFlags.numaMask = 1;
+ RtsFlags.GcFlags.ringBell = false;
+ RtsFlags.GcFlags.longGCSync = 0; /* detection turned off */
+
+ RtsFlags.DebugFlags.scheduler = false;
+ RtsFlags.DebugFlags.interpreter = false;
+ RtsFlags.DebugFlags.weak = false;
+ RtsFlags.DebugFlags.gccafs = false;
+ RtsFlags.DebugFlags.gc = false;
+ RtsFlags.DebugFlags.block_alloc = false;
+ RtsFlags.DebugFlags.sanity = false;
+ RtsFlags.DebugFlags.stable = false;
+ RtsFlags.DebugFlags.stm = false;
+ RtsFlags.DebugFlags.prof = false;
+ RtsFlags.DebugFlags.apply = false;
+ RtsFlags.DebugFlags.linker = false;
+ RtsFlags.DebugFlags.squeeze = false;
+ RtsFlags.DebugFlags.hpc = false;
+ RtsFlags.DebugFlags.sparks = false;
+ RtsFlags.DebugFlags.numa = false;
+ RtsFlags.DebugFlags.compact = false;
#if defined(PROFILING)
- RtsFlags.CcFlags.doCostCentres = 0;
+ RtsFlags.CcFlags.doCostCentres = COST_CENTRES_NONE;
+ RtsFlags.CcFlags.outputFileNameStem = NULL;
#endif /* PROFILING */
- RtsFlags.ProfFlags.doHeapProfile = rtsFalse;
- RtsFlags.ProfFlags. heapProfileInterval = USToTime(100000); // 100ms
+ RtsFlags.ProfFlags.doHeapProfile = false;
+ RtsFlags.ProfFlags.heapProfileInterval = USToTime(100000); // 100ms
-#ifdef PROFILING
- RtsFlags.ProfFlags.includeTSOs = rtsFalse;
- RtsFlags.ProfFlags.showCCSOnException = rtsFalse;
+#if defined(PROFILING)
+ RtsFlags.ProfFlags.includeTSOs = false;
+ RtsFlags.ProfFlags.showCCSOnException = false;
RtsFlags.ProfFlags.maxRetainerSetSize = 8;
RtsFlags.ProfFlags.ccsLength = 25;
RtsFlags.ProfFlags.modSelector = NULL;
RtsFlags.ProfFlags.bioSelector = NULL;
#endif
-#ifdef TRACING
+#if defined(TRACING)
RtsFlags.TraceFlags.tracing = TRACE_NONE;
- RtsFlags.TraceFlags.timestamp = rtsFalse;
- RtsFlags.TraceFlags.scheduler = rtsFalse;
- RtsFlags.TraceFlags.gc = rtsFalse;
- RtsFlags.TraceFlags.sparks_sampled= rtsFalse;
- RtsFlags.TraceFlags.sparks_full = rtsFalse;
- RtsFlags.TraceFlags.user = rtsFalse;
+ RtsFlags.TraceFlags.timestamp = false;
+ RtsFlags.TraceFlags.scheduler = false;
+ RtsFlags.TraceFlags.gc = false;
+ RtsFlags.TraceFlags.sparks_sampled= false;
+ RtsFlags.TraceFlags.sparks_full = false;
+ RtsFlags.TraceFlags.user = false;
+ RtsFlags.TraceFlags.trace_output = NULL;
#endif
-#ifdef PROFILING
+#if defined(PROFILING)
// When profiling we want a lot more ticks
RtsFlags.MiscFlags.tickInterval = USToTime(1000); // 1ms
#else
#endif
RtsFlags.ConcFlags.ctxtSwitchTime = USToTime(20000); // 20ms
- RtsFlags.MiscFlags.install_signal_handlers = rtsTrue;
- RtsFlags.MiscFlags.machineReadable = rtsFalse;
- RtsFlags.MiscFlags.linkerMemBase = 0;
+ RtsFlags.MiscFlags.install_signal_handlers = true;
+ RtsFlags.MiscFlags.install_seh_handlers = true;
+ RtsFlags.MiscFlags.generate_stack_trace = true;
+ RtsFlags.MiscFlags.generate_dump_file = false;
+ RtsFlags.MiscFlags.machineReadable = false;
+ RtsFlags.MiscFlags.internalCounters = false;
+ RtsFlags.MiscFlags.linkerAlwaysPic = DEFAULT_LINKER_ALWAYS_PIC;
+ RtsFlags.MiscFlags.linkerMemBase = 0;
-#ifdef THREADED_RTS
- RtsFlags.ParFlags.nNodes = 1;
- RtsFlags.ParFlags.migrate = rtsTrue;
+#if defined(THREADED_RTS)
+ RtsFlags.ParFlags.nCapabilities = 1;
+ RtsFlags.ParFlags.migrate = true;
RtsFlags.ParFlags.parGcEnabled = 1;
RtsFlags.ParFlags.parGcGen = 0;
- RtsFlags.ParFlags.parGcLoadBalancingEnabled = rtsTrue;
- RtsFlags.ParFlags.parGcLoadBalancingGen = 1;
+ RtsFlags.ParFlags.parGcLoadBalancingEnabled = true;
+ RtsFlags.ParFlags.parGcLoadBalancingGen = ~0u; /* auto, based on -A */
RtsFlags.ParFlags.parGcNoSyncWithIdle = 0;
+ RtsFlags.ParFlags.parGcThreads = 0; /* defaults to -N */
RtsFlags.ParFlags.setAffinity = 0;
#endif
RtsFlags.ParFlags.maxLocalSparks = 4096;
#endif /* THREADED_RTS */
-#ifdef TICKY_TICKY
- RtsFlags.TickyFlags.showTickyStats = rtsFalse;
+#if defined(TICKY_TICKY)
+ RtsFlags.TickyFlags.showTickyStats = false;
RtsFlags.TickyFlags.tickyFile = NULL;
#endif
}
" -kc<size> Sets the stack chunk size (default 32k)",
" -kb<size> Sets the stack chunk buffer size (default 1k)",
"",
-" -A<size> Sets the minimum allocation area size (default 512k) Egs: -A1m -A10k",
-" -n<size> Allocation area chunk size (0 = disabled, default: 0)",
-" -O<size> Sets the minimum size of the old generation (default 1M)",
-" -M<size> Sets the maximum heap size (default unlimited) Egs: -M256k -M1G",
-" -H<size> Sets the minimum heap size (default 0M) Egs: -H24m -H1G",
-" -m<n> Minimum % of heap which must be available (default 3%)",
-" -G<n> Number of generations (default: 2)",
-" -c<n> Use in-place compaction instead of copying in the oldest generation",
+" -A<size> Sets the minimum allocation area size (default 1m) Egs: -A20m -A10k",
+" -AL<size> Sets the amount of large-object memory that can be allocated",
+" before a GC is triggered (default: the value of -A)",
+" -F<n> Sets the collecting threshold for old generations as a factor of",
+" the live data in that generation the last time it was collected",
+" (default: 2.0)",
+" -n<size> Allocation area chunk size (0 = disabled, default: 0)",
+" -O<size> Sets the minimum size of the old generation (default 1M)",
+" -M<size> Sets the maximum heap size (default unlimited) Egs: -M256k -M1G",
+" -H<size> Sets the minimum heap size (default 0M) Egs: -H24m -H1G",
+" -xb<addr> Sets the address from which a suitable start for the heap memory",
+" will be searched from. This is useful if the default address",
+" clashes with some third-party library.",
+" -m<n> Minimum % of heap which must be available (default 3%)",
+" -G<n> Number of generations (default: 2)",
+" -c<n> Use in-place compaction instead of copying in the oldest generation",
" when live data is at least <n>% of the maximum heap size set with",
" -M (default: 30%)",
" -c Use in-place compaction for all oldest generation collections",
" -S[<file>] Detailed GC statistics (if <file> omitted, uses stderr)",
"",
"",
-" -Z Don't squeeze out update frames on stack overflow",
-" -B Sound the bell at the start of each garbage collection",
+" -Z Don't squeeze out update frames on stack overflow",
+" -B Sound the bell at the start of each garbage collection",
#if defined(PROFILING)
"",
-" -p Time/allocation profile (output file <program>.prof)",
-" -P More detailed Time/Allocation profile",
-" -Pa Give information about *all* cost centres",
+" -p Time/allocation profile in tree format ",
+" (output file <output prefix>.prof)",
+" -po<file> Override profiling output file name prefix (program name by default)",
+" -P More detailed Time/Allocation profile in tree format",
+" -Pa Give information about *all* cost centres in tree format",
+" -pj Output cost-center profile in JSON format",
"",
+" -h Heap residency profile, by cost centre stack",
" -h<break-down> Heap residency profile (hp2ps) (output file <program>.hp)",
" break-down: c = cost centre stack (default)",
" m = module",
+" T = closure type",
" d = closure description",
" y = type description",
" r = retainer",
" -xt Include threads (TSOs) in a heap profile",
"",
" -xc Show current cost centre stack on raising an exception",
+#else /* PROFILING */
+" -h Heap residency profile (output file <program>.hp)",
+" -hT Produce a heap profile grouped by closure type",
#endif /* PROFILING */
-#ifdef TRACING
+#if defined(TRACING)
"",
-" -l[flags] Log events in binary format to the file <program>.eventlog",
-# ifdef DEBUG
+" -ol<file> Send binary eventlog to <file> (default: <program>.eventlog)",
+" -l[flags] Log events to a file",
+# if defined(DEBUG)
" -v[flags] Log events to stderr",
# endif
" where [flags] can contain:",
" f par spark events (full detail)",
" u user events (emitted from Haskell code)",
" a all event classes above",
-# ifdef DEBUG
+# if defined(DEBUG)
" t add time stamps (only useful with -v)",
# endif
" -x disable an event class, for any flag above",
" the initial enabled event classes are 'sgpu'",
#endif
-#if !defined(PROFILING)
-"",
-" -h Heap residency profile (output file <program>.hp)",
-#endif
" -i<sec> Time between heap profile samples (seconds, default: 0.1)",
"",
#if defined(TICKY_TICKY)
" Default: 0.02 sec.",
" -V<secs> Master tick interval in seconds (0 == disable timer).",
" This sets the resolution for -C and the heap profile timer -i,",
-" and is the frequence of time profile samples.",
-#ifdef PROFILING
+" and is the frequency of time profile samples.",
+#if defined(PROFILING)
" Default: 0.001 sec.",
#else
" Default: 0.01 sec.",
" -Dz DEBUG: stack squeezing",
" -Dc DEBUG: program coverage",
" -Dr DEBUG: sparks",
+" -DC DEBUG: compact",
"",
" NOTE: DEBUG events are sent to stderr by default; add -l to create a",
" binary event log file instead.",
" -qg[<n>] Use parallel GC only for generations >= <n>",
" (default: 0, -qg alone turns off parallel GC)",
" -qb[<n>] Use load-balancing in the parallel GC only for generations >= <n>",
-" (default: 1, -qb alone turns off load-balancing)",
+" (default: 1 for -A < 32M, 0 otherwise;",
+" -qb alone turns off load-balancing)",
+" -qn<n> Use <n> threads for parallel GC (defaults to value of -N)",
" -qa Use the OS to set thread affinity (experimental)",
" -qm Don't automatically migrate threads between CPUs",
" -qi<n> If a processor has been idle for the last <n> GCs, do not",
" wake it up for a non-load-balancing parallel GC.",
" (0 disables, default: 0)",
+" --numa[=<node_mask>]",
+" Use NUMA, nodes given by <node_mask> (default: off)",
+#if defined(DEBUG)
+" --debug-numa[=<num_nodes>]",
+" Pretend NUMA: like --numa, but without the system calls.",
+" Can be used on non-NUMA systems for debugging.",
+"",
+#endif
#endif
" --install-signal-handlers=<yes|no>",
" Install signal handlers (default: yes)",
+#if defined(mingw32_HOST_OS)
+" --install-seh-handlers=<yes|no>",
+" Install exception handlers (default: yes)",
+" --generate-crash-dumps",
+" Generate Windows crash dumps, requires exception handlers",
+" to be installed. Implies --install-signal-handlers=yes.",
+" (default: no)",
+" --generate-stack-traces=<yes|no>",
+" Generate a stack trace when your application encounters a",
+" fatal error. When symbols are available an attempt will be",
+" made to resolve addresses to names. (default: yes)",
+#endif
#if defined(THREADED_RTS)
" -e<n> Maximum number of outstanding local sparks (default: 4096)",
#endif
#if defined(x86_64_HOST_ARCH)
+#if !DEFAULT_LINKER_ALWAYS_PIC
+" -xp Assume that all object files were compiled with -fPIC",
+" -fexternal-dynamic-refs and load them anywhere in the address",
+" space",
+#endif
" -xm Base address to mmap memory in the GHCi linker",
" (hex; must be <80000000)",
#endif
" -xq The allocation limit given to a thread after it receives",
" an AllocationLimitExceeded exception. (default: 100k)",
"",
+" -Mgrace=<n>",
+" The amount of allocation after the program receives a",
+" HeapOverflow exception before the exception is thrown again, if",
+" the program is still exceeding the heap limit.",
+"",
"RTS options may also be specified using the GHCRTS environment variable.",
"",
"Other RTS options may be available for programs compiled a different way.",
0
};
-STATIC_INLINE rtsBool strequal(const char *a, const char * b)
+/**
+Note [Windows Unicode Arguments]
+~~~~~~~~~~~~~~~~~~~~~~~~~~
+On Windows argv is usually encoded in the current Codepage which might not
+support unicode.
+
+Instead of ignoring the arguments to hs_init we expect them to be utf-8
+encoded when coming from a custom main function. In the regular hs_main we
+get the unicode arguments from the windows API and pass them along utf8
+encoded instead.
+
+This reduces special casing of arguments in later parts of the RTS and base
+libraries to dealing with slash differences and using utf8 instead of the
+current locale on Windows when decoding arguments.
+
+*/
+
+#if defined(mingw32_HOST_OS)
+//Allocate a buffer and return the string utf8 encoded.
+char* lpcwstrToUTF8(const wchar_t* utf16_str)
+{
+ //Check the utf8 encoded size first
+ int res = WideCharToMultiByte(CP_UTF8, 0, utf16_str, -1, NULL, 0,
+ NULL, NULL);
+ if (res == 0) {
+ return NULL;
+ }
+ char* buffer = (char*) stgMallocBytes((size_t)res, "getUTF8Args 2");
+ res = WideCharToMultiByte(CP_UTF8, 0, utf16_str, -1, buffer, res,
+ NULL, NULL);
+ return buffer;
+}
+
+char** getUTF8Args(int* argc)
+{
+ LPCWSTR cmdLine = GetCommandLineW();
+ LPWSTR* argvw = CommandLineToArgvW(cmdLine, argc);
+
+ // We create two argument arrays, one which is later permutated by the RTS
+ // instead of the main argv.
+ // The other one is used to free the allocted memory later.
+ char** argv = (char**) stgMallocBytes(sizeof(char*) * (*argc + 1),
+ "getUTF8Args 1");
+ win32_full_utf8_argv = (char**) stgMallocBytes(sizeof(char*) * (*argc + 1),
+ "getUTF8Args 1");
+
+ for (int i = 0; i < *argc; i++)
+ {
+ argv[i] = lpcwstrToUTF8(argvw[i]);
+ }
+ argv[*argc] = NULL;
+ memcpy(win32_full_utf8_argv, argv, sizeof(char*) * (*argc + 1));
+
+ LocalFree(argvw);
+ win32_utf8_argv = argv;
+ win32_full_utf8_argc = *argc;
+ return argv;
+}
+#endif
+
+STATIC_INLINE bool strequal(const char *a, const char * b)
{
return(strcmp(a, b) == 0);
}
- rtsConfig (global) contains the supplied RtsConfig
+ On Windows argv is assumed to be utf8 encoded for unicode compatibility.
+ See Note [Windows Unicode Arguments]
+
-------------------------------------------------------------------------- */
void setupRtsFlags (int *argc, char *argv[], RtsConfig rts_config)
{
- nat mode;
- nat total_arg;
- nat arg, rts_argc0;
+ uint32_t mode;
+ uint32_t total_arg;
+ uint32_t arg, rts_argc0;
rtsConfig = rts_config;
// process arguments from the GHCRTS environment variable next
// (arguments from the command line override these).
+ // If we ignore all non-builtin rtsOpts we skip these.
+ if(rtsConfig.rts_opts_enabled != RtsOptsIgnoreAll)
{
char *ghc_rts = getenv("GHCRTS");
}
}
- // Split arguments (argv) into PGM (argv) and RTS (rts_argv) parts
- // argv[0] must be PGM argument -- leave in argv
- for (mode = PGM; arg < total_arg; arg++) {
- // The '--RTS' argument disables all future +RTS ... -RTS processing.
- if (strequal("--RTS", argv[arg])) {
- arg++;
- break;
- }
- // The '--' argument is passed through to the program, but
- // disables all further +RTS ... -RTS processing.
- else if (strequal("--", argv[arg])) {
- break;
- }
- else if (strequal("+RTS", argv[arg])) {
- mode = RTS;
- }
- else if (strequal("-RTS", argv[arg])) {
- mode = PGM;
- }
- else if (mode == RTS) {
- appendRtsArg(copyArg(argv[arg]));
- }
- else {
- argv[(*argc)++] = argv[arg];
+ // If we ignore all commandline rtsOpts we skip processing of argv by
+ // the RTS completely
+ if(!(rtsConfig.rts_opts_enabled == RtsOptsIgnoreAll ||
+ rtsConfig.rts_opts_enabled == RtsOptsIgnore)
+ )
+ {
+ // Split arguments (argv) into PGM (argv) and RTS (rts_argv) parts
+ // argv[0] must be PGM argument -- leave in argv
+ //
+ for (mode = PGM; arg < total_arg; arg++) {
+ // The '--RTS' argument disables all future
+ // +RTS ... -RTS processing.
+ if (strequal("--RTS", argv[arg])) {
+ arg++;
+ break;
+ }
+ // The '--' argument is passed through to the program, but
+ // disables all further +RTS ... -RTS processing.
+ else if (strequal("--", argv[arg])) {
+ break;
+ }
+ else if (strequal("+RTS", argv[arg])) {
+ mode = RTS;
+ }
+ else if (strequal("-RTS", argv[arg])) {
+ mode = PGM;
+ }
+ else if (mode == RTS) {
+ appendRtsArg(copyArg(argv[arg]));
+ }
+ else {
+ argv[(*argc)++] = argv[arg];
+ }
}
+
}
+
// process remaining program arguments
for (; arg < total_arg; arg++) {
argv[(*argc)++] = argv[arg];
if (RtsFlags.GcFlags.statsFile != NULL) {
initStatsFile (RtsFlags.GcFlags.statsFile);
}
-#ifdef TICKY_TICKY
+#if defined(TICKY_TICKY)
if (RtsFlags.TickyFlags.tickyFile != NULL) {
initStatsFile (RtsFlags.TickyFlags.tickyFile);
}
static void procRtsOpts (int rts_argc0,
RtsOptsEnabledEnum rtsOptsEnabled)
{
- rtsBool error = rtsFalse;
+ bool error = false;
int arg;
int unchecked_arg_start;
either OPTION_SAFE or OPTION_UNSAFE. To make sure we cover
every branch we use an option_checked flag which is reset
at the start each iteration and checked at the end. */
- rtsBool option_checked = rtsFalse;
+ bool option_checked = false;
// See Note [OPTION_SAFE vs OPTION_UNSAFE].
-#define OPTION_SAFE option_checked = rtsTrue;
-#define OPTION_UNSAFE checkUnsafe(rtsOptsEnabled); option_checked = rtsTrue;
+#define OPTION_SAFE option_checked = true;
+#define OPTION_UNSAFE checkUnsafe(rtsOptsEnabled); option_checked = true;
if (rts_argv[arg][0] != '-') {
fflush(stdout);
errorBelch("unexpected RTS argument: %s", rts_argv[arg]);
- error = rtsTrue;
+ error = true;
} else {
/* 0 is dash, 1 is first letter */
- /* see Trac #9839 */
+ /* see #9839 */
unchecked_arg_start = 1;
switch(rts_argv[arg][1]) {
x*, which allows for more options.
*/
-#ifdef TICKY_TICKY
+#if defined(TICKY_TICKY)
# define TICKY_BUILD_ONLY(x) x
#else
# define TICKY_BUILD_ONLY(x) \
errorBelch("the flag %s requires the program to be built with -ticky", \
rts_argv[arg]); \
-error = rtsTrue;
+error = true;
#endif
-#ifdef PROFILING
+#if defined(PROFILING)
# define PROFILING_BUILD_ONLY(x) x
#else
# define PROFILING_BUILD_ONLY(x) \
errorBelch("the flag %s requires the program to be built with -prof", \
rts_argv[arg]); \
-error = rtsTrue;
+error = true;
#endif
-#ifdef TRACING
+#if defined(TRACING)
# define TRACING_BUILD_ONLY(x) x
#else
# define TRACING_BUILD_ONLY(x) \
errorBelch("the flag %s requires the program to be built with -eventlog or -debug", \
rts_argv[arg]); \
-error = rtsTrue;
+error = true;
#endif
-#ifdef THREADED_RTS
+#if defined(THREADED_RTS)
# define THREADED_BUILD_ONLY(x) x
#else
# define THREADED_BUILD_ONLY(x) \
errorBelch("the flag %s requires the program to be built with -threaded", \
rts_argv[arg]); \
-error = rtsTrue;
+error = true;
#endif
-#ifdef DEBUG
+#if defined(DEBUG)
# define DEBUG_BUILD_ONLY(x) x
#else
# define DEBUG_BUILD_ONLY(x) \
errorBelch("the flag %s requires the program to be built with -debug", \
rts_argv[arg]); \
-error = rtsTrue;
+error = true;
#endif
/* =========== GENERAL ========================== */
case '?':
OPTION_SAFE;
- error = rtsTrue;
+ error = true;
break;
/* This isn't going to allow us to keep related options
if (strequal("install-signal-handlers=yes",
&rts_argv[arg][2])) {
OPTION_UNSAFE;
- RtsFlags.MiscFlags.install_signal_handlers = rtsTrue;
+ RtsFlags.MiscFlags.install_signal_handlers = true;
}
else if (strequal("install-signal-handlers=no",
&rts_argv[arg][2])) {
OPTION_UNSAFE;
- RtsFlags.MiscFlags.install_signal_handlers = rtsFalse;
+ RtsFlags.MiscFlags.install_signal_handlers = false;
+ }
+ else if (strequal("install-seh-handlers=yes",
+ &rts_argv[arg][2])) {
+ OPTION_UNSAFE;
+ RtsFlags.MiscFlags.install_seh_handlers = true;
+ }
+ else if (strequal("install-seh-handlers=no",
+ &rts_argv[arg][2])) {
+ OPTION_UNSAFE;
+ RtsFlags.MiscFlags.install_seh_handlers = false;
+ }
+ else if (strequal("generate-stack-traces=yes",
+ &rts_argv[arg][2])) {
+ OPTION_UNSAFE;
+ RtsFlags.MiscFlags.generate_stack_trace = true;
+ }
+ else if (strequal("generate-stack-traces=no",
+ &rts_argv[arg][2])) {
+ OPTION_UNSAFE;
+ RtsFlags.MiscFlags.generate_stack_trace = false;
+ }
+ else if (strequal("generate-crash-dumps",
+ &rts_argv[arg][2])) {
+ OPTION_UNSAFE;
+ RtsFlags.MiscFlags.generate_dump_file = true;
}
else if (strequal("machine-readable",
&rts_argv[arg][2])) {
OPTION_UNSAFE;
- RtsFlags.MiscFlags.machineReadable = rtsTrue;
+ RtsFlags.MiscFlags.machineReadable = true;
+ }
+ else if (strequal("internal-counters",
+ &rts_argv[arg][2])) {
+ OPTION_SAFE;
+ RtsFlags.MiscFlags.internalCounters = true;
}
else if (strequal("info",
&rts_argv[arg][2])) {
OPTION_SAFE;
- printRtsInfo();
+ printRtsInfo(rtsConfig);
stg_exit(0);
}
+#if defined(THREADED_RTS)
+ else if (!strncmp("numa", &rts_argv[arg][2], 4)) {
+ if (!osBuiltWithNumaSupport()) {
+ errorBelch("%s: This GHC build was compiled without NUMA support.",
+ rts_argv[arg]);
+ error = true;
+ break;
+ }
+ OPTION_SAFE;
+ StgWord mask;
+ if (rts_argv[arg][6] == '=') {
+ mask = (StgWord)strtol(rts_argv[arg]+7,
+ (char **) NULL, 10);
+ } else {
+ mask = (StgWord)~0;
+ }
+ if (!osNumaAvailable()) {
+ errorBelch("%s: OS reports NUMA is not available",
+ rts_argv[arg]);
+ error = true;
+ break;
+ }
+
+ RtsFlags.GcFlags.numa = true;
+ RtsFlags.GcFlags.numaMask = mask;
+ }
+#endif
+#if defined(DEBUG) && defined(THREADED_RTS)
+ else if (!strncmp("debug-numa", &rts_argv[arg][2], 10)) {
+ OPTION_SAFE;
+ size_t nNodes;
+ if (rts_argv[arg][12] == '=' &&
+ isdigit(rts_argv[arg][13])) {
+ nNodes = (StgWord)strtol(rts_argv[arg]+13,
+ (char **) NULL, 10);
+ } else {
+ errorBelch("%s: missing number of nodes",
+ rts_argv[arg]);
+ error = true;
+ break;
+ }
+ if (nNodes > MAX_NUMA_NODES) {
+ errorBelch("%s: Too many NUMA nodes (max %d)",
+ rts_argv[arg], MAX_NUMA_NODES);
+ error = true;
+ } else {
+ RtsFlags.GcFlags.numa = true;
+ RtsFlags.DebugFlags.numa = true;
+ RtsFlags.GcFlags.numaMask = (1<<nNodes) - 1;
+ }
+ }
+#endif
+ else if (!strncmp("long-gc-sync=", &rts_argv[arg][2], 13)) {
+ OPTION_SAFE;
+ if (rts_argv[arg][2] == '\0') {
+ /* use default */
+ } else {
+ RtsFlags.GcFlags.longGCSync =
+ fsecondsToTime(atof(rts_argv[arg]+16));
+ }
+ break;
+ }
else {
OPTION_SAFE;
errorBelch("unknown RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
}
break;
case 'A':
OPTION_UNSAFE;
- // minimum two blocks in the nursery, so that we have one to
- // grab for allocate().
- RtsFlags.GcFlags.minAllocAreaSize
- = decodeSize(rts_argv[arg], 2, 2*BLOCK_SIZE, HS_INT_MAX)
- / BLOCK_SIZE;
+ if (rts_argv[arg][2] == 'L') {
+ RtsFlags.GcFlags.largeAllocLim
+ = decodeSize(rts_argv[arg], 3, 2*BLOCK_SIZE,
+ HS_INT_MAX) / BLOCK_SIZE;
+ } else {
+ // minimum two blocks in the nursery, so that we have one
+ // to grab for allocate().
+ RtsFlags.GcFlags.minAllocAreaSize
+ = decodeSize(rts_argv[arg], 2, 2*BLOCK_SIZE,
+ HS_INT_MAX) / BLOCK_SIZE;
+ }
break;
case 'n':
OPTION_UNSAFE;
case 'B':
OPTION_UNSAFE;
- RtsFlags.GcFlags.ringBell = rtsTrue;
+ RtsFlags.GcFlags.ringBell = true;
unchecked_arg_start++;
goto check_rest;
RtsFlags.GcFlags.compactThreshold =
atof(rts_argv[arg]+2);
} else {
- RtsFlags.GcFlags.compact = rtsTrue;
+ RtsFlags.GcFlags.compact = true;
}
break;
case 'w':
OPTION_UNSAFE;
- RtsFlags.GcFlags.sweep = rtsTrue;
+ RtsFlags.GcFlags.sweep = true;
unchecked_arg_start++;
goto check_rest;
case 'K':
OPTION_UNSAFE;
RtsFlags.GcFlags.maxStkSize =
- decodeSize(rts_argv[arg], 2, sizeof(W_), HS_WORD_MAX)
+ decodeSize(rts_argv[arg], 2, 0, HS_WORD_MAX)
/ sizeof(W_);
break;
case 'M':
OPTION_UNSAFE;
- RtsFlags.GcFlags.maxHeapSize =
- decodeSize(rts_argv[arg], 2, BLOCK_SIZE, HS_WORD_MAX)
- / BLOCK_SIZE;
- /* user give size in *bytes* but "maxHeapSize" is in
- * *blocks* */
+ if (0 == strncmp("grace=", rts_argv[arg] + 2, 6)) {
+ RtsFlags.GcFlags.heapLimitGrace =
+ decodeSize(rts_argv[arg], 8, BLOCK_SIZE, HS_WORD_MAX);
+ } else {
+ RtsFlags.GcFlags.maxHeapSize =
+ decodeSize(rts_argv[arg], 2, BLOCK_SIZE, HS_WORD_MAX)
+ / BLOCK_SIZE;
+ // user give size in *bytes* but "maxHeapSize" is in
+ // *blocks*
+ }
break;
case 'm':
if (strncmp("maxN", &rts_argv[arg][1], 4) == 0) {
OPTION_SAFE;
THREADED_BUILD_ONLY(
- int nNodes;
+ int nCapabilities;
int proc = (int)getNumberOfProcessors();
- nNodes = strtol(rts_argv[arg]+5, (char **) NULL, 10);
- if (nNodes > proc) { nNodes = proc; }
+ nCapabilities = strtol(rts_argv[arg]+5, (char **) NULL, 10);
+ if (nCapabilities > proc) { nCapabilities = proc; }
- if (nNodes <= 0) {
+ if (nCapabilities <= 0) {
errorBelch("bad value for -maxN");
- error = rtsTrue;
+ error = true;
}
#if defined(PROFILING)
- RtsFlags.ParFlags.nNodes = 1;
+ RtsFlags.ParFlags.nCapabilities = 1;
#else
- RtsFlags.ParFlags.nNodes = (nat)nNodes;
+ RtsFlags.ParFlags.nCapabilities = (uint32_t)nCapabilities;
#endif
) break;
} else {
case 'H':
OPTION_UNSAFE;
if (rts_argv[arg][2] == '\0') {
- RtsFlags.GcFlags.heapSizeSuggestionAuto = rtsTrue;
+ RtsFlags.GcFlags.heapSizeSuggestionAuto = true;
} else {
- RtsFlags.GcFlags.heapSizeSuggestion =
- (nat)(decodeSize(rts_argv[arg], 2, BLOCK_SIZE, HS_WORD_MAX) / BLOCK_SIZE);
+ RtsFlags.GcFlags.heapSizeSuggestion = (uint32_t)
+ (decodeSize(rts_argv[arg], 2, BLOCK_SIZE, HS_WORD_MAX)
+ / BLOCK_SIZE);
}
break;
case 'O':
OPTION_UNSAFE;
RtsFlags.GcFlags.minOldGenSize =
- (nat)(decodeSize(rts_argv[arg], 2, BLOCK_SIZE,
+ (uint32_t)(decodeSize(rts_argv[arg], 2, BLOCK_SIZE,
HS_WORD_MAX)
/ BLOCK_SIZE);
break;
} else {
Time t = fsecondsToTime(atof(rts_argv[arg]+2));
if (t == 0) {
- RtsFlags.GcFlags.doIdleGC = rtsFalse;
+ RtsFlags.GcFlags.doIdleGC = false;
} else {
- RtsFlags.GcFlags.doIdleGC = rtsTrue;
+ RtsFlags.GcFlags.doIdleGC = true;
RtsFlags.GcFlags.idleGCDelayTime = t;
}
}
}
r = openStatsFile(rts_argv[arg]+2, NULL,
&RtsFlags.GcFlags.statsFile);
- if (r == -1) { error = rtsTrue; }
+ if (r == -1) { error = true; }
}
break;
case 'Z':
OPTION_UNSAFE;
- RtsFlags.GcFlags.squeezeUpdFrames = rtsFalse;
+ RtsFlags.GcFlags.squeezeUpdFrames = false;
unchecked_arg_start++;
goto check_rest;
errorBelch("flag -Pa given an argument"
" when none was expected: %s"
,rts_argv[arg]);
- error = rtsTrue;
+ error = true;
}
break;
+ case 'j':
+ RtsFlags.CcFlags.doCostCentres = COST_CENTRES_JSON;
+ break;
+ case 'o':
+ if (rts_argv[arg][3] == '\0') {
+ errorBelch("flag -po expects an argument");
+ error = true;
+ break;
+ }
+ RtsFlags.CcFlags.outputFileNameStem = rts_argv[arg]+3;
+ break;
case '\0':
if (rts_argv[arg][1] == 'P') {
- RtsFlags.CcFlags.doCostCentres =
- COST_CENTRES_VERBOSE;
+ RtsFlags.CcFlags.doCostCentres = COST_CENTRES_VERBOSE;
} else {
- RtsFlags.CcFlags.doCostCentres =
- COST_CENTRES_SUMMARY;
+ RtsFlags.CcFlags.doCostCentres = COST_CENTRES_SUMMARY;
}
break;
default:
OPTION_SAFE;
THREADED_BUILD_ONLY(
if (rts_argv[arg][2] == '\0') {
-#if defined(PROFILING)
- RtsFlags.ParFlags.nNodes = 1;
-#else
- RtsFlags.ParFlags.nNodes = getNumberOfProcessors();
-#endif
+ RtsFlags.ParFlags.nCapabilities = getNumberOfProcessors();
} else {
- int nNodes;
+ int nCapabilities;
OPTION_SAFE; /* but see extra checks below... */
- nNodes = strtol(rts_argv[arg]+2, (char **) NULL, 10);
+ nCapabilities = strtol(rts_argv[arg]+2, (char **) NULL, 10);
- if (nNodes <= 0) {
+ if (nCapabilities <= 0) {
errorBelch("bad value for -N");
- error = rtsTrue;
+ error = true;
}
if (rtsOptsEnabled == RtsOptsSafeOnly &&
- nNodes > (int)getNumberOfProcessors()) {
+ nCapabilities > (int)getNumberOfProcessors()) {
errorRtsOptsDisabled("Using large values for -N is not allowed by default. %s");
stg_exit(EXIT_FAILURE);
}
- RtsFlags.ParFlags.nNodes = (nat)nNodes;
+ RtsFlags.ParFlags.nCapabilities = (uint32_t)nCapabilities;
}
) break;
switch (rts_argv[arg][2]) {
case '1':
// backwards compat only
- RtsFlags.ParFlags.parGcEnabled = rtsFalse;
+ RtsFlags.ParFlags.parGcEnabled = false;
break;
default:
errorBelch("unknown RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
break;
}
) break;
switch (rts_argv[arg][2]) {
case '\0':
errorBelch("incomplete RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
break;
case 'g':
if (rts_argv[arg][3] == '\0') {
- RtsFlags.ParFlags.parGcEnabled = rtsFalse;
+ RtsFlags.ParFlags.parGcEnabled = false;
} else {
- RtsFlags.ParFlags.parGcEnabled = rtsTrue;
+ RtsFlags.ParFlags.parGcEnabled = true;
RtsFlags.ParFlags.parGcGen
= strtol(rts_argv[arg]+3, (char **) NULL, 10);
}
case 'b':
if (rts_argv[arg][3] == '\0') {
RtsFlags.ParFlags.parGcLoadBalancingEnabled =
- rtsFalse;
+ false;
}
else {
RtsFlags.ParFlags.parGcLoadBalancingEnabled =
- rtsTrue;
+ true;
RtsFlags.ParFlags.parGcLoadBalancingGen
= strtol(rts_argv[arg]+3, (char **) NULL, 10);
}
RtsFlags.ParFlags.parGcNoSyncWithIdle
= strtol(rts_argv[arg]+3, (char **) NULL, 10);
break;
+ case 'n': {
+ int threads;
+ threads = strtol(rts_argv[arg]+3, (char **) NULL, 10);
+ if (threads <= 0) {
+ errorBelch("-qn must be 1 or greater");
+ error = true;
+ } else {
+ RtsFlags.ParFlags.parGcThreads = threads;
+ }
+ break;
+ }
case 'a':
- RtsFlags.ParFlags.setAffinity = rtsTrue;
+ RtsFlags.ParFlags.setAffinity = true;
break;
case 'm':
- RtsFlags.ParFlags.migrate = rtsFalse;
+ RtsFlags.ParFlags.migrate = false;
break;
case 'w':
// -qw was removed; accepted for backwards compat
break;
default:
errorBelch("unknown RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
break;
}
) break;
= strtol(rts_argv[arg]+2, (char **) NULL, 10);
if (RtsFlags.ParFlags.maxLocalSparks <= 0) {
errorBelch("bad value for -e");
- error = rtsTrue;
+ error = true;
}
}
) break;
OPTION_SAFE;
TICKY_BUILD_ONLY(
- RtsFlags.TickyFlags.showTickyStats = rtsTrue;
+ RtsFlags.TickyFlags.showTickyStats = true;
{
int r;
r = openStatsFile(rts_argv[arg]+2,
TICKY_FILENAME_FMT,
&RtsFlags.TickyFlags.tickyFile);
- if (r == -1) { error = rtsTrue; }
+ if (r == -1) { error = true; }
}
) break;
- /* =========== TRACING ---------=================== */
+ /* =========== OUTPUT ============================ */
+
+ case 'o':
+ switch(rts_argv[arg][2]) {
+ case 'l':
+ OPTION_SAFE;
+ TRACING_BUILD_ONLY(
+ if (strlen(&rts_argv[arg][3]) == 0) {
+ errorBelch("-ol expects filename");
+ error = true;
+ } else {
+ RtsFlags.TraceFlags.trace_output =
+ strdup(&rts_argv[arg][3]);
+ }
+ );
+ break;
+
+ default:
+ errorBelch("Unknown output flag -o%c", rts_argv[arg][2]);
+ error = true;
+ }
+ break;
+
+ /* =========== TRACING ============================ */
case 'l':
OPTION_SAFE;
case '\0':
OPTION_SAFE;
errorBelch("incomplete RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
break;
case 'b': /* heapBase in hex; undocumented */
OPTION_UNSAFE;
if (rts_argv[arg][3] != '\0') {
RtsFlags.GcFlags.heapBase
- = strtol(rts_argv[arg]+3, (char **) NULL, 16);
+ = strToStgWord(rts_argv[arg]+3, (char **) NULL, 0);
} else {
errorBelch("-xb: requires argument");
- error = rtsTrue;
+ error = true;
}
break;
#if defined(x86_64_HOST_ARCH)
+ case 'p': /* linkerAlwaysPic */
+ OPTION_UNSAFE;
+ RtsFlags.MiscFlags.linkerAlwaysPic = true;
+ break;
+
case 'm': /* linkerMemBase */
OPTION_UNSAFE;
if (rts_argv[arg][3] != '\0') {
= strtol(rts_argv[arg]+3, (char **) NULL, 16);
if (RtsFlags.MiscFlags.linkerMemBase > 0x80000000) {
errorBelch("-xm: value must be <80000000");
- error = rtsTrue;
+ error = true;
}
} else {
RtsFlags.MiscFlags.linkerMemBase = 0;
an exception */
OPTION_SAFE;
PROFILING_BUILD_ONLY(
- RtsFlags.ProfFlags.showCCSOnException = rtsTrue;
+ RtsFlags.ProfFlags.showCCSOnException = true;
);
unchecked_arg_start++;
goto check_rest;
case 't': /* Include memory used by TSOs in a heap profile */
OPTION_SAFE;
PROFILING_BUILD_ONLY(
- RtsFlags.ProfFlags.includeTSOs = rtsTrue;
+ RtsFlags.ProfFlags.includeTSOs = true;
);
unchecked_arg_start++;
goto check_rest;
default:
OPTION_SAFE;
errorBelch("unknown RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
break;
}
break; /* defensive programming */
/* check the rest to be sure there is nothing afterwards.*/
- /* see Trac #9839 */
+ /* see #9839 */
check_rest:
{
/* start checking from the first unchecked position,
* not from index 2*/
- /* see Trac #9839 */
+ /* see #9839 */
if (rts_argv[arg][unchecked_arg_start] != '\0') {
errorBelch("flag -%c given an argument"
" when none was expected: %s",
rts_argv[arg][1],rts_argv[arg]);
- error = rtsTrue;
+ error = true;
}
break;
}
default:
OPTION_SAFE;
errorBelch("unknown RTS option: %s",rts_argv[arg]);
- error = rtsTrue;
+ error = true;
break;
}
"of the stack chunk size (-kc)");
errorUsage();
}
+
+ if (RtsFlags.GcFlags.maxHeapSize != 0 &&
+ RtsFlags.GcFlags.heapSizeSuggestion >
+ RtsFlags.GcFlags.maxHeapSize) {
+ RtsFlags.GcFlags.maxHeapSize = RtsFlags.GcFlags.heapSizeSuggestion;
+ }
+
+ if (RtsFlags.GcFlags.maxHeapSize != 0 &&
+ RtsFlags.GcFlags.minAllocAreaSize >
+ RtsFlags.GcFlags.maxHeapSize) {
+ errorBelch("maximum heap size (-M) is smaller than minimum alloc area size (-A)");
+ RtsFlags.GcFlags.minAllocAreaSize = RtsFlags.GcFlags.maxHeapSize;
+ }
+
+ // If we have -A16m or larger, use -n4m.
+ if (RtsFlags.GcFlags.minAllocAreaSize >= (16*1024*1024) / BLOCK_SIZE) {
+ RtsFlags.GcFlags.nurseryChunkSize = (4*1024*1024) / BLOCK_SIZE;
+ }
+
+ if (RtsFlags.ParFlags.parGcLoadBalancingGen == ~0u) {
+ StgWord alloc_area_bytes
+ = RtsFlags.GcFlags.minAllocAreaSize * BLOCK_SIZE;
+
+ // If allocation area is larger that CPU cache
+ // we can finish scanning quicker doing work-stealing
+ // scan. #9221
+ // 32M looks big enough not to fit into L2 cache
+ // of popular modern CPUs.
+ if (alloc_area_bytes >= 32 * 1024 * 1024) {
+ RtsFlags.ParFlags.parGcLoadBalancingGen = 0;
+ } else {
+ RtsFlags.ParFlags.parGcLoadBalancingGen = 1;
+ }
+ }
+
+ // We can't generate dumps without signal handlers
+ if (RtsFlags.MiscFlags.generate_dump_file) {
+ RtsFlags.MiscFlags.install_seh_handlers = true;
+ }
}
static void errorUsage (void)
f = NULL; /* NULL means use debugBelch */
} else {
if (*filename != '\0') { /* stats file specified */
- f = fopen(filename,"w");
+ f = __rts_fopen (filename,"w");
} else {
+ if (filename_fmt == NULL) {
+ errorBelch("Invalid stats filename format (NULL)\n");
+ return -1;
+ }
/* default <program>.<ext> */
char stats_filename[STATS_FILENAME_MAXLEN];
- sprintf(stats_filename, filename_fmt, prog_name);
- f = fopen(stats_filename,"w");
+ snprintf(stats_filename, STATS_FILENAME_MAXLEN, filename_fmt,
+ prog_name);
+ f = __rts_fopen (stats_filename,"w");
}
if (f == NULL) {
errorBelch("Can't open stats file %s\n", filename);
-------------------------------------------------------------------------- */
static StgWord64
-decodeSize(const char *flag, nat offset, StgWord64 min, StgWord64 max)
+decodeSize(const char *flag, uint32_t offset, StgWord64 min, StgWord64 max)
{
char c;
const char *s;
return val;
}
-#ifdef DEBUG
+#if defined(DEBUG)
static void read_debug_flags(const char* arg)
{
// Already parsed "-D"
for (c = arg + 2; *c != '\0'; c++) {
switch (*c) {
case 's':
- RtsFlags.DebugFlags.scheduler = rtsTrue;
+ RtsFlags.DebugFlags.scheduler = true;
break;
case 'i':
- RtsFlags.DebugFlags.interpreter = rtsTrue;
+ RtsFlags.DebugFlags.interpreter = true;
break;
case 'w':
- RtsFlags.DebugFlags.weak = rtsTrue;
+ RtsFlags.DebugFlags.weak = true;
break;
case 'G':
- RtsFlags.DebugFlags.gccafs = rtsTrue;
+ RtsFlags.DebugFlags.gccafs = true;
break;
case 'g':
- RtsFlags.DebugFlags.gc = rtsTrue;
+ RtsFlags.DebugFlags.gc = true;
break;
case 'b':
- RtsFlags.DebugFlags.block_alloc = rtsTrue;
+ RtsFlags.DebugFlags.block_alloc = true;
break;
case 'S':
- RtsFlags.DebugFlags.sanity = rtsTrue;
+ RtsFlags.DebugFlags.sanity = true;
break;
case 't':
- RtsFlags.DebugFlags.stable = rtsTrue;
+ RtsFlags.DebugFlags.stable = true;
break;
case 'p':
- RtsFlags.DebugFlags.prof = rtsTrue;
+ RtsFlags.DebugFlags.prof = true;
break;
case 'l':
- RtsFlags.DebugFlags.linker = rtsTrue;
+ RtsFlags.DebugFlags.linker = true;
break;
case 'a':
- RtsFlags.DebugFlags.apply = rtsTrue;
+ RtsFlags.DebugFlags.apply = true;
break;
case 'm':
- RtsFlags.DebugFlags.stm = rtsTrue;
+ RtsFlags.DebugFlags.stm = true;
break;
case 'z':
- RtsFlags.DebugFlags.squeeze = rtsTrue;
+ RtsFlags.DebugFlags.squeeze = true;
break;
case 'c':
- RtsFlags.DebugFlags.hpc = rtsTrue;
+ RtsFlags.DebugFlags.hpc = true;
break;
case 'r':
- RtsFlags.DebugFlags.sparks = rtsTrue;
+ RtsFlags.DebugFlags.sparks = true;
+ break;
+ case 'C':
+ RtsFlags.DebugFlags.compact = true;
break;
default:
bad_option( arg );
}
#endif
-#ifdef PROFILING
+#if defined(PROFILING)
// Parse a "-h" flag, returning whether the parse resulted in an error.
-static rtsBool read_heap_profiling_flag(const char *arg_in)
+static bool read_heap_profiling_flag(const char *arg)
{
// Already parsed "-h"
- // For historical reasons the parser here mutates the arguments.
- // However, for sanity we want to guarantee const-correctness and parsing
- // really ought to be an immutable operation. To avoid rewriting the parser
- // we just operate on a temporary copy of the argument.
- char *arg = strdup(arg_in);
- rtsBool error = rtsFalse;
+ bool error = false;
switch (arg[2]) {
case '\0':
case 'C':
case 'r':
case 'B':
case 'b':
+ case 'T':
if (arg[2] != '\0' && arg[3] != '\0') {
{
- char *left = strchr(arg, '{');
- char *right = strrchr(arg, '}');
+ const char *left = strchr(arg, '{');
+ const char *right = strrchr(arg, '}');
// curly braces are optional, for
// backwards compat.
if (!right)
right = arg + strlen(arg);
- char *selector = strndup(left, right - left);
+ char *selector = stgStrndup(left, right - left + 1);
switch (arg[2]) {
case 'c': // cost centre label select
if (RtsFlags.ProfFlags.doHeapProfile != 0) {
errorBelch("multiple heap profile options");
- error = rtsTrue;
+ error = true;
break;
}
case 'b':
RtsFlags.ProfFlags.doHeapProfile = HEAP_BY_LDV;
break;
+ case 'T':
+ RtsFlags.ProfFlags.doHeapProfile = HEAP_BY_CLOSURE_TYPE;
+ break;
}
break;
default:
errorBelch("invalid heap profile option: %s", arg);
- error = rtsTrue;
+ error = true;
}
- free(arg);
return error;
}
#endif
static void read_trace_flags(const char *arg)
{
const char *c;
- rtsBool enabled = rtsTrue;
+ bool enabled = true;
/* Syntax for tracing flags currently looks like:
*
* -l To turn on eventlog tracing with default trace classes
* Similarly, in future we might default to slightly less verbose
* scheduler or GC tracing.
*/
- RtsFlags.TraceFlags.scheduler = rtsTrue;
- RtsFlags.TraceFlags.gc = rtsTrue;
- RtsFlags.TraceFlags.sparks_sampled = rtsTrue;
- RtsFlags.TraceFlags.user = rtsTrue;
+ RtsFlags.TraceFlags.scheduler = true;
+ RtsFlags.TraceFlags.gc = true;
+ RtsFlags.TraceFlags.sparks_sampled = true;
+ RtsFlags.TraceFlags.user = true;
for (c = arg; *c != '\0'; c++) {
switch(*c) {
case '\0':
break;
case '-':
- enabled = rtsFalse;
+ enabled = false;
break;
case 'a':
RtsFlags.TraceFlags.scheduler = enabled;
RtsFlags.TraceFlags.sparks_sampled = enabled;
RtsFlags.TraceFlags.sparks_full = enabled;
RtsFlags.TraceFlags.user = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
case 's':
RtsFlags.TraceFlags.scheduler = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
case 'p':
RtsFlags.TraceFlags.sparks_sampled = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
case 'f':
RtsFlags.TraceFlags.sparks_full = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
case 't':
RtsFlags.TraceFlags.timestamp = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
case 'g':
RtsFlags.TraceFlags.gc = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
case 'u':
RtsFlags.TraceFlags.user = enabled;
- enabled = rtsTrue;
+ enabled = true;
break;
default:
errorBelch("unknown trace option: %c",*c);
void
setProgArgv(int argc, char *argv[])
{
+ freeArgv(prog_argc,prog_argv);
prog_argc = argc;
prog_argv = copyArgv(argc,argv);
setProgName(prog_argv);
void
freeWin32ProgArgv (void)
{
- int i;
-
- if (win32_prog_argv != NULL) {
- for (i = 0; i < win32_prog_argc; i++) {
- stgFree(win32_prog_argv[i]);
- }
- stgFree(win32_prog_argv);
+ if(win32_utf8_argv == NULL) {
+ return;
+ }
+ else
+ {
+ freeArgv(win32_full_utf8_argc, win32_full_utf8_argv);
+ stgFree(win32_utf8_argv);
}
- win32_prog_argc = 0;
- win32_prog_argv = NULL;
-}
-void
-getWin32ProgArgv(int *argc, wchar_t **argv[])
-{
- *argc = win32_prog_argc;
- *argv = win32_prog_argv;
}
-void
-setWin32ProgArgv(int argc, wchar_t *argv[])
-{
- int i;
-
- freeWin32ProgArgv();
-
- win32_prog_argc = argc;
- if (argv == NULL) {
- win32_prog_argv = NULL;
- return;
- }
-
- win32_prog_argv = stgCallocBytes(argc + 1, sizeof (wchar_t *),
- "setWin32ProgArgv 1");
- for (i = 0; i < argc; i++) {
- win32_prog_argv[i] = stgMallocBytes((wcslen(argv[i]) + 1) * sizeof(wchar_t),
- "setWin32ProgArgv 2");
- wcscpy(win32_prog_argv[i], argv[i]);
- }
- win32_prog_argv[argc] = NULL;
-}
#endif
/* ----------------------------------------------------------------------------