1 /* ---------------------------------------------------------------------------
3 * (c) The GHC Team, 2003-2012
7 * A Capability represents the token required to execute STG code,
8 * and all the state an OS thread/task needs to run Haskell code:
9 * its STG registers, a pointer to its TSO, a nursery etc. During
10 * STG execution, a pointer to the capabilitity is kept in a
11 * register (BaseReg; actually it is a pointer to cap->r).
13 * Only in an THREADED_RTS build will there be multiple capabilities,
14 * for non-threaded builds there is only one global capability, namely
17 * --------------------------------------------------------------------------*/
19 #include "PosixSource.h"
22 #include "Capability.h"
26 #include "sm/GC.h" // for gcWorkerThread()
32 // one global capability, this is the Capability for non-threaded
33 // builds, and for +RTS -N1
34 Capability MainCapability
;
36 nat n_capabilities
= 0;
37 nat enabled_capabilities
= 0;
39 // The array of Capabilities. It's important that when we need
40 // to allocate more Capabilities we don't have to move the existing
41 // Capabilities, because there may be pointers to them in use
42 // (e.g. threads in waitForReturnCapability(), see #8209), so this is
43 // an array of Capability* rather than an array of Capability.
44 Capability
**capabilities
= NULL
;
46 // Holds the Capability which last became free. This is used so that
47 // an in-call has a chance of quickly finding a free Capability.
48 // Maintaining a global free list of Capabilities would require global
49 // locking, so we don't do that.
50 Capability
*last_free_capability
= NULL
;
53 * Indicates that the RTS wants to synchronise all the Capabilities
54 * for some reason. All Capabilities should stop and return to the
57 volatile StgWord pending_sync
= 0;
59 /* Let foreign code get the current Capability -- assuming there is one!
60 * This is useful for unsafe foreign calls because they are called with
61 * the current Capability held, but they are not passed it. For example,
62 * see see the integer-gmp package which calls allocate() in its
63 * stgAllocForGMP() function (which gets called by gmp functions).
65 Capability
* rts_unsafeGetMyCapability (void)
67 #if defined(THREADED_RTS)
70 return &MainCapability
;
74 #if defined(THREADED_RTS)
78 return sched_state
>= SCHED_INTERRUPTING
79 || recent_activity
== ACTIVITY_INACTIVE
; // need to check for deadlock
83 #if defined(THREADED_RTS)
85 findSpark (Capability
*cap
)
92 if (!emptyRunQueue(cap
) || cap
->returning_tasks_hd
!= NULL
) {
93 // If there are other threads, don't try to run any new
94 // sparks: sparks might be speculative, we don't want to take
95 // resources away from the main computation.
102 // first try to get a spark from our own pool.
103 // We should be using reclaimSpark(), because it works without
104 // needing any atomic instructions:
105 // spark = reclaimSpark(cap->sparks);
106 // However, measurements show that this makes at least one benchmark
107 // slower (prsa) and doesn't affect the others.
108 spark
= tryStealSpark(cap
->sparks
);
109 while (spark
!= NULL
&& fizzledSpark(spark
)) {
110 cap
->spark_stats
.fizzled
++;
111 traceEventSparkFizzle(cap
);
112 spark
= tryStealSpark(cap
->sparks
);
115 cap
->spark_stats
.converted
++;
117 // Post event for running a spark from capability's own pool.
118 traceEventSparkRun(cap
);
122 if (!emptySparkPoolCap(cap
)) {
126 if (n_capabilities
== 1) { return NULL
; } // makes no sense...
128 debugTrace(DEBUG_sched
,
129 "cap %d: Trying to steal work from other capabilities",
132 /* visit cap.s 0..n-1 in sequence until a theft succeeds. We could
133 start at a random place instead of 0 as well. */
134 for ( i
=0 ; i
< n_capabilities
; i
++ ) {
135 robbed
= capabilities
[i
];
136 if (cap
== robbed
) // ourselves...
139 if (emptySparkPoolCap(robbed
)) // nothing to steal here
142 spark
= tryStealSpark(robbed
->sparks
);
143 while (spark
!= NULL
&& fizzledSpark(spark
)) {
144 cap
->spark_stats
.fizzled
++;
145 traceEventSparkFizzle(cap
);
146 spark
= tryStealSpark(robbed
->sparks
);
148 if (spark
== NULL
&& !emptySparkPoolCap(robbed
)) {
149 // we conflicted with another thread while trying to steal;
155 cap
->spark_stats
.converted
++;
156 traceEventSparkSteal(cap
, robbed
->no
);
160 // otherwise: no success, try next one
164 debugTrace(DEBUG_sched
, "No sparks stolen");
168 // Returns True if any spark pool is non-empty at this moment in time
169 // The result is only valid for an instant, of course, so in a sense
170 // is immediately invalid, and should not be relied upon for
177 for (i
=0; i
< n_capabilities
; i
++) {
178 if (!emptySparkPoolCap(capabilities
[i
])) {
186 /* -----------------------------------------------------------------------------
187 * Manage the returning_tasks lists.
189 * These functions require cap->lock
190 * -------------------------------------------------------------------------- */
192 #if defined(THREADED_RTS)
194 newReturningTask (Capability
*cap
, Task
*task
)
196 ASSERT_LOCK_HELD(&cap
->lock
);
197 ASSERT(task
->next
== NULL
);
198 if (cap
->returning_tasks_hd
) {
199 ASSERT(cap
->returning_tasks_tl
->next
== NULL
);
200 cap
->returning_tasks_tl
->next
= task
;
202 cap
->returning_tasks_hd
= task
;
204 cap
->returning_tasks_tl
= task
;
208 popReturningTask (Capability
*cap
)
210 ASSERT_LOCK_HELD(&cap
->lock
);
212 task
= cap
->returning_tasks_hd
;
214 cap
->returning_tasks_hd
= task
->next
;
215 if (!cap
->returning_tasks_hd
) {
216 cap
->returning_tasks_tl
= NULL
;
223 /* ----------------------------------------------------------------------------
226 * The Capability is initially marked not free.
227 * ------------------------------------------------------------------------- */
230 initCapability( Capability
*cap
, nat i
)
235 cap
->in_haskell
= rtsFalse
;
237 cap
->disabled
= rtsFalse
;
239 cap
->run_queue_hd
= END_TSO_QUEUE
;
240 cap
->run_queue_tl
= END_TSO_QUEUE
;
242 #if defined(THREADED_RTS)
243 initMutex(&cap
->lock
);
244 cap
->running_task
= NULL
; // indicates cap is free
245 cap
->spare_workers
= NULL
;
246 cap
->n_spare_workers
= 0;
247 cap
->suspended_ccalls
= NULL
;
248 cap
->returning_tasks_hd
= NULL
;
249 cap
->returning_tasks_tl
= NULL
;
250 cap
->inbox
= (Message
*)END_TSO_QUEUE
;
251 cap
->sparks
= allocSparkPool();
252 cap
->spark_stats
.created
= 0;
253 cap
->spark_stats
.dud
= 0;
254 cap
->spark_stats
.overflowed
= 0;
255 cap
->spark_stats
.converted
= 0;
256 cap
->spark_stats
.gcd
= 0;
257 cap
->spark_stats
.fizzled
= 0;
259 cap
->total_allocated
= 0;
261 cap
->f
.stgEagerBlackholeInfo
= (W_
)&__stg_EAGER_BLACKHOLE_info
;
262 cap
->f
.stgGCEnter1
= (StgFunPtr
)__stg_gc_enter_1
;
263 cap
->f
.stgGCFun
= (StgFunPtr
)__stg_gc_fun
;
265 cap
->mut_lists
= stgMallocBytes(sizeof(bdescr
*) *
266 RtsFlags
.GcFlags
.generations
,
268 cap
->saved_mut_lists
= stgMallocBytes(sizeof(bdescr
*) *
269 RtsFlags
.GcFlags
.generations
,
272 for (g
= 0; g
< RtsFlags
.GcFlags
.generations
; g
++) {
273 cap
->mut_lists
[g
] = NULL
;
276 cap
->free_tvar_watch_queues
= END_STM_WATCH_QUEUE
;
277 cap
->free_invariant_check_queues
= END_INVARIANT_CHECK_QUEUE
;
278 cap
->free_trec_chunks
= END_STM_CHUNK_LIST
;
279 cap
->free_trec_headers
= NO_TREC
;
280 cap
->transaction_tokens
= 0;
281 cap
->context_switch
= 0;
282 cap
->pinned_object_block
= NULL
;
283 cap
->pinned_object_blocks
= NULL
;
286 cap
->r
.rCCCS
= CCS_SYSTEM
;
292 traceCapsetAssignCap(CAPSET_OSPROCESS_DEFAULT
, i
);
293 traceCapsetAssignCap(CAPSET_CLOCKDOMAIN_DEFAULT
, i
);
294 #if defined(THREADED_RTS)
295 traceSparkCounters(cap
);
299 /* ---------------------------------------------------------------------------
300 * Function: initCapabilities()
302 * Purpose: set up the Capability handling. For the THREADED_RTS build,
303 * we keep a table of them, the size of which is
304 * controlled by the user via the RTS flag -N.
306 * ------------------------------------------------------------------------- */
308 initCapabilities( void )
310 /* Declare a couple capability sets representing the process and
311 clock domain. Each capability will get added to these capsets. */
312 traceCapsetCreate(CAPSET_OSPROCESS_DEFAULT
, CapsetTypeOsProcess
);
313 traceCapsetCreate(CAPSET_CLOCKDOMAIN_DEFAULT
, CapsetTypeClockdomain
);
315 #if defined(THREADED_RTS)
318 // We can't support multiple CPUs if BaseReg is not a register
319 if (RtsFlags
.ParFlags
.nNodes
> 1) {
320 errorBelch("warning: multiple CPUs not supported in this build, reverting to 1");
321 RtsFlags
.ParFlags
.nNodes
= 1;
326 moreCapabilities(0, RtsFlags
.ParFlags
.nNodes
);
327 n_capabilities
= RtsFlags
.ParFlags
.nNodes
;
329 #else /* !THREADED_RTS */
332 capabilities
= stgMallocBytes(sizeof(Capability
*), "initCapabilities");
333 capabilities
[0] = &MainCapability
;
334 initCapability(&MainCapability
, 0);
338 enabled_capabilities
= n_capabilities
;
340 // There are no free capabilities to begin with. We will start
341 // a worker Task to each Capability, which will quickly put the
342 // Capability on the free list when it finds nothing to do.
343 last_free_capability
= capabilities
[0];
347 moreCapabilities (nat from USED_IF_THREADS
, nat to USED_IF_THREADS
)
349 #if defined(THREADED_RTS)
351 Capability
**old_capabilities
= capabilities
;
353 capabilities
= stgMallocBytes(to
* sizeof(Capability
*), "moreCapabilities");
356 // THREADED_RTS must work on builds that don't have a mutable
357 // BaseReg (eg. unregisterised), so in this case
358 // capabilities[0] must coincide with &MainCapability.
359 capabilities
[0] = &MainCapability
;
362 for (i
= 0; i
< to
; i
++) {
364 capabilities
[i
] = old_capabilities
[i
];
366 capabilities
[i
] = stgMallocBytes(sizeof(Capability
),
368 initCapability(capabilities
[i
], i
);
372 debugTrace(DEBUG_sched
, "allocated %d more capabilities", to
- from
);
374 if (old_capabilities
!= NULL
) {
375 stgFree(old_capabilities
);
380 /* ----------------------------------------------------------------------------
381 * setContextSwitches: cause all capabilities to context switch as
383 * ------------------------------------------------------------------------- */
385 void contextSwitchAllCapabilities(void)
388 for (i
=0; i
< n_capabilities
; i
++) {
389 contextSwitchCapability(capabilities
[i
]);
393 void interruptAllCapabilities(void)
396 for (i
=0; i
< n_capabilities
; i
++) {
397 interruptCapability(capabilities
[i
]);
401 /* ----------------------------------------------------------------------------
402 * Give a Capability to a Task. The task must currently be sleeping
403 * on its condition variable.
405 * Requires cap->lock (modifies cap->running_task).
407 * When migrating a Task, the migrater must take task->lock before
408 * modifying task->cap, to synchronise with the waking up Task.
409 * Additionally, the migrater should own the Capability (when
410 * migrating the run queue), or cap->lock (when migrating
411 * returning_workers).
413 * ------------------------------------------------------------------------- */
415 #if defined(THREADED_RTS)
417 giveCapabilityToTask (Capability
*cap USED_IF_DEBUG
, Task
*task
)
419 ASSERT_LOCK_HELD(&cap
->lock
);
420 ASSERT(task
->cap
== cap
);
421 debugTrace(DEBUG_sched
, "passing capability %d to %s %#" FMT_HexWord64
,
422 cap
->no
, task
->incall
->tso ?
"bound task" : "worker",
423 serialisableTaskId(task
));
424 ACQUIRE_LOCK(&task
->lock
);
425 if (task
->wakeup
== rtsFalse
) {
426 task
->wakeup
= rtsTrue
;
427 // the wakeup flag is needed because signalCondition() doesn't
428 // flag the condition if the thread is already runniing, but we want
430 signalCondition(&task
->cond
);
432 RELEASE_LOCK(&task
->lock
);
436 /* ----------------------------------------------------------------------------
437 * Function: releaseCapability(Capability*)
439 * Purpose: Letting go of a capability. Causes a
440 * 'returning worker' thread or a 'waiting worker'
441 * to wake up, in that order.
442 * ------------------------------------------------------------------------- */
444 #if defined(THREADED_RTS)
446 releaseCapability_ (Capability
* cap
,
447 rtsBool always_wakeup
)
451 task
= cap
->running_task
;
453 ASSERT_PARTIAL_CAPABILITY_INVARIANTS(cap
,task
);
455 cap
->running_task
= NULL
;
457 // Check to see whether a worker thread can be given
458 // the go-ahead to return the result of an external call..
459 if (cap
->returning_tasks_hd
!= NULL
) {
460 giveCapabilityToTask(cap
,cap
->returning_tasks_hd
);
461 // The Task pops itself from the queue (see waitForReturnCapability())
465 // If there is a pending sync, then we should just leave the
466 // Capability free. The thread trying to sync will be about to
467 // call waitForReturnCapability().
468 if (pending_sync
!= 0 && pending_sync
!= SYNC_GC_PAR
) {
469 last_free_capability
= cap
; // needed?
470 debugTrace(DEBUG_sched
, "sync pending, set capability %d free", cap
->no
);
474 // If the next thread on the run queue is a bound thread,
475 // give this Capability to the appropriate Task.
476 if (!emptyRunQueue(cap
) && peekRunQueue(cap
)->bound
) {
477 // Make sure we're not about to try to wake ourselves up
478 // ASSERT(task != cap->run_queue_hd->bound);
479 // assertion is false: in schedule() we force a yield after
480 // ThreadBlocked, but the thread may be back on the run queue
482 task
= peekRunQueue(cap
)->bound
->task
;
483 giveCapabilityToTask(cap
, task
);
487 if (!cap
->spare_workers
) {
488 // Create a worker thread if we don't have one. If the system
489 // is interrupted, we only create a worker task if there
490 // are threads that need to be completed. If the system is
491 // shutting down, we never create a new worker.
492 if (sched_state
< SCHED_SHUTTING_DOWN
|| !emptyRunQueue(cap
)) {
493 debugTrace(DEBUG_sched
,
494 "starting new worker on capability %d", cap
->no
);
495 startWorkerTask(cap
);
500 // If we have an unbound thread on the run queue, or if there's
501 // anything else to do, give the Capability to a worker thread.
503 !emptyRunQueue(cap
) || !emptyInbox(cap
) ||
504 (!cap
->disabled
&& !emptySparkPoolCap(cap
)) || globalWorkToDo()) {
505 if (cap
->spare_workers
) {
506 giveCapabilityToTask(cap
, cap
->spare_workers
);
507 // The worker Task pops itself from the queue;
513 cap
->r
.rCCCS
= CCS_IDLE
;
515 last_free_capability
= cap
;
516 debugTrace(DEBUG_sched
, "freeing capability %d", cap
->no
);
520 releaseCapability (Capability
* cap USED_IF_THREADS
)
522 ACQUIRE_LOCK(&cap
->lock
);
523 releaseCapability_(cap
, rtsFalse
);
524 RELEASE_LOCK(&cap
->lock
);
528 releaseAndWakeupCapability (Capability
* cap USED_IF_THREADS
)
530 ACQUIRE_LOCK(&cap
->lock
);
531 releaseCapability_(cap
, rtsTrue
);
532 RELEASE_LOCK(&cap
->lock
);
536 releaseCapabilityAndQueueWorker (Capability
* cap USED_IF_THREADS
)
540 ACQUIRE_LOCK(&cap
->lock
);
542 task
= cap
->running_task
;
544 // If the Task is stopped, we shouldn't be yielding, we should
546 ASSERT(!task
->stopped
);
548 // If the current task is a worker, save it on the spare_workers
549 // list of this Capability. A worker can mark itself as stopped,
550 // in which case it is not replaced on the spare_worker queue.
551 // This happens when the system is shutting down (see
552 // Schedule.c:workerStart()).
553 if (!isBoundTask(task
))
555 if (cap
->n_spare_workers
< MAX_SPARE_WORKERS
)
557 task
->next
= cap
->spare_workers
;
558 cap
->spare_workers
= task
;
559 cap
->n_spare_workers
++;
563 debugTrace(DEBUG_sched
, "%d spare workers already, exiting",
564 cap
->n_spare_workers
);
565 releaseCapability_(cap
,rtsFalse
);
566 // hold the lock until after workerTaskStop; c.f. scheduleWorker()
567 workerTaskStop(task
);
568 RELEASE_LOCK(&cap
->lock
);
572 // Bound tasks just float around attached to their TSOs.
574 releaseCapability_(cap
,rtsFalse
);
576 RELEASE_LOCK(&cap
->lock
);
580 /* ----------------------------------------------------------------------------
581 * waitForReturnCapability (Capability **pCap, Task *task)
583 * Purpose: when an OS thread returns from an external call,
584 * it calls waitForReturnCapability() (via Schedule.resumeThread())
585 * to wait for permission to enter the RTS & communicate the
586 * result of the external call back to the Haskell thread that
589 * ------------------------------------------------------------------------- */
591 waitForReturnCapability (Capability
**pCap
, Task
*task
)
593 #if !defined(THREADED_RTS)
595 MainCapability
.running_task
= task
;
596 task
->cap
= &MainCapability
;
597 *pCap
= &MainCapability
;
600 Capability
*cap
= *pCap
;
603 // Try last_free_capability first
604 cap
= last_free_capability
;
605 if (cap
->running_task
) {
607 // otherwise, search for a free capability
609 for (i
= 0; i
< n_capabilities
; i
++) {
610 if (!capabilities
[i
]->running_task
) {
611 cap
= capabilities
[i
];
616 // Can't find a free one, use last_free_capability.
617 cap
= last_free_capability
;
621 // record the Capability as the one this Task is now assocated with.
625 ASSERT(task
->cap
== cap
);
628 ACQUIRE_LOCK(&cap
->lock
);
630 debugTrace(DEBUG_sched
, "returning; I want capability %d", cap
->no
);
632 if (!cap
->running_task
) {
633 // It's free; just grab it
634 cap
->running_task
= task
;
635 RELEASE_LOCK(&cap
->lock
);
637 newReturningTask(cap
,task
);
638 RELEASE_LOCK(&cap
->lock
);
641 ACQUIRE_LOCK(&task
->lock
);
642 // task->lock held, cap->lock not held
643 if (!task
->wakeup
) waitCondition(&task
->cond
, &task
->lock
);
645 task
->wakeup
= rtsFalse
;
646 RELEASE_LOCK(&task
->lock
);
648 // now check whether we should wake up...
649 ACQUIRE_LOCK(&cap
->lock
);
650 if (cap
->running_task
== NULL
) {
651 if (cap
->returning_tasks_hd
!= task
) {
652 giveCapabilityToTask(cap
,cap
->returning_tasks_hd
);
653 RELEASE_LOCK(&cap
->lock
);
656 cap
->running_task
= task
;
657 popReturningTask(cap
);
658 RELEASE_LOCK(&cap
->lock
);
661 RELEASE_LOCK(&cap
->lock
);
667 cap
->r
.rCCCS
= CCS_SYSTEM
;
670 ASSERT_FULL_CAPABILITY_INVARIANTS(cap
, task
);
672 debugTrace(DEBUG_sched
, "resuming capability %d", cap
->no
);
678 #if defined(THREADED_RTS)
679 /* ----------------------------------------------------------------------------
681 * ------------------------------------------------------------------------- */
683 /* See Note [GC livelock] in Schedule.c for why we have gcAllowed
684 and return the rtsBool */
685 rtsBool
/* Did we GC? */
686 yieldCapability (Capability
** pCap
, Task
*task
, rtsBool gcAllowed
)
688 Capability
*cap
= *pCap
;
690 if ((pending_sync
== SYNC_GC_PAR
) && gcAllowed
) {
691 traceEventGcStart(cap
);
693 traceEventGcEnd(cap
);
694 traceSparkCounters(cap
);
695 // See Note [migrated bound threads 2]
696 if (task
->cap
== cap
) {
701 debugTrace(DEBUG_sched
, "giving up capability %d", cap
->no
);
703 // We must now release the capability and wait to be woken up
705 task
->wakeup
= rtsFalse
;
706 releaseCapabilityAndQueueWorker(cap
);
709 ACQUIRE_LOCK(&task
->lock
);
710 // task->lock held, cap->lock not held
711 if (!task
->wakeup
) waitCondition(&task
->cond
, &task
->lock
);
713 task
->wakeup
= rtsFalse
;
714 RELEASE_LOCK(&task
->lock
);
716 debugTrace(DEBUG_sched
, "woken up on capability %d", cap
->no
);
718 ACQUIRE_LOCK(&cap
->lock
);
719 if (cap
->running_task
!= NULL
) {
720 debugTrace(DEBUG_sched
,
721 "capability %d is owned by another task", cap
->no
);
722 RELEASE_LOCK(&cap
->lock
);
726 if (task
->cap
!= cap
) {
727 // see Note [migrated bound threads]
728 debugTrace(DEBUG_sched
,
729 "task has been migrated to cap %d", task
->cap
->no
);
730 RELEASE_LOCK(&cap
->lock
);
734 if (task
->incall
->tso
== NULL
) {
735 ASSERT(cap
->spare_workers
!= NULL
);
736 // if we're not at the front of the queue, release it
737 // again. This is unlikely to happen.
738 if (cap
->spare_workers
!= task
) {
739 giveCapabilityToTask(cap
,cap
->spare_workers
);
740 RELEASE_LOCK(&cap
->lock
);
743 cap
->spare_workers
= task
->next
;
745 cap
->n_spare_workers
--;
748 cap
->running_task
= task
;
749 RELEASE_LOCK(&cap
->lock
);
753 debugTrace(DEBUG_sched
, "resuming capability %d", cap
->no
);
754 ASSERT(cap
->running_task
== task
);
757 cap
->r
.rCCCS
= CCS_SYSTEM
;
762 ASSERT_FULL_CAPABILITY_INVARIANTS(cap
,task
);
767 // Note [migrated bound threads]
769 // There's a tricky case where:
770 // - cap A is running an unbound thread T1
771 // - there is a bound thread T2 at the head of the run queue on cap A
772 // - T1 makes a safe foreign call, the task bound to T2 is woken up on cap A
773 // - T1 returns quickly grabbing A again (T2 is still waking up on A)
774 // - T1 blocks, the scheduler migrates T2 to cap B
775 // - the task bound to T2 wakes up on cap B
777 // We take advantage of the following invariant:
779 // - A bound thread can only be migrated by the holder of the
780 // Capability on which the bound thread currently lives. So, if we
781 // hold Capabilty C, and task->cap == C, then task cannot be
782 // migrated under our feet.
784 // Note [migrated bound threads 2]
786 // Second tricky case;
787 // - A bound Task becomes a GC thread
788 // - scheduleDoGC() migrates the thread belonging to this Task,
789 // because the Capability it is on is disabled
790 // - after GC, gcWorkerThread() returns, but now we are
791 // holding a Capability that is not the same as task->cap
792 // - Hence we must check for this case and immediately give up the
795 /* ----------------------------------------------------------------------------
798 * If a Capability is currently idle, wake up a Task on it. Used to
799 * get every Capability into the GC.
800 * ------------------------------------------------------------------------- */
803 prodCapability (Capability
*cap
, Task
*task
)
805 ACQUIRE_LOCK(&cap
->lock
);
806 if (!cap
->running_task
) {
807 cap
->running_task
= task
;
808 releaseCapability_(cap
,rtsTrue
);
810 RELEASE_LOCK(&cap
->lock
);
813 /* ----------------------------------------------------------------------------
816 * Attempt to gain control of a Capability if it is free.
818 * ------------------------------------------------------------------------- */
821 tryGrabCapability (Capability
*cap
, Task
*task
)
823 if (cap
->running_task
!= NULL
) return rtsFalse
;
824 ACQUIRE_LOCK(&cap
->lock
);
825 if (cap
->running_task
!= NULL
) {
826 RELEASE_LOCK(&cap
->lock
);
830 cap
->running_task
= task
;
831 RELEASE_LOCK(&cap
->lock
);
836 #endif /* THREADED_RTS */
838 /* ----------------------------------------------------------------------------
841 * At shutdown time, we want to let everything exit as cleanly as
842 * possible. For each capability, we let its run queue drain, and
843 * allow the workers to stop.
845 * This function should be called when interrupted and
846 * sched_state = SCHED_SHUTTING_DOWN, thus any worker that wakes up
847 * will exit the scheduler and call taskStop(), and any bound thread
848 * that wakes up will return to its caller. Runnable threads are
851 * ------------------------------------------------------------------------- */
854 shutdownCapability (Capability
*cap USED_IF_THREADS
,
855 Task
*task USED_IF_THREADS
,
856 rtsBool safe USED_IF_THREADS
)
858 #if defined(THREADED_RTS)
863 // Loop indefinitely until all the workers have exited and there
864 // are no Haskell threads left. We used to bail out after 50
865 // iterations of this loop, but that occasionally left a worker
866 // running which caused problems later (the closeMutex() below
867 // isn't safe, for one thing).
869 for (i
= 0; /* i < 50 */; i
++) {
870 ASSERT(sched_state
== SCHED_SHUTTING_DOWN
);
872 debugTrace(DEBUG_sched
,
873 "shutting down capability %d, attempt %d", cap
->no
, i
);
874 ACQUIRE_LOCK(&cap
->lock
);
875 if (cap
->running_task
) {
876 RELEASE_LOCK(&cap
->lock
);
877 debugTrace(DEBUG_sched
, "not owner, yielding");
881 cap
->running_task
= task
;
883 if (cap
->spare_workers
) {
884 // Look for workers that have died without removing
885 // themselves from the list; this could happen if the OS
886 // summarily killed the thread, for example. This
887 // actually happens on Windows when the system is
888 // terminating the program, and the RTS is running in a
892 for (t
= cap
->spare_workers
; t
!= NULL
; t
= t
->next
) {
893 if (!osThreadIsAlive(t
->id
)) {
894 debugTrace(DEBUG_sched
,
895 "worker thread %p has died unexpectedly", (void *)(size_t)t
->id
);
896 cap
->n_spare_workers
--;
898 cap
->spare_workers
= t
->next
;
900 prev
->next
= t
->next
;
907 if (!emptyRunQueue(cap
) || cap
->spare_workers
) {
908 debugTrace(DEBUG_sched
,
909 "runnable threads or workers still alive, yielding");
910 releaseCapability_(cap
,rtsFalse
); // this will wake up a worker
911 RELEASE_LOCK(&cap
->lock
);
916 // If "safe", then busy-wait for any threads currently doing
917 // foreign calls. If we're about to unload this DLL, for
918 // example, we need to be sure that there are no OS threads
919 // that will try to return to code that has been unloaded.
920 // We can be a bit more relaxed when this is a standalone
921 // program that is about to terminate, and let safe=false.
922 if (cap
->suspended_ccalls
&& safe
) {
923 debugTrace(DEBUG_sched
,
924 "thread(s) are involved in foreign calls, yielding");
925 cap
->running_task
= NULL
;
926 RELEASE_LOCK(&cap
->lock
);
927 // The IO manager thread might have been slow to start up,
928 // so the first attempt to kill it might not have
929 // succeeded. Just in case, try again - the kill message
930 // will only be sent once.
932 // To reproduce this deadlock: run ffi002(threaded1)
933 // repeatedly on a loaded machine.
939 traceSparkCounters(cap
);
940 RELEASE_LOCK(&cap
->lock
);
943 // we now have the Capability, its run queue and spare workers
944 // list are both empty.
946 // ToDo: we can't drop this mutex, because there might still be
947 // threads performing foreign calls that will eventually try to
948 // return via resumeThread() and attempt to grab cap->lock.
949 // closeMutex(&cap->lock);
954 shutdownCapabilities(Task
*task
, rtsBool safe
)
957 for (i
=0; i
< n_capabilities
; i
++) {
958 ASSERT(task
->incall
->tso
== NULL
);
959 shutdownCapability(capabilities
[i
], task
, safe
);
961 #if defined(THREADED_RTS)
962 ASSERT(checkSparkCountInvariant());
967 freeCapability (Capability
*cap
)
969 stgFree(cap
->mut_lists
);
970 stgFree(cap
->saved_mut_lists
);
971 #if defined(THREADED_RTS)
972 freeSparkPool(cap
->sparks
);
974 traceCapsetRemoveCap(CAPSET_OSPROCESS_DEFAULT
, cap
->no
);
975 traceCapsetRemoveCap(CAPSET_CLOCKDOMAIN_DEFAULT
, cap
->no
);
980 freeCapabilities (void)
982 #if defined(THREADED_RTS)
984 for (i
=0; i
< n_capabilities
; i
++) {
985 freeCapability(capabilities
[i
]);
986 stgFree(capabilities
[i
]);
989 freeCapability(&MainCapability
);
991 stgFree(capabilities
);
992 traceCapsetDelete(CAPSET_OSPROCESS_DEFAULT
);
993 traceCapsetDelete(CAPSET_CLOCKDOMAIN_DEFAULT
);
996 /* ---------------------------------------------------------------------------
997 Mark everything directly reachable from the Capabilities. When
998 using multiple GC threads, each GC thread marks all Capabilities
999 for which (c `mod` n == 0), for Capability c and thread n.
1000 ------------------------------------------------------------------------ */
1003 markCapability (evac_fn evac
, void *user
, Capability
*cap
,
1004 rtsBool no_mark_sparks USED_IF_THREADS
)
1008 // Each GC thread is responsible for following roots from the
1009 // Capability of the same number. There will usually be the same
1010 // or fewer Capabilities as GC threads, but just in case there
1011 // are more, we mark every Capability whose number is the GC
1012 // thread's index plus a multiple of the number of GC threads.
1013 evac(user
, (StgClosure
**)(void *)&cap
->run_queue_hd
);
1014 evac(user
, (StgClosure
**)(void *)&cap
->run_queue_tl
);
1015 #if defined(THREADED_RTS)
1016 evac(user
, (StgClosure
**)(void *)&cap
->inbox
);
1018 for (incall
= cap
->suspended_ccalls
; incall
!= NULL
;
1019 incall
=incall
->next
) {
1020 evac(user
, (StgClosure
**)(void *)&incall
->suspended_tso
);
1023 #if defined(THREADED_RTS)
1024 if (!no_mark_sparks
) {
1025 traverseSparkQueue (evac
, user
, cap
);
1029 // Free STM structures for this Capability
1034 markCapabilities (evac_fn evac
, void *user
)
1037 for (n
= 0; n
< n_capabilities
; n
++) {
1038 markCapability(evac
, user
, capabilities
[n
], rtsFalse
);
1042 #if defined(THREADED_RTS)
1043 rtsBool
checkSparkCountInvariant (void)
1045 SparkCounters sparks
= { 0, 0, 0, 0, 0, 0 };
1046 StgWord64 remaining
= 0;
1049 for (i
= 0; i
< n_capabilities
; i
++) {
1050 sparks
.created
+= capabilities
[i
]->spark_stats
.created
;
1051 sparks
.dud
+= capabilities
[i
]->spark_stats
.dud
;
1052 sparks
.overflowed
+= capabilities
[i
]->spark_stats
.overflowed
;
1053 sparks
.converted
+= capabilities
[i
]->spark_stats
.converted
;
1054 sparks
.gcd
+= capabilities
[i
]->spark_stats
.gcd
;
1055 sparks
.fizzled
+= capabilities
[i
]->spark_stats
.fizzled
;
1056 remaining
+= sparkPoolSize(capabilities
[i
]->sparks
);
1060 * created = converted + remaining + gcd + fizzled
1062 debugTrace(DEBUG_sparks
,"spark invariant: %ld == %ld + %ld + %ld + %ld "
1063 "(created == converted + remaining + gcd + fizzled)",
1064 sparks
.created
, sparks
.converted
, remaining
,
1065 sparks
.gcd
, sparks
.fizzled
);
1067 return (sparks
.created
==
1068 sparks
.converted
+ remaining
+ sparks
.gcd
+ sparks
.fizzled
);