1 /* ----------------------------------------------------------------------------
3 * (c) The GHC Team, 1998-2004
5 * API for invoking Haskell functions via the RTS
7 * To understand the structure of the RTS headers, see the wiki:
8 * http://ghc.haskell.org/trac/ghc/wiki/Commentary/SourceTree/Includes
10 * --------------------------------------------------------------------------*/
22 * Running the scheduler
25 NoStatus
, /* not finished yet */
26 Success
, /* completed successfully */
27 Killed
, /* uncaught exception */
28 Interrupted
, /* stopped in response to a call to interruptStgRts */
29 HeapExhausted
/* out of memory */
32 typedef struct StgClosure_
*HaskellObj
;
35 * An abstract type representing the token returned by rts_lock() and
36 * used when allocating objects and threads in the RTS.
38 typedef struct Capability_ Capability
;
41 * The public view of a Capability: we can be sure it starts with
42 * these two components (but it may have more private fields).
44 typedef struct CapabilityPublic_
{
49 /* ----------------------------------------------------------------------------
50 RTS configuration settings, for passing to hs_init_ghc()
51 ------------------------------------------------------------------------- */
54 RtsOptsNone
, // +RTS causes an error
55 RtsOptsSafeOnly
, // safe RTS options allowed; others cause an error
56 RtsOptsAll
// all RTS options allowed
59 // The RtsConfig struct is passed (by value) to hs_init_ghc(). The
60 // reason for using a struct is extensibility: we can add more
61 // fields to this later without breaking existing client code.
64 // Whether to interpret +RTS options on the command line
65 RtsOptsEnabledEnum rts_opts_enabled
;
67 // Whether to give RTS flag suggestions
68 HsBool rts_opts_suggestions
;
70 // additional RTS options
73 // True if GHC was not passed -no-hs-main
76 // Whether to retain CAFs (default: false)
79 // Called before processing command-line flags, so that default
80 // settings for RtsFlags can be provided.
81 void (* defaultsHook
) (void);
83 // Called just before exiting
84 void (* onExitHook
) (void);
86 // Called on a stack overflow, before exiting
87 void (* stackOverflowHook
) (W_ stack_size
);
89 // Called on heap overflow, before exiting
90 void (* outOfHeapHook
) (W_ request_size
, W_ heap_size
);
92 // Called when malloc() fails, before exiting
93 void (* mallocFailHook
) (W_ request_size
/* in bytes */, const char *msg
);
95 // Called for every GC
96 void (* gcDoneHook
) (unsigned int gen
,
97 W_ allocated_bytes
, /* since last GC */
100 W_ max_copied_per_thread_bytes
,
103 W_ sync_elapsed_ns
, W_ elapsed_ns
, W_ cpu_ns
);
107 // Clients should start with defaultRtsConfig and then customise it.
108 // Bah, I really wanted this to be a const struct value, but it seems
109 // you can't do that in C (it generates code).
110 extern const RtsConfig defaultRtsConfig
;
112 /* ----------------------------------------------------------------------------
113 Starting up and shutting down the Haskell RTS.
114 ------------------------------------------------------------------------- */
116 /* DEPRECATED, use hs_init() or hs_init_ghc() instead */
117 extern void startupHaskell ( int argc
, char *argv
[],
118 void (*init_root
)(void) );
120 /* DEPRECATED, use hs_exit() instead */
121 extern void shutdownHaskell ( void );
123 /* Like hs_init(), but allows rtsopts. For more complicated usage,
124 * use hs_init_ghc. */
125 extern void hs_init_with_rtsopts (int *argc
, char **argv
[]);
128 * GHC-specific version of hs_init() that allows specifying whether
129 * +RTS ... -RTS options are allowed or not (default: only "safe"
130 * options are allowed), and allows passing an option string that is
131 * to be interpreted by the RTS only, not passed to the program.
133 extern void hs_init_ghc (int *argc
, char **argv
[], // program arguments
134 RtsConfig rts_config
); // RTS configuration
136 extern void shutdownHaskellAndExit (int exitCode
, int fastExit
)
137 GNUC3_ATTRIBUTE(__noreturn__
);
139 #ifndef mingw32_HOST_OS
140 extern void shutdownHaskellAndSignal (int sig
, int fastExit
)
141 GNUC3_ATTRIBUTE(__noreturn__
);
144 extern void getProgArgv ( int *argc
, char **argv
[] );
145 extern void setProgArgv ( int argc
, char *argv
[] );
146 extern void getFullProgArgv ( int *argc
, char **argv
[] );
147 extern void setFullProgArgv ( int argc
, char *argv
[] );
148 extern void freeFullProgArgv ( void ) ;
150 /* exit() override */
151 extern void (*exitFn
)(int);
153 /* ----------------------------------------------------------------------------
156 You have to surround all access to the RtsAPI with these calls.
157 ------------------------------------------------------------------------- */
159 // acquires a token which may be used to create new objects and
161 Capability
*rts_lock (void);
163 // releases the token acquired with rts_lock().
164 void rts_unlock (Capability
*token
);
166 // If you are in a context where you know you have a current capability but
167 // do not know what it is, then use this to get it. Basically this only
168 // applies to "unsafe" foreign calls (as unsafe foreign calls are made with
169 // the capability held).
171 // WARNING: There is *no* guarantee this returns anything sensible (eg NULL)
172 // when there is no current capability.
173 Capability
*rts_unsafeGetMyCapability (void);
175 // Specify the Capability that the current OS thread should run on when it calls
176 // into Haskell. The actual capability will be calculated as the supplied
177 // value modulo the number of enabled Capabilities.
179 // Note that the thread may still be migrated by the RTS scheduler, but that
180 // will only happen if there are multiple threads running on one Capability and
181 // another Capability is free.
183 // If affinity is non-zero, the current thread will be bound to
184 // specific CPUs according to the prevailing affinity policy for the
185 // specified capability, set by either +RTS -qa or +RTS --numa.
186 void rts_setInCallCapability (int preferred_capability
, int affinity
);
188 /* ----------------------------------------------------------------------------
189 Building Haskell objects from C datatypes.
190 ------------------------------------------------------------------------- */
191 HaskellObj
rts_mkChar ( Capability
*, HsChar c
);
192 HaskellObj
rts_mkInt ( Capability
*, HsInt i
);
193 HaskellObj
rts_mkInt8 ( Capability
*, HsInt8 i
);
194 HaskellObj
rts_mkInt16 ( Capability
*, HsInt16 i
);
195 HaskellObj
rts_mkInt32 ( Capability
*, HsInt32 i
);
196 HaskellObj
rts_mkInt64 ( Capability
*, HsInt64 i
);
197 HaskellObj
rts_mkWord ( Capability
*, HsWord w
);
198 HaskellObj
rts_mkWord8 ( Capability
*, HsWord8 w
);
199 HaskellObj
rts_mkWord16 ( Capability
*, HsWord16 w
);
200 HaskellObj
rts_mkWord32 ( Capability
*, HsWord32 w
);
201 HaskellObj
rts_mkWord64 ( Capability
*, HsWord64 w
);
202 HaskellObj
rts_mkPtr ( Capability
*, HsPtr a
);
203 HaskellObj
rts_mkFunPtr ( Capability
*, HsFunPtr a
);
204 HaskellObj
rts_mkFloat ( Capability
*, HsFloat f
);
205 HaskellObj
rts_mkDouble ( Capability
*, HsDouble f
);
206 HaskellObj
rts_mkStablePtr ( Capability
*, HsStablePtr s
);
207 HaskellObj
rts_mkBool ( Capability
*, HsBool b
);
208 HaskellObj
rts_mkString ( Capability
*, char *s
);
210 HaskellObj
rts_apply ( Capability
*, HaskellObj
, HaskellObj
);
212 /* ----------------------------------------------------------------------------
213 Deconstructing Haskell objects
214 ------------------------------------------------------------------------- */
215 HsChar
rts_getChar ( HaskellObj
);
216 HsInt
rts_getInt ( HaskellObj
);
217 HsInt8
rts_getInt8 ( HaskellObj
);
218 HsInt16
rts_getInt16 ( HaskellObj
);
219 HsInt32
rts_getInt32 ( HaskellObj
);
220 HsInt64
rts_getInt64 ( HaskellObj
);
221 HsWord
rts_getWord ( HaskellObj
);
222 HsWord8
rts_getWord8 ( HaskellObj
);
223 HsWord16
rts_getWord16 ( HaskellObj
);
224 HsWord32
rts_getWord32 ( HaskellObj
);
225 HsWord64
rts_getWord64 ( HaskellObj
);
226 HsPtr
rts_getPtr ( HaskellObj
);
227 HsFunPtr
rts_getFunPtr ( HaskellObj
);
228 HsFloat
rts_getFloat ( HaskellObj
);
229 HsDouble
rts_getDouble ( HaskellObj
);
230 HsStablePtr
rts_getStablePtr ( HaskellObj
);
231 HsBool
rts_getBool ( HaskellObj
);
233 /* ----------------------------------------------------------------------------
234 Evaluating Haskell expressions
236 The versions ending in '_' allow you to specify an initial stack size.
237 Note that these calls may cause Garbage Collection, so all HaskellObj
238 references are rendered invalid by these calls.
240 All of these functions take a (Capability **) - there is a
241 Capability pointer both input and output. We use an inout
242 parameter because this is less error-prone for the client than a
243 return value - the client could easily forget to use the return
244 value, whereas incorrectly using an inout parameter will usually
245 result in a type error.
246 ------------------------------------------------------------------------- */
248 void rts_eval (/* inout */ Capability
**,
249 /* in */ HaskellObj p
,
250 /* out */ HaskellObj
*ret
);
252 void rts_eval_ (/* inout */ Capability
**,
253 /* in */ HaskellObj p
,
254 /* in */ unsigned int stack_size
,
255 /* out */ HaskellObj
*ret
);
257 void rts_evalIO (/* inout */ Capability
**,
258 /* in */ HaskellObj p
,
259 /* out */ HaskellObj
*ret
);
261 void rts_evalStableIO (/* inout */ Capability
**,
262 /* in */ HsStablePtr s
,
263 /* out */ HsStablePtr
*ret
);
265 void rts_evalLazyIO (/* inout */ Capability
**,
266 /* in */ HaskellObj p
,
267 /* out */ HaskellObj
*ret
);
269 void rts_evalLazyIO_ (/* inout */ Capability
**,
270 /* in */ HaskellObj p
,
271 /* in */ unsigned int stack_size
,
272 /* out */ HaskellObj
*ret
);
274 void rts_checkSchedStatus (char* site
, Capability
*);
276 SchedulerStatus
rts_getSchedStatus (Capability
*cap
);
279 * The RTS allocates some thread-local data when you make a call into
280 * Haskell using one of the rts_eval() functions. This data is not
281 * normally freed until hs_exit(). If you want to free it earlier
282 * than this, perhaps because the thread is about to exit, then call
283 * rts_done() from the thread.
285 * It is safe to make more rts_eval() calls after calling rts_done(),
286 * but the next one will cause allocation of the thread-local memory
289 void rts_done (void);
291 /* --------------------------------------------------------------------------
294 These are used by foreign export and foreign import "wrapper" stubs.
295 ----------------------------------------------------------------------- */
297 // When producing Windows DLLs the we need to know which symbols are in the
298 // local package/DLL vs external ones.
300 // Note that RtsAPI.h is also included by foreign export stubs in
301 // the base package itself.
303 #if defined(COMPILING_WINDOWS_DLL) && !defined(COMPILING_BASE_PACKAGE)
304 __declspec(dllimport
) extern StgWord base_GHCziTopHandler_runIO_closure
[];
305 __declspec(dllimport
) extern StgWord base_GHCziTopHandler_runNonIO_closure
[];
307 extern StgWord base_GHCziTopHandler_runIO_closure
[];
308 extern StgWord base_GHCziTopHandler_runNonIO_closure
[];
311 #define runIO_closure base_GHCziTopHandler_runIO_closure
312 #define runNonIO_closure base_GHCziTopHandler_runNonIO_closure
314 /* ------------------------------------------------------------------------ */
320 #endif /* RTSAPI_H */