1 /* -----------------------------------------------------------------------------
3 * (c) The GHC Team, 1998-2002
5 * Main function for a standalone Haskell program.
7 * ---------------------------------------------------------------------------*/
9 #include "PosixSource.h"
14 #include "OSThreads.h"
15 #include "Storage.h" /* initStorage, exitStorage */
16 #include "Schedule.h" /* initScheduler */
17 #include "Stats.h" /* initStats */
18 #include "STM.h" /* initSTM */
20 #include "RtsSignals.h"
21 #include "Timer.h" /* startTimer, stopTimer */
25 #include "Prelude.h" /* fixupRTStoPreludeRefs */
28 #include "ThreadLabels.h"
29 #include "BlockAlloc.h"
31 #include "RtsTypeable.h"
33 #if defined(RTS_GTK_FRONTPANEL)
34 #include "FrontPanel.h"
37 #if defined(PROFILING) || defined(DEBUG)
38 # include "Profiling.h"
39 # include "ProfHeap.h"
40 # include "RetainerProfile.h"
44 # include "GranSimRts.h"
47 #if defined(GRAN) || defined(PAR)
48 # include "ParallelRts.h"
52 # include "Parallel.h"
56 #if defined(mingw32_HOST_OS)
57 #include "win32/AsyncIO.h"
69 // Count of how many outstanding hs_init()s there have been.
70 static int hs_init_count
= 0;
72 // Here we save the terminal settings on the standard file
73 // descriptors, if we need to change them (eg. to support NoBuffering
75 static void *saved_termios
[3] = {NULL
,NULL
,NULL
};
78 __hscore_get_saved_termios(int fd
)
80 return (0 <= fd
&& fd
< (int)(sizeof(saved_termios
) / sizeof(*saved_termios
))) ?
81 saved_termios
[fd
] : NULL
;
85 __hscore_set_saved_termios(int fd
, void* ts
)
87 if (0 <= fd
&& fd
< (int)(sizeof(saved_termios
) / sizeof(*saved_termios
))) {
88 saved_termios
[fd
] = ts
;
92 /* -----------------------------------------------------------------------------
93 Initialise floating point unit on x86 (currently disabled. why?)
94 (see comment in ghc/compiler/nativeGen/MachInstrs.lhs).
95 -------------------------------------------------------------------------- */
97 #define X86_INIT_FPU 0
101 x86_init_fpu ( void )
103 __volatile
unsigned short int fpu_cw
;
105 // Grab the control word
106 __asm
__volatile ("fnstcw %0" : "=m" (fpu_cw
));
109 printf("fpu_cw: %x\n", fpu_cw
);
112 // Set bits 8-9 to 10 (64-bit precision).
113 fpu_cw
= (fpu_cw
& 0xfcff) | 0x0200;
115 // Store the new control word back
116 __asm
__volatile ("fldcw %0" : : "m" (fpu_cw
));
120 /* -----------------------------------------------------------------------------
122 -------------------------------------------------------------------------- */
125 hs_init(int *argc
, char **argv
[])
128 if (hs_init_count
> 1) {
129 // second and subsequent inits are ignored
133 /* The very first thing we do is grab the start time...just in case we're
134 * collecting timing statistics.
140 * The parallel system needs to be initialised and synchronised before
141 * the program is run.
143 startupParallelSystem(argv
);
145 if (*argv
[0] == '-') { /* Strip off mainPE flag argument */
150 argv
[1] = argv
[0]; /* ignore the nPEs argument */
154 /* Set the RTS flags to default values. */
155 initRtsFlagsDefaults();
157 /* Call the user hook to reset defaults, if present */
160 /* Parse the flags, separating the RTS flags from the programs args */
161 if (argc
!= NULL
&& argv
!= NULL
) {
162 setupRtsFlags(argc
, *argv
, &rts_argc
, rts_argv
);
163 setProgArgv(*argc
,*argv
);
166 /* initTracing must be after setupRtsFlags() */
170 /* NB: this really must be done after processing the RTS flags */
171 IF_PAR_DEBUG(verbose
,
172 debugBelch("==== Synchronising system (%d PEs)\n", nPEs
));
173 synchroniseSystem(); // calls initParallelSystem etc
176 /* Perform initialisation of adjustor thunk layer. */
179 /* initialise scheduler data structures (needs to be done before
185 /* And start GranSim profiling if required: */
186 if (RtsFlags
.GranFlags
.GranSimStats
.Full
)
187 init_gr_simulation(rts_argc
, rts_argv
, prog_argc
, prog_argv
);
189 /* And start GUM profiling if required: */
190 if (RtsFlags
.ParFlags
.ParStats
.Full
)
191 init_gr_simulation(rts_argc
, rts_argv
, prog_argc
, prog_argv
);
192 #endif /* PAR || GRAN */
194 /* initialize the storage manager */
197 /* initialise the stable pointer table */
198 initStablePtrTable();
200 /* initialise the shared Typeable store */
204 /* initialise thread label table (tso->char*) */
205 initThreadLabelTable();
208 #if defined(PROFILING) || defined(DEBUG)
212 /* start the virtual timer 'subsystem'. */
215 /* Initialise the stats department */
218 #if defined(RTS_USER_SIGNALS)
219 /* Initialise the user signal handler set */
221 /* Set up handler to run on SIGINT, etc. */
222 initDefaultHandlers();
225 #if defined(mingw32_HOST_OS)
229 #ifdef RTS_GTK_FRONTPANEL
230 if (RtsFlags
.GcFlags
.frontpanel
) {
239 #if defined(THREADED_RTS) && !defined(mingw32_HOST_OS)
243 /* Record initialization times */
247 // Compatibility interface
249 startupHaskell(int argc
, char *argv
[], void (*init_root
)(void))
251 hs_init(&argc
, &argv
);
253 hs_add_root(init_root
);
257 /* -----------------------------------------------------------------------------
258 Per-module initialisation
260 This process traverses all the compiled modules in the program
261 starting with "Main", and performing per-module initialisation for
264 So far, two things happen at initialisation time:
266 - we register stable names for each foreign-exported function
267 in that module. This prevents foreign-exported entities, and
268 things they depend on, from being garbage collected.
270 - we supply a unique integer to each statically declared cost
271 centre and cost centre stack in the program.
273 The code generator inserts a small function "__stginit_<module>" in each
274 module and calls the registration functions in each of the modules it
277 The init* functions are compiled in the same way as STG code,
278 i.e. without normal C call/return conventions. Hence we must use
279 StgRun to call this stuff.
280 -------------------------------------------------------------------------- */
282 /* The init functions use an explicit stack...
284 #define INIT_STACK_BLOCKS 4
285 static F_
*init_stack
= NULL
;
288 hs_add_root(void (*init_root
)(void))
292 Capability
*cap
= &MainCapability
;
294 if (hs_init_count
<= 0) {
295 barf("hs_add_root() must be called after hs_init()");
298 /* The initialisation stack grows downward, with sp pointing
299 to the last occupied word */
300 init_sp
= INIT_STACK_BLOCKS
*BLOCK_SIZE_W
;
301 bd
= allocGroup_lock(INIT_STACK_BLOCKS
);
302 init_stack
= (F_
*)bd
->start
;
303 init_stack
[--init_sp
] = (F_
)stg_init_finish
;
304 if (init_root
!= NULL
) {
305 init_stack
[--init_sp
] = (F_
)init_root
;
308 cap
->r
.rSp
= (P_
)(init_stack
+ init_sp
);
309 StgRun((StgFunPtr
)stg_init
, &cap
->r
);
313 #if defined(PROFILING) || defined(DEBUG)
314 // This must be done after module initialisation.
315 // ToDo: make this work in the presence of multiple hs_add_root()s.
320 /* -----------------------------------------------------------------------------
321 Shutting down the RTS
322 -------------------------------------------------------------------------- */
327 if (hs_init_count
<= 0) {
328 errorBelch("warning: too many hs_exit()s");
332 if (hs_init_count
> 0) {
333 // ignore until it's the last one
337 /* start timing the shutdown */
340 #if defined(THREADED_RTS) && !defined(mingw32_HOST_OS)
344 /* stop all running tasks */
348 /* end_gr_simulation prints global stats if requested -- HWL */
349 if (!RtsFlags
.GranFlags
.GranSimStats
.Suppressed
)
353 /* stop the ticker */
356 /* reset the standard file descriptors to blocking mode */
357 resetNonBlockingFd(0);
358 resetNonBlockingFd(1);
359 resetNonBlockingFd(2);
362 // Reset the terminal settings on the standard file descriptors,
363 // if we changed them. See System.Posix.Internals.tcSetAttr for
364 // more details, including the reason we termporarily disable
368 sigset_t sigset
, old_sigset
;
369 sigemptyset(&sigset
);
370 sigaddset(&sigset
, SIGTTOU
);
371 sigprocmask(SIG_BLOCK
, &sigset
, &old_sigset
);
372 for (fd
= 0; fd
<= 2; fd
++) {
373 struct termios
* ts
= (struct termios
*)__hscore_get_saved_termios(fd
);
375 tcsetattr(fd
,TCSANOW
,ts
);
378 sigprocmask(SIG_SETMASK
, &old_sigset
, NULL
);
383 /* controlled exit; good thread! */
384 shutdownParallelSystem(0);
386 /* global statistics in parallel system */
390 /* stop timing the shutdown, we're about to print stats */
393 // clean up things from the storage manager's point of view.
394 // also outputs the stats (+RTS -s) info.
397 /* free shared Typeable store */
400 /* initialise the stable pointer table */
401 exitStablePtrTable();
403 /* free hash table storage */
406 #ifdef RTS_GTK_FRONTPANEL
407 if (RtsFlags
.GcFlags
.frontpanel
) {
412 #if defined(PROFILING)
413 reportCCSProfiling();
416 #if defined(PROFILING) || defined(DEBUG)
421 // Originally, this was in report_ccs_profiling(). Now, retainer
422 // profiling might tack some extra stuff on to the end of this file
423 // during endProfiling().
427 #if defined(TICKY_TICKY)
428 if (RtsFlags
.TickyFlags
.showTickyStats
) PrintTickyInfo();
431 #if defined(mingw32_HOST_OS)
435 // Finally, free all our storage.
439 // Compatibility interfaces
441 shutdownHaskell(void)
447 shutdownHaskellAndExit(int n
)
449 if (hs_init_count
== 1) {
453 /* really exit (stg_exit() would call shutdownParallelSystem() again) */
462 * called from STG-land to exit the program
466 static int exit_started
=rtsFalse
;
469 void (*exitFn
)(int) = 0;
475 /* HACK: avoid a loop when exiting due to a stupid error */
478 exit_started
=rtsTrue
;
480 IF_PAR_DEBUG(verbose
, debugBelch("==-- stg_exit %d on [%x]...", n
, mytid
));
481 shutdownParallelSystem(n
);