- 02 Aug, 2009 1 commit
-
-
Simon Marlow authored
The first phase of this tidyup is focussed on the header files, and in particular making sure we are exposinng publicly exactly what we need to, and no more. - Rts.h now includes everything that the RTS exposes publicly, rather than a random subset of it. - Most of the public header files have moved into subdirectories, and many of them have been renamed. But clients should not need to include any of the other headers directly, just #include the main public headers: Rts.h, HsFFI.h, RtsAPI.h. - All the headers needed for via-C compilation have moved into the stg subdirectory, which is self-contained. Most of the headers for the rest of the RTS APIs have moved into the rts subdirectory. - I left MachDeps.h where it is, because it is so widely used in Haskell code. - I left a deprecated stub for RtsFlags.h in place. The flag structures are now exposed by Rts.h. - Various internal APIs are no longer exposed by public header files. - Various bits of dead code and declarations have been removed - More gcc warnings are turned on, and the RTS code is more warning-clean. - More source files #include "PosixSource.h", and hence only use standard POSIX (1003.1c-1995) interfaces. There is a lot more tidying up still to do, this is just the first pass. I also intend to standardise the names for external RTS APIs (e.g use the rts_ prefix consistently), and declare the internal APIs as hidden for shared libraries.
-
- 12 Jun, 2009 1 commit
-
-
Duncan Coutts authored
We need this, or something equivalent, to be able to implement stgAllocForGMP outside of the rts. That's because we want to use allocateLocal which allocates from the given capability without having to take any locks. In the gmp primops we're basically in an unsafe foreign call, that is a context where we hold a current capability. So it's safe for us to use allocateLocal. We just need a way to get the current capability. The method to get the current capability varies depends on whether we're using the threaded rts or not. When stgAllocForGMP is built inside the rts that's ok because we can do it conditionally on THREADED_RTS. Outside the rts we need a single api we can call without knowing if we're talking to a threaded rts or not, hence this addition.
-
- 09 Dec, 2008 1 commit
-
-
Simon Marlow authored
Really we should be raising an exception in this case, but that's tricky (see comments). At least now we shut down the runtime correctly rather than just exiting.
-
- 09 Jul, 2008 1 commit
-
-
Simon Marlow authored
2301: Control-C now causes the new exception (AsyncException UserInterrupt) to be raised in the main thread. The signal handler is set up by GHC.TopHandler.runMainIO, and can be overriden in the usual way by installing a new signal handler. The advantage is that now all programs will get a chance to clean up on ^C. When UserInterrupt is caught by the topmost handler, we now exit the program via kill(getpid(),SIGINT), which tells the parent process that we exited as a result of ^C, so the parent can take appropriate action (it might want to exit too, for example). One subtlety is that we have to use a weak reference to the ThreadId for the main thread, so that the signal handler doesn't prevent the main thread from being subject to deadlock detection. 1619: we now ignore SIGPIPE by default. Although POSIX says that a SIGPIPE should terminate the process by default, I wonder if this decision was made because many C applications failed to check the exit code from write(). In Haskell a failed write due to a closed pipe will generate an exception anyway, so the main difference is that we now get a useful error message instead of silent program termination. See #1619 for more discussion.
-
- 17 Jul, 2007 1 commit
-
-
Ian Lynagh authored
-
- 09 Aug, 2006 1 commit
-
-
Simon Marlow authored
See #753
-
- 26 Jul, 2006 1 commit
-
-
Simon Marlow authored
-
- 07 Apr, 2006 1 commit
-
-
Simon Marlow authored
Most of the other users of the fptools build system have migrated to Cabal, and with the move to darcs we can now flatten the source tree without losing history, so here goes. The main change is that the ghc/ subdir is gone, and most of what it contained is now at the top level. The build system now makes no pretense at being multi-project, it is just the GHC build system. No doubt this will break many things, and there will be a period of instability while we fix the dependencies. A straightforward build should work, but I haven't yet fixed binary/source distributions. Changes to the Building Guide will follow, too.
-
- 21 Oct, 2005 1 commit
-
-
simonmar authored
Big re-hash of the threaded/SMP runtime This is a significant reworking of the threaded and SMP parts of the runtime. There are two overall goals here: - To push down the scheduler lock, reducing contention and allowing more parts of the system to run without locks. In particular, the scheduler does not require a lock any more in the common case. - To improve affinity, so that running Haskell threads stick to the same OS threads as much as possible. At this point we have the basic structure working, but there are some pieces missing. I believe it's reasonably stable - the important parts of the testsuite pass in all the (normal,threaded,SMP) ways. In more detail: - Each capability now has a run queue, instead of one global run queue. The Capability and Task APIs have been completely rewritten; see Capability.h and Task.h for the details. - Each capability has its own pool of worker Tasks. Hence, Haskell threads on a Capability's run queue will run on the same worker Task(s). As long as the OS is doing something reasonable, this should mean they usually stick to the same CPU. Another way to look at this is that we're assuming each Capability is associated with a fixed CPU. - What used to be StgMainThread is now part of the Task structure. Every OS thread in the runtime has an associated Task, and it can ask for its current Task at any time with myTask(). - removed RTS_SUPPORTS_THREADS symbol, use THREADED_RTS instead (it is now defined for SMP too). - The RtsAPI has had to change; we must explicitly pass a Capability around now. The previous interface assumed some global state. SchedAPI has also changed a lot. - The OSThreads API now supports thread-local storage, used to implement myTask(), although it could be done more efficiently using gcc's __thread extension when available. - I've moved some POSIX-specific stuff into the posix subdirectory, moving in the direction of separating out platform-specific implementations. - lots of lock-debugging and assertions in the runtime. In particular, when DEBUG is on, we catch multiple ACQUIRE_LOCK()s, and there is also an ASSERT_LOCK_HELD() call. What's missing so far: - I have almost certainly broken the Win32 build, will fix soon. - any kind of thread migration or load balancing. This is high up the agenda, though. - various performance tweaks to do - throwTo and forkProcess still do not work in SMP mode
-
- 13 Aug, 2004 1 commit
-
-
simonmar authored
Merge backend-hacking-branch onto HEAD. Yay!
-
- 21 Sep, 2003 1 commit
-
-
wolfgang authored
Bound Threads ============= Introduce a way to use foreign libraries that rely on thread local state from multiple threads (mainly affects the threaded RTS). See the file threads.tex in CVS at haskell-report/ffi/threads.tex (not entirely finished yet) for a definition of this extension. A less formal description is also found in the documentation of Control.Concurrent. The changes mostly affect the THREADED_RTS (./configure --enable-threaded-rts), except for saving & restoring errno on a per-TSO basis, which is also necessary for the non-threaded RTS (a bugfix). Detailed list of changes ------------------------ - errno is saved in the TSO object and restored when necessary: ghc/includes/TSO.h, ghc/rts/Interpreter.c, ghc/rts/Schedule.c - rts_mainLazyIO is no longer needed, main is no special case anymore ghc/includes/RtsAPI.h, ghc/rts/RtsAPI.c, ghc/rts/Main.c, ghc/rts/Weak.c - passCapability: a new function that releases the capability and "passes" it to a specific OS thread: ghc/rts/Capability.h ghc/rts/Capability.c - waitThread(), scheduleWaitThread() and schedule() get an optional Capability *initialCapability passed as an argument: ghc/includes/SchedAPI.h, ghc/rts/Schedule.c, ghc/rts/RtsAPI.c - Bound Thread scheduling (that's what this is all about): ghc/rts/Schedule.h, ghc/rts/Schedule.c - new Primop isCurrentThreadBound#: ghc/compiler/prelude/primops.txt.pp, ghc/includes/PrimOps.h, ghc/rts/PrimOps.hc, ghc/rts/Schedule.h, ghc/rts/Schedule.c - a simple function, rtsSupportsBoundThreads, that returns true if THREADED_RTS is defined: ghc/rts/Schedule.h, ghc/rts/Schedule.c - a new implementation of forkProcess (the old implementation stays in place for the non-threaded case). Partially broken; works for the standard fork-and-exec case, but not for much else. A proper forkProcess is really next to impossible to implement: ghc/rts/Schedule.c - Library support for bound threads: Control.Concurrent. rtsSupportsBoundThreads, isCurrentThreadBound, forkOS, runInBoundThread, runInUnboundThread libraries/base/Control/Concurrent.hs, libraries/base/Makefile, libraries/base/include/HsBase.h, libraries/base/cbits/forkOS.c (new file)
-
- 22 Aug, 2003 1 commit
-
-
sof authored
rts_mainEvalIO() ~> rts_mainLazyIO() Merge to STABLE.
-
- 06 Feb, 2003 1 commit
-
-
simonmar authored
rts_mkFunPtr and rts_getFunPtr were missing. Thanks to Daan Leijen for spotting and reporting the bug. MERGE TO STABLE
-
- 29 Jan, 2003 1 commit
-
-
simonmar authored
- re-instate setProgArgv, it is used in System.Environment (bah, could have sworn I grepped for it and found nothing...) - Remove init_stack symbol from the Linker's symbol table; this is now static.
-
- 28 Jan, 2003 1 commit
-
-
simonmar authored
Flesh out support for hs_init() and hs_exit() according to the latest FFI spec. For GHC, I also added: hs_add_root( void (*fn)(void) ); which is used to specify the root module. This *must* be called prior to invoking any Haskell functions. The previous way of doing things still works: startupHaskell( argc, argv, root ); but the right way to do this is now hs_init( &argc, &argv ); hs_add_root( root ); It is possible to invoke hs_add_root() multiple times with different roots. - setProgArgv() has been removed; it was unused and looks like it was there to support STG Hugs.
-
- 25 Jan, 2003 1 commit
-
-
wolfgang authored
This commit fixes many bugs and limitations in the threaded RTS. There are still some issues remaining, though. The following bugs should have been fixed: - [+] "safe" calls could cause crashes - [+] yieldToReturningWorker/grabReturnCapability - It used to deadlock. - [+] couldn't wake blocked workers - Calls into the RTS could go unanswered for a long time, and that includes ordinary callbacks in some circumstances. - [+] couldn't block on an MVar and expect to be woken up by a signal handler - Depending on the exact situation, the RTS shut down or blocked forever and ignored the signal. - [+] The locking scheme in RtsAPI.c didn't work - [+] run_thread label in wrong place (schedule()) - [+] Deadlock in GHC.Handle - if a signal arrived at the wrong time, an mvar was never filled again - [+] Signals delivered to the "wrong" thread were ignored or handled too late. Issues: *) If GC can move TSO objects (I don't know - can it?), then ghci will occasionally crash when calling foreign functions, because the parameters are stored on the TSO stack. *) There is still a race condition lurking in the code (both threaded and non-threaded RTS are affected): If a signal arrives after the check for pending signals in schedule(), but before the call to select() in awaitEvent(), select() will be called anyway. The signal handler will be executed much later than expected. *) For Win32, GHC doesn't yet support non-blocking IO, so while a thread is waiting for IO, no call-ins can happen. If the RTS is blocked in awaitEvent, it uses a polling loop on Win32, so call-ins should work (although the polling loop looks ugly). *) Deadlock detection is disabled for the threaded rts, because I don't know how to do it properly in the presence of foreign call-ins from foreign threads. This causes the tests conc031, conc033 and conc034 to fail. *) "safe" is currently treated as "threadsafe". Implementing "safe" in a way that blocks other Haskell threads is more difficult than was thought at first. I think it could be done with a few additional lines of code, but personally, I'm strongly in favour of abolishing the distinction. *) Running finalizers at program termination is inefficient - there are two OS threads passing messages back and forth for every finalizer that is run. Also (just as in the non-threaded case) the finalizers are run in parallel to any remaining haskell threads and to any foreign call-ins that might still happen.
-
- 05 Sep, 2002 1 commit
-
-
simonmar authored
Remove RtsAPIDeprec.c, since this is causing grief. The upshot (I think) is that you won't be able to do foreign import "wrapper" with an Addr in the type.
-
- 16 Jul, 2002 1 commit
-
-
simonmar authored
Remove DLL_IMPORT from the two closure declarations in this file, because otherwise the file is not standalone. Doing the right thing doesn't seem easy, because we have to get the right value of DONT_WANT_WIN32_DLLS from somewhere. Anyway if/when DLL support is revived we'll have to revisit this. MERGE TO STABLE
-
- 15 Jul, 2002 1 commit
-
-
simonmar authored
Static closures are not declared 'const' in generated code, so don't declare them 'const' in here. Spotted-by: GCC 3.1
-
- 27 Jun, 2002 1 commit
-
-
simonmar authored
Finally fix foreign export and foreign import "wrapper" so that exceptions raised during the call are handled properly rather than causing the RTS to bomb out. In particular, calling System.exitWith in a foreign export will cause the program to terminate cleanly with the desired exit code. All other exceptions are printed on stderr (and the program is terminated). Details: GHC.TopHandler.runMain is now called runIO, and has type IO a -> IO a (previously it had type IO a -> IO (), but that's not general enough for a foreign export). The stubs for foreign export and forein import "wrapper" now automatically wrap the computation in runIO or its dual, runNonIO. It turned out to be simpler to do it this way than to do the wrapping in Haskell land (plain foreign exports don't have wrappers in Haskell).
-
- 15 Feb, 2002 1 commit
-
-
sof authored
Add rts_mainEvalIO proto
-
- 22 Jan, 2002 1 commit
-
-
simonmar authored
Deadlock is now an exception instead of a return status from rts_evalIO(). The current behaviour is as follows, and can be changed if necessary: in the event of a deadlock, the top main thread is taken from the main thread queue, and if it is blocked on an MVar or an Exception (for throwTo), then it receives a Deadlock exception. If it is blocked on a BLACKHOLE, we instead send it the NonTermination exception. Note that only the main thread gets the exception: it is the responsibility of the main thread to unblock other threads if necessary. There's a slight difference in the SMP build: *all* the main threads get an exception, because clearly none of them may make progress (compared to the non-SMP situation, where all but the top main thread are usually blocked).
-
- 29 Oct, 2001 1 commit
-
-
simonmar authored
Wrap the include file entry-points in extern "C" { ... } if this is a C++ compiler.
-
- 23 Oct, 2001 1 commit
-
-
simonmar authored
Add new function: rts_evalStableIO (HsStablePtr s, /*out*/HsStablePtr *ret) which is a version of rts_evalStrictIO() that can be invoked from Haskell.
-
- 03 Aug, 2001 1 commit
-
-
sof authored
Full complement of sized Int/Word getter routines
-
- 22 Mar, 2001 1 commit
-
-
hwloidl authored
-*- outline -*- Time-stamp: <Thu Mar 22 2001 03:50:16 Stardate: [-30]6365.79 hwloidl> This commit covers changes in GHC to get GUM (way=mp) and GUM/GdH (way=md) working. It is a merge of my working version of GUM, based on GHC 4.06, with GHC 4.11. Almost all changes are in the RTS (see below). GUM is reasonably stable, we used the 4.06 version in large-ish programs for recent papers. Couple of things I want to change, but nothing urgent. GUM/GdH has just been merged and needs more testing. Hope to do that in the next weeks. It works in our working build but needs tweaking to run. GranSim doesn't work yet (*sigh*). Most of the code should be in, but needs more debugging. ToDo: I still want to make the following minor modifications before the release - Better wrapper skript for parallel execution [ghc/compiler/main] - Update parallel docu: started on it but it's minimal [ghc/docs/users_guide] - Clean up [nofib/parallel]: it's a real mess right now (*sigh*) - Update visualisation tools (minor things only IIRC) [ghc/utils/parallel] - Add a Klingon-English glossary * RTS: Almost all changes are restricted to ghc/rts/parallel and should not interfere with the rest. I only comment on changes outside the parallel dir: - Several changes in Schedule.c (scheduling loop; createThreads etc); should only affect parallel code - Added ghc/rts/hooks/ShutdownEachPEHook.c - ghc/rts/Linker.[ch]: GUM doesn't know about Stable Names (ifdefs)!! - StgMiscClosures.h: END_TSO_QUEUE etc now defined here (from StgMiscClosures.hc) END_ECAF_LIST was missing a leading stg_ - SchedAPI.h: taskStart now defined in here; it's only a wrapper around scheduleThread now, but might use some init, shutdown later - RtsAPI.h: I have nuked the def of rts_evalNothing * Compiler: - ghc/compiler/main/DriverState.hs added PVM-ish flags to the parallel way added new ways for parallel ticky profiling and distributed exec - ghc/compiler/main/DriverPipeline.hs added a fct run_phase_MoveBinary which is called with way=mp after linking; it moves the bin file into a PVM dir and produces a wrapper script for parallel execution maybe cleaner to add a MoveBinary phase in DriverPhases.hs but this way it's less intrusive and MoveBinary makes probably only sense for mp anyway * Nofib: - nofib/spectral/Makefile, nofib/real/Makefile, ghc/tests/programs/Makefile: modified to skip some tests if HWL_NOFIB_HACK is set; only tmp to record which test prgs cause problems in my working build right now
-
- 09 Feb, 2001 1 commit
-
-
simonmar authored
Declare the 3rd argument to startupHaskell as a function pointer rather than a void *, to avoid accidental mis-declarations of __init_Foo symbols.
-
- 11 Jan, 2001 1 commit
-
-
simonmar authored
Re-organisation of ghc/lib/std and hslibs/lang ---------------------------------------------- In brief: move deprecated features out of ghc/lib/std and into hslibs/lang, move new FFI libraries into ghc/lib/std and start using them. - foreign import may now return an unboxed type (this was advertised to work before, but in fact didn't). Subsequent cleanups in PrelInt/PrelWord. - Ptr is now defined in ghc/lib/std/PrelPtr.lhs. Ptr is no longer a newtype of Addr, it is defined directly in terms of Addr#. - PrelAddr has disappeared from ghc/lib/std, all uses of Addr in ghc/lib/std have been replaced with Ptr. The definitions of Addr has been moved to hslibs/lang/Addr.lhs, as has lots of other Addr-related stuff. - ForeignObj has been removed from ghc/lib/std, and replaced with ForeignPtr. The definition of ForeignObj has been moved to hslibs/lang/ForeignObj.lhs. - Most of the new FFI has been moved into ghc/lib/std in the form of modules PrelMarshalAlloc, PrelCString, PrelCError, PrelMarshalError, PrelMarshalArray, PrelMarshalUtils, PrelCTypes, PrelCTypesISO, and PrelStorable. The corresponding modules in hslibs/lang simply re-export the contents of these modules. - PrelPosixTypes defines a few POSIX types (CMode == mode_t, etc.) - PrelCError changed to access errno using foreign label and peek (the POSIX book I have says that errno is guaranteed to be an extern int, so this should be OK until I get around to making errno thread-safe). - Hacked the macros that generate the code for CTypes and CTypesISO to generate much less code (ghc/lib/std/cbits/CTypes.h). - RtsAPI is now a bit more honest when it comes to building heap objects (it uses the correct constructors). - the Bits class and related stuff has been moved to ghc/lib/std (it was simpler this way). - Directory and System have been converted to use the new FFI.
-
- 07 Nov, 2000 1 commit
-
-
simonmar authored
Clean ups: - reduce the namespace pollution of StgTypes.h, it doesn't define the shorthand versions any more (W_, I_ etc.). These are moved into Stg.h. StgTypes.h also defines StgClosure as an "opaque" struct. - RtsAPI.h is now standalone, and includes HsFFI.h and thereby config.h & StgTypes.h. Now we don't need to #include "Stg.h" in *_stub.c. - all the rts_mkXXXX and rts_getXXXX functions are defined in terms of the HsXXXX types rather than random C types (this fixes some potential bugs in our foreign export support). - added HsWord type, to match StgWord. The Haskell version of this type isn't "documented", but perhaps it should be.
-
- 29 Aug, 2000 1 commit
-
-
qrczak authored
Don't use a typedef called int64 in RtsAPI. It conflicts with e.g. OCaml's headers. It should be cleaned better...
-
- 07 Aug, 2000 1 commit
-
-
qrczak authored
Now Char, Char#, StgChar have 31 bits (physically 32). "foo"# is still an array of bytes. CharRep represents 32 bits (on a 64-bit arch too). There is also Int8Rep, used in those places where bytes were originally meant. readCharArray, indexCharOffAddr etc. still use bytes. Storable and {I,M}Array use wide Chars. In future perhaps all sized integers should be primitive types. Then some usages of indexing primops scattered through the code could be changed to then-available Int8 ones, and then Char variants of primops could be made wide (other usages that handle text should use conversion that will be provided later). I/O and _ccall_ arguments assume ISO-8859-1. UTF-8 is internally used for string literals (only). Z-encoding is ready for Unicode identifiers. Ranges of intlike and charlike closures are more easily configurable. I've probably broken nativeGen/MachCode.lhs:chrCode for Alpha but I don't know the Alpha assembler to fix it (what is zapnot?). Generally I'm not sure if I've done the NCG changes right. This commit breaks the binary compatibility (of course). TODO: * is* and to{Lower,Upper} in Char (in progress). * Libraries for text conversion (in design / experiments), to be plugged to I/O and a higher level foreign library. * PackedString. * StringBuffer and accepting source in encodings other than ISO-8859-1.
-
- 27 Jun, 2000 1 commit
-
-
sewardj authored
Fix compilation problems with int64 and nat64.
-
- 15 Jun, 2000 1 commit
-
-
daan authored
Added definition of int64 to make it compilable with both gcc and VisualC++
-
- 26 Apr, 2000 1 commit
-
-
simonmar authored
comment-only clarifications; Killed means "uncaught exception".
-
- 10 Apr, 2000 1 commit
-
-
sewardj authored
Make getArgs and getProgName behave identically in combined and standalone modes.
-
- 31 Mar, 2000 1 commit
-
-
hwloidl authored
Numerous changes in the RTS to get GUM-4.06 working (currently works with parfib-ish programs). Most changes are isolated in the rts/parallel dir. rts/parallel/: The most important changes are a rewrite of the (un-)packing code (Pack.c) and changes in LAGA, GALA table operations (Global.c) expecially in rebuilding the tables during GC. rts/: Minor changes in Schedule.c, GC.c (interface to par specific root marking and evacuation), and lots of additions to Sanity.c (surprise ;-) Main.c change for startup: I use a new function rts_evalNothing to start non-main-PEs in a PAR || SMP setup (RtsAPI.c) includes/: Updated GranSim macros in PrimOps.h. lib/std: Few changes in PrelHandle.c etc replacing ForeignObj by Addr in a PAR setup (we still don't support ForeignObjs or WeakPtrs in GUM). Typically use #define FILE_OBJECT Addr when dealing with files. hslibs/lang/: Same as above (in Foreign(Obj).lhs, Weak.lhs, IOExts.lhs etc). -- HWL
-
- 30 Mar, 2000 1 commit
-
-
simonmar authored
HEADS UP!!! change the type of startupHaskell(): void startupHaskell ( int argc, char *argv[], void *init_root ); the extra parameter is a pointer to the initialisation function for the root module in the program. eg., Main.c now passes __init_Main for this parameter. It can be left as NULL if there is no root module. This interface may need to be revised, since in some circumstances there may be more than one "root module". Sigbjorn: H/Direct will need some changes to stay in sync here.
-
- 13 Jan, 2000 1 commit
-
-
simonmar authored
- remove AllBlocked scheduler return code. Nobody owned up to having created it or even knowing what it was there for. - clean up fatal error condition handling somewhat. The process exit code from a GHC program now indicates the kind of failure for certain kinds of exit: general internal RTS error 254 program deadlocked 253 program interrupted (ctrl-C) 252 heap overflow 251 main thread killed 250 and we leave exit codes 1-199 for the user (as is traditional at MS, 200-249 are reserved for future expansion, and may contain undocumented extensions :-)
-
- 02 Nov, 1999 1 commit
-
-
simonmar authored
This commit adds in the current state of our SMP support. Notably, this allows the new way 's' to be built, providing support for running multiple Haskell threads simultaneously on top of any pthreads implementation, the idea being to take advantage of commodity SMP boxes. Don't expect to get much of a speedup yet; due to the excessive locking required to synchronise access to mutable heap objects, you'll see a slowdown in most cases, even on a UP machine. The best I've seen is a 1.6-1.7 speedup on an example that did no locking (two optimised nfibs in parallel). - new RTS -N flag specifies how many pthreads to start. - new driver -smp flag, tells the driver to use way 's'. - new compiler -fsmp option (not for user comsumption) tells the compiler not to generate direct jumps to thunk entry code. - largely rewritten scheduler - _ccall_GC is now done by handing back a "token" to the RTS before executing the ccall; it should now be possible to execute blocking ccalls in the current thread while allowing the RTS to continue running Haskell threads as normal. - you can only call thread-safe C libraries from a way 's' build, of course. Pthread support is still incomplete, and weird things (including deadlocks) are likely to happen.
-
- 06 Jul, 1999 1 commit
-
-
sof authored
Redo previous commit to cut down on the use of COMPILING_RTS where possible - SchedAPI.h is now an RTS internal header file which RtsAPI.h no longer includes.
-