1 /* ----------------------------------------------------------------------------
2  *
3  * (c) The GHC Team, 1998-2004
4  *
5  * API for invoking Haskell functions via the RTS
6  *
7  * To understand the structure of the RTS headers, see the wiki:
8  *   http://ghc.haskell.org/trac/ghc/wiki/Commentary/SourceTree/Includes
9  *
10  * --------------------------------------------------------------------------*/
11 
12 #pragma once
13 
14 #if defined(__cplusplus)
15 extern "C" {
16 #endif
17 
18 #include "HsFFI.h"
19 #include "rts/Time.h"
20 #include "rts/EventLogWriter.h"
21 
22 /*
23  * Running the scheduler
24  */
25 typedef enum {
26     NoStatus,    /* not finished yet */
27     Success,     /* completed successfully */
28     Killed,      /* uncaught exception */
29     Interrupted, /* stopped in response to a call to interruptStgRts */
30     HeapExhausted /* out of memory */
31 } SchedulerStatus;
32 
33 typedef struct StgClosure_ *HaskellObj;
34 
35 /*
36  * An abstract type representing the token returned by rts_lock() and
37  * used when allocating objects and threads in the RTS.
38  */
39 typedef struct Capability_ Capability;
40 
41 /*
42  * The public view of a Capability: we can be sure it starts with
43  * these two components (but it may have more private fields).
44  */
45 typedef struct CapabilityPublic_ {
46     StgFunTable f;
47     StgRegTable r;
48 } CapabilityPublic;
49 
50 /* ----------------------------------------------------------------------------
51    RTS configuration settings, for passing to hs_init_ghc()
52    ------------------------------------------------------------------------- */
53 
54 typedef enum {
55     RtsOptsNone,         // +RTS causes an error
56     RtsOptsIgnore,       // Ignore command line arguments
57     RtsOptsIgnoreAll,    // Ignore command line and Environment arguments
58     RtsOptsSafeOnly,     // safe RTS options allowed; others cause an error
59     RtsOptsAll           // all RTS options allowed
60   } RtsOptsEnabledEnum;
61 
62 struct GCDetails_;
63 
64 // The RtsConfig struct is passed (by value) to hs_init_ghc().  The
65 // reason for using a struct is extensibility: we can add more
66 // fields to this later without breaking existing client code.
67 typedef struct {
68 
69     // Whether to interpret +RTS options on the command line
70     RtsOptsEnabledEnum rts_opts_enabled;
71 
72     // Whether to give RTS flag suggestions
73     HsBool rts_opts_suggestions;
74 
75     // additional RTS options
76     const char *rts_opts;
77 
78     // True if GHC was not passed -no-hs-main
79     HsBool rts_hs_main;
80 
81     // Whether to retain CAFs (default: false)
82     HsBool keep_cafs;
83 
84     // Writer a for eventlog.
85     const EventLogWriter *eventlog_writer;
86 
87     // Called before processing command-line flags, so that default
88     // settings for RtsFlags can be provided.
89     void (* defaultsHook) (void);
90 
91     // Called just before exiting
92     void (* onExitHook) (void);
93 
94     // Called on a stack overflow, before exiting
95     void (* stackOverflowHook) (W_ stack_size);
96 
97     // Called on heap overflow, before exiting
98     void (* outOfHeapHook) (W_ request_size, W_ heap_size);
99 
100     // Called when malloc() fails, before exiting
101     void (* mallocFailHook) (W_ request_size /* in bytes */, const char *msg);
102 
103     // Called for every GC
104     void (* gcDoneHook) (const struct GCDetails_ *stats);
105 
106     // Called when GC sync takes too long (+RTS --long-gc-sync=<time>)
107     void (* longGCSync) (uint32_t this_cap, Time time_ns);
108     void (* longGCSyncEnd) (Time time_ns);
109 } RtsConfig;
110 
111 // Clients should start with defaultRtsConfig and then customise it.
112 // Bah, I really wanted this to be a const struct value, but it seems
113 // you can't do that in C (it generates code).
114 extern const RtsConfig defaultRtsConfig;
115 
116 /* -----------------------------------------------------------------------------
117    Statistics
118    -------------------------------------------------------------------------- */
119 
120 //
121 // Stats about a single GC
122 //
123 typedef struct GCDetails_ {
124     // The generation number of this GC
125   uint32_t gen;
126     // Number of threads used in this GC
127   uint32_t threads;
128     // Number of bytes allocated since the previous GC
129   uint64_t allocated_bytes;
130     // Total amount of live data in the heap (incliudes large + compact data).
131     // Updated after every GC. Data in uncollected generations (in minor GCs)
132     // are considered live.
133   uint64_t live_bytes;
134     // Total amount of live data in large objects
135   uint64_t large_objects_bytes;
136     // Total amount of live data in compact regions
137   uint64_t compact_bytes;
138     // Total amount of slop (wasted memory)
139   uint64_t slop_bytes;
140     // Total amount of memory in use by the RTS
141   uint64_t mem_in_use_bytes;
142     // Total amount of data copied during this GC
143   uint64_t copied_bytes;
144     // In parallel GC, the max amount of data copied by any one thread
145   uint64_t par_max_copied_bytes;
146   // In parallel GC, the amount of balanced data copied by all threads
147   uint64_t par_balanced_copied_bytes;
148     // The time elapsed during synchronisation before GC
149   Time sync_elapsed_ns;
150     // The CPU time used during GC itself
151   Time cpu_ns;
152     // The time elapsed during GC itself
153   Time elapsed_ns;
154 } GCDetails;
155 
156 //
157 // Stats about the RTS currently, and since the start of execution
158 //
159 typedef struct _RTSStats {
160 
161   // -----------------------------------
162   // Cumulative stats about memory use
163 
164     // Total number of GCs
165   uint32_t gcs;
166     // Total number of major (oldest generation) GCs
167   uint32_t major_gcs;
168     // Total bytes allocated
169   uint64_t allocated_bytes;
170     // Maximum live data (including large objects + compact regions) in the
171     // heap. Updated after a major GC.
172   uint64_t max_live_bytes;
173     // Maximum live data in large objects
174   uint64_t max_large_objects_bytes;
175     // Maximum live data in compact regions
176   uint64_t max_compact_bytes;
177     // Maximum slop
178   uint64_t max_slop_bytes;
179     // Maximum memory in use by the RTS
180   uint64_t max_mem_in_use_bytes;
181     // Sum of live bytes across all major GCs.  Divided by major_gcs
182     // gives the average live data over the lifetime of the program.
183   uint64_t cumulative_live_bytes;
184     // Sum of copied_bytes across all GCs
185   uint64_t copied_bytes;
186     // Sum of copied_bytes across all parallel GCs
187   uint64_t par_copied_bytes;
188     // Sum of par_max_copied_bytes across all parallel GCs
189   uint64_t cumulative_par_max_copied_bytes;
190     // Sum of par_balanced_copied_byes across all parallel GCs.
191   uint64_t cumulative_par_balanced_copied_bytes;
192 
193   // -----------------------------------
194   // Cumulative stats about time use
195   // (we use signed values here because due to inaccuracies in timers
196   // the values can occasionally go slightly negative)
197 
198     // Total CPU time used by the init phase
199   Time init_cpu_ns;
200     // Total elapsed time used by the init phase
201   Time init_elapsed_ns;
202     // Total CPU time used by the mutator
203   Time mutator_cpu_ns;
204     // Total elapsed time used by the mutator
205   Time mutator_elapsed_ns;
206     // Total CPU time used by the GC
207   Time gc_cpu_ns;
208     // Total elapsed time used by the GC
209   Time gc_elapsed_ns;
210     // Total CPU time (at the previous GC)
211   Time cpu_ns;
212     // Total elapsed time (at the previous GC)
213   Time elapsed_ns;
214 
215   // -----------------------------------
216   // Stats about the most recent GC
217 
218   GCDetails gc;
219 
220   // -----------------------------------
221   // Internal Counters
222 
223     // The number of times a GC thread spun on its 'gc_spin' lock.
224     // Will be zero if the rts was not built with PROF_SPIN
225   uint64_t gc_spin_spin;
226     // The number of times a GC thread yielded on its 'gc_spin' lock.
227     // Will be zero if the rts was not built with PROF_SPIN
228   uint64_t gc_spin_yield;
229     // The number of times a GC thread spun on its 'mut_spin' lock.
230     // Will be zero if the rts was not built with PROF_SPIN
231   uint64_t mut_spin_spin;
232     // The number of times a GC thread yielded on its 'mut_spin' lock.
233     // Will be zero if the rts was not built with PROF_SPIN
234   uint64_t mut_spin_yield;
235     // The number of times a GC thread has checked for work across all parallel
236     // GCs
237   uint64_t any_work;
238     // The number of times a GC thread has checked for work and found none
239     // across all parallel GCs
240   uint64_t no_work;
241     // The number of times a GC thread has iterated it's outer loop across all
242     // parallel GCs
243   uint64_t scav_find_work;
244 } RTSStats;
245 
246 void getRTSStats (RTSStats *s);
247 int getRTSStatsEnabled (void);
248 
249 // Returns the total number of bytes allocated since the start of the program.
250 // TODO: can we remove this?
251 uint64_t getAllocations (void);
252 
253 /* ----------------------------------------------------------------------------
254    Starting up and shutting down the Haskell RTS.
255    ------------------------------------------------------------------------- */
256 
257 /* DEPRECATED, use hs_init() or hs_init_ghc() instead  */
258 extern void startupHaskell         ( int argc, char *argv[],
259                                      void (*init_root)(void) );
260 
261 /* DEPRECATED, use hs_exit() instead  */
262 extern void shutdownHaskell        ( void );
263 
264 /* Like hs_init(), but allows rtsopts. For more complicated usage,
265  * use hs_init_ghc. */
266 extern void hs_init_with_rtsopts (int *argc, char **argv[]);
267 
268 /*
269  * GHC-specific version of hs_init() that allows specifying whether
270  * +RTS ... -RTS options are allowed or not (default: only "safe"
271  * options are allowed), and allows passing an option string that is
272  * to be interpreted by the RTS only, not passed to the program.
273  */
274 extern void hs_init_ghc (int *argc, char **argv[],   // program arguments
275                          RtsConfig rts_config);      // RTS configuration
276 
277 extern void shutdownHaskellAndExit (int exitCode, int fastExit)
278     GNUC3_ATTRIBUTE(__noreturn__);
279 
280 #if !defined(mingw32_HOST_OS)
281 extern void shutdownHaskellAndSignal (int sig, int fastExit)
282      GNUC3_ATTRIBUTE(__noreturn__);
283 #endif
284 
285 extern void getProgArgv            ( int *argc, char **argv[] );
286 extern void setProgArgv            ( int argc, char *argv[] );
287 extern void getFullProgArgv        ( int *argc, char **argv[] );
288 extern void setFullProgArgv        ( int argc, char *argv[] );
289 extern void freeFullProgArgv       ( void ) ;
290 
291 /* exit() override */
292 extern void (*exitFn)(int);
293 
294 /* ----------------------------------------------------------------------------
295    Locking.
296 
297    You have to surround all access to the RtsAPI with these calls.
298    ------------------------------------------------------------------------- */
299 
300 // acquires a token which may be used to create new objects and
301 // evaluate them.
302 Capability *rts_lock (void);
303 
304 // releases the token acquired with rts_lock().
305 void rts_unlock (Capability *token);
306 
307 // If you are in a context where you know you have a current capability but
308 // do not know what it is, then use this to get it. Basically this only
309 // applies to "unsafe" foreign calls (as unsafe foreign calls are made with
310 // the capability held).
311 //
312 // WARNING: There is *no* guarantee this returns anything sensible (eg NULL)
313 // when there is no current capability.
314 Capability *rts_unsafeGetMyCapability (void);
315 
316 /* ----------------------------------------------------------------------------
317    Which cpu should the OS thread and Haskell thread run on?
318 
319    1. Run the current thread on the given capability:
320      rts_setInCallCapability(cap, 0);
321 
322    2. Run the current thread on the given capability and set the cpu affinity
323       for this thread:
324      rts_setInCallCapability(cap, 1);
325 
326    3. Run the current thread on the given numa node:
327      rts_pinThreadToNumaNode(node);
328 
329    4. Run the current thread on the given capability and on the given numa node:
330      rts_setInCallCapability(cap, 0);
331      rts_pinThreadToNumaNode(cap);
332    ------------------------------------------------------------------------- */
333 
334 // Specify the Capability that the current OS thread should run on when it calls
335 // into Haskell.  The actual capability will be calculated as the supplied
336 // value modulo the number of enabled Capabilities.
337 //
338 // Note that the thread may still be migrated by the RTS scheduler, but that
339 // will only happen if there are multiple threads running on one Capability and
340 // another Capability is free.
341 //
342 // If affinity is non-zero, the current thread will be bound to
343 // specific CPUs according to the prevailing affinity policy for the
344 // specified capability, set by either +RTS -qa or +RTS --numa.
345 void rts_setInCallCapability (int preferred_capability, int affinity);
346 
347 // Specify the CPU Node that the current OS thread should run on when it calls
348 // into Haskell. The argument can be either a node number or capability number.
349 // The actual node will be calculated as the supplied value modulo the number
350 // of numa nodes.
351 void rts_pinThreadToNumaNode (int node);
352 
353 /* ----------------------------------------------------------------------------
354    Building Haskell objects from C datatypes.
355    ------------------------------------------------------------------------- */
356 HaskellObj   rts_mkChar       ( Capability *, HsChar   c );
357 HaskellObj   rts_mkInt        ( Capability *, HsInt    i );
358 HaskellObj   rts_mkInt8       ( Capability *, HsInt8   i );
359 HaskellObj   rts_mkInt16      ( Capability *, HsInt16  i );
360 HaskellObj   rts_mkInt32      ( Capability *, HsInt32  i );
361 HaskellObj   rts_mkInt64      ( Capability *, HsInt64  i );
362 HaskellObj   rts_mkWord       ( Capability *, HsWord   w );
363 HaskellObj   rts_mkWord8      ( Capability *, HsWord8  w );
364 HaskellObj   rts_mkWord16     ( Capability *, HsWord16 w );
365 HaskellObj   rts_mkWord32     ( Capability *, HsWord32 w );
366 HaskellObj   rts_mkWord64     ( Capability *, HsWord64 w );
367 HaskellObj   rts_mkPtr        ( Capability *, HsPtr    a );
368 HaskellObj   rts_mkFunPtr     ( Capability *, HsFunPtr a );
369 HaskellObj   rts_mkFloat      ( Capability *, HsFloat  f );
370 HaskellObj   rts_mkDouble     ( Capability *, HsDouble f );
371 HaskellObj   rts_mkStablePtr  ( Capability *, HsStablePtr s );
372 HaskellObj   rts_mkBool       ( Capability *, HsBool   b );
373 HaskellObj   rts_mkString     ( Capability *, char    *s );
374 
375 HaskellObj   rts_apply        ( Capability *, HaskellObj, HaskellObj );
376 
377 /* ----------------------------------------------------------------------------
378    Deconstructing Haskell objects
379    ------------------------------------------------------------------------- */
380 HsChar       rts_getChar      ( HaskellObj );
381 HsInt        rts_getInt       ( HaskellObj );
382 HsInt8       rts_getInt8      ( HaskellObj );
383 HsInt16      rts_getInt16     ( HaskellObj );
384 HsInt32      rts_getInt32     ( HaskellObj );
385 HsInt64      rts_getInt64     ( HaskellObj );
386 HsWord       rts_getWord      ( HaskellObj );
387 HsWord8      rts_getWord8     ( HaskellObj );
388 HsWord16     rts_getWord16    ( HaskellObj );
389 HsWord32     rts_getWord32    ( HaskellObj );
390 HsWord64     rts_getWord64    ( HaskellObj );
391 HsPtr        rts_getPtr       ( HaskellObj );
392 HsFunPtr     rts_getFunPtr    ( HaskellObj );
393 HsFloat      rts_getFloat     ( HaskellObj );
394 HsDouble     rts_getDouble    ( HaskellObj );
395 HsStablePtr  rts_getStablePtr ( HaskellObj );
396 HsBool       rts_getBool      ( HaskellObj );
397 
398 /* ----------------------------------------------------------------------------
399    Evaluating Haskell expressions
400 
401    The versions ending in '_' allow you to specify an initial stack size.
402    Note that these calls may cause Garbage Collection, so all HaskellObj
403    references are rendered invalid by these calls.
404 
405    All of these functions take a (Capability **) - there is a
406    Capability pointer both input and output.  We use an inout
407    parameter because this is less error-prone for the client than a
408    return value - the client could easily forget to use the return
409    value, whereas incorrectly using an inout parameter will usually
410    result in a type error.
411    ------------------------------------------------------------------------- */
412 
413 void rts_eval (/* inout */ Capability **,
414                /* in    */ HaskellObj p,
415                /* out */   HaskellObj *ret);
416 
417 void rts_eval_ (/* inout */ Capability **,
418                 /* in    */ HaskellObj p,
419                 /* in    */ unsigned int stack_size,
420                 /* out   */ HaskellObj *ret);
421 
422 void rts_evalIO (/* inout */ Capability **,
423                  /* in    */ HaskellObj p,
424                  /* out */   HaskellObj *ret);
425 
426 void rts_evalStableIOMain (/* inout */ Capability **,
427                            /* in    */ HsStablePtr s,
428                            /* out */   HsStablePtr *ret);
429 
430 void rts_evalStableIO (/* inout */ Capability **,
431                        /* in    */ HsStablePtr s,
432                        /* out */   HsStablePtr *ret);
433 
434 void rts_evalLazyIO (/* inout */ Capability **,
435                      /* in    */ HaskellObj p,
436                      /* out */   HaskellObj *ret);
437 
438 void rts_evalLazyIO_ (/* inout */ Capability **,
439                       /* in    */ HaskellObj p,
440                       /* in    */ unsigned int stack_size,
441                       /* out   */ HaskellObj *ret);
442 
443 void rts_checkSchedStatus (char* site, Capability *);
444 
445 SchedulerStatus rts_getSchedStatus (Capability *cap);
446 
447 /*
448  * The RTS allocates some thread-local data when you make a call into
449  * Haskell using one of the rts_eval() functions.  This data is not
450  * normally freed until hs_exit().  If you want to free it earlier
451  * than this, perhaps because the thread is about to exit, then call
452  * rts_done() from the thread.
453  *
454  * It is safe to make more rts_eval() calls after calling rts_done(),
455  * but the next one will cause allocation of the thread-local memory
456  * again.
457  */
458 void rts_done (void);
459 
460 /* --------------------------------------------------------------------------
461    Wrapper closures
462 
463    These are used by foreign export and foreign import "wrapper" stubs.
464    ----------------------------------------------------------------------- */
465 
466 // When producing Windows DLLs the we need to know which symbols are in the
467 //      local package/DLL vs external ones.
468 //
469 //      Note that RtsAPI.h is also included by foreign export stubs in
470 //      the base package itself.
471 //
472 #if defined(COMPILING_WINDOWS_DLL) && !defined(COMPILING_BASE_PACKAGE)
473 __declspec(dllimport) extern StgWord base_GHCziTopHandler_runIO_closure[];
474 __declspec(dllimport) extern StgWord base_GHCziTopHandler_runNonIO_closure[];
475 #else
476 extern StgWord base_GHCziTopHandler_runIO_closure[];
477 extern StgWord base_GHCziTopHandler_runNonIO_closure[];
478 #endif
479 
480 #define runIO_closure     base_GHCziTopHandler_runIO_closure
481 #define runNonIO_closure  base_GHCziTopHandler_runNonIO_closure
482 
483 /* ------------------------------------------------------------------------ */
484 
485 #if defined(__cplusplus)
486 }
487 #endif
488