The OpenD Programming Language

1 /**
2  * The fiber module provides OS-indepedent lightweight threads aka fibers.
3  *
4  * Copyright: Copyright Sean Kelly 2005 - 2012.
5  * License: Distributed under the
6  *      $(LINK2 http://www.boost.org/LICENSE_1_0.txt, Boost Software License 1.0).
7  *    (See accompanying file LICENSE)
8  * Authors:   Sean Kelly, Walter Bright, Alex Rønne Petersen, Martin Nowak
9  * Source:    $(DRUNTIMESRC core/thread/fiber.d)
10  */
11 
12 module core.thread.fiber;
13 
14 import core.thread.osthread;
15 import core.thread.threadgroup;
16 import core.thread.types;
17 import core.thread.context;
18 
19 import core.memory : pageSize;
20 
21 ///////////////////////////////////////////////////////////////////////////////
22 // Fiber Platform Detection
23 ///////////////////////////////////////////////////////////////////////////////
24 
25 version (GNU)
26 {
27     import gcc.builtins;
28     version (GNU_StackGrowsDown)
29         version = StackGrowsDown;
30 }
31 else
32 {
33     // this should be true for most architectures
34     version = StackGrowsDown;
35 }
36 
37 version (Windows)
38 {
39     import core.stdc.stdlib : malloc, free;
40     import core.sys.windows.winbase;
41     import core.sys.windows.winnt;
42 }
43 
44 private
45 {
46     version (D_InlineAsm_X86)
47     {
48         version (Windows)
49             version = AsmX86_Windows;
50         else version (Posix)
51             version = AsmX86_Posix;
52 
53         version = AlignFiberStackTo16Byte;
54     }
55     else version (D_InlineAsm_X86_64)
56     {
57         version (Windows)
58         {
59             version = AsmX86_64_Windows;
60             version = AlignFiberStackTo16Byte;
61         }
62         else version (Posix)
63         {
64             version = AsmX86_64_Posix;
65             version = AlignFiberStackTo16Byte;
66         }
67     }
68     else version (PPC)
69     {
70         version (OSX)
71         {
72             version = AsmPPC_Darwin;
73             version = AsmExternal;
74             version = AlignFiberStackTo16Byte;
75         }
76         else version (Posix)
77         {
78             version = AsmPPC_Posix;
79             version = AsmExternal;
80         }
81     }
82     else version (PPC64)
83     {
84         version (OSX)
85         {
86             version = AsmPPC_Darwin;
87             version = AsmExternal;
88             version = AlignFiberStackTo16Byte;
89         }
90         else version (Posix)
91         {
92             version = AlignFiberStackTo16Byte;
93         }
94     }
95     else version (MIPS_O32)
96     {
97         version (Posix)
98         {
99             version = AsmMIPS_O32_Posix;
100             version = AsmExternal;
101         }
102     }
103     else version (AArch64)
104     {
105         version (Posix)
106         {
107             version = AsmAArch64_Posix;
108             version = AsmExternal;
109             version = AlignFiberStackTo16Byte;
110         }
111     }
112     else version (ARM)
113     {
114         version (Posix)
115         {
116             version = AsmARM_Posix;
117             version = AsmExternal;
118         }
119     }
120     else version (SPARC)
121     {
122         // NOTE: The SPARC ABI specifies only doubleword alignment.
123         version = AlignFiberStackTo16Byte;
124     }
125     else version (SPARC64)
126     {
127         version = AlignFiberStackTo16Byte;
128     }
129     else version (LoongArch64)
130     {
131         version (Posix)
132         {
133             version = AsmLoongArch64_Posix;
134             version = AsmExternal;
135             version = AlignFiberStackTo16Byte;
136         }
137     }
138 
139     version (Posix)
140     {
141         version (AsmX86_Windows)    {} else
142         version (AsmX86_Posix)      {} else
143         version (AsmX86_64_Windows) {} else
144         version (AsmX86_64_Posix)   {} else
145         version (AsmExternal)       {} else
146         {
147             // NOTE: The ucontext implementation requires architecture specific
148             //       data definitions to operate so testing for it must be done
149             //       by checking for the existence of ucontext_t rather than by
150             //       a version identifier.  Please note that this is considered
151             //       an obsolescent feature according to the POSIX spec, so a
152             //       custom solution is still preferred.
153             import core.sys.posix.ucontext;
154         }
155     }
156 }
157 
158 ///////////////////////////////////////////////////////////////////////////////
159 // Fiber Entry Point and Context Switch
160 ///////////////////////////////////////////////////////////////////////////////
161 
162 private
163 {
164     import core.atomic : atomicStore, cas, MemoryOrder;
165     import core.exception : onOutOfMemoryError;
166     import core.stdc.stdlib : abort;
167 
168     extern (C) void fiber_entryPoint() nothrow
169     {
170         Fiber   obj = Fiber.getThis();
171         assert( obj );
172 
173         assert( Thread.getThis().m_curr is obj.m_ctxt );
174         atomicStore!(MemoryOrder.raw)(*cast(shared)&Thread.getThis().m_lock, false);
175         obj.m_ctxt.tstack = obj.m_ctxt.bstack;
176         obj.m_state = Fiber.State.EXEC;
177 
178         try
179         {
180             obj.run();
181         }
182         catch ( Throwable t )
183         {
184             obj.m_unhandled = t;
185         }
186 
187         static if ( __traits( compiles, ucontext_t ) )
188           obj.m_ucur = &obj.m_utxt;
189 
190         obj.m_state = Fiber.State.TERM;
191         obj.switchOut();
192     }
193 
194   // Look above the definition of 'class Fiber' for some information about the implementation of this routine
195   version (AsmExternal)
196   {
197       extern (C) void fiber_switchContext( void** oldp, void* newp ) nothrow @nogc;
198       version (AArch64)
199           extern (C) void fiber_trampoline() nothrow;
200   }
201   else
202     extern (C) void fiber_switchContext( void** oldp, void* newp ) nothrow @nogc
203     {
204         // NOTE: The data pushed and popped in this routine must match the
205         //       default stack created by Fiber.initStack or the initial
206         //       switch into a new context will fail.
207 
208         version (AsmX86_Windows)
209         {
210             asm pure nothrow @nogc
211             {
212                 naked;
213 
214                 // save current stack state
215                 push EBP;
216                 mov  EBP, ESP;
217                 push EDI;
218                 push ESI;
219                 push EBX;
220                 push dword ptr FS:[0];
221                 push dword ptr FS:[4];
222                 push dword ptr FS:[8];
223                 push EAX;
224 
225                 // store oldp again with more accurate address
226                 mov EAX, dword ptr 8[EBP];
227                 mov [EAX], ESP;
228                 // load newp to begin context switch
229                 mov ESP, dword ptr 12[EBP];
230 
231                 // load saved state from new stack
232                 pop EAX;
233                 pop dword ptr FS:[8];
234                 pop dword ptr FS:[4];
235                 pop dword ptr FS:[0];
236                 pop EBX;
237                 pop ESI;
238                 pop EDI;
239                 pop EBP;
240 
241                 // 'return' to complete switch
242                 pop ECX;
243                 jmp ECX;
244             }
245         }
246         else version (AsmX86_64_Windows)
247         {
248             asm pure nothrow @nogc
249             {
250                 naked;
251 
252                 // save current stack state
253                 // NOTE: When changing the layout of registers on the stack,
254                 //       make sure that the XMM registers are still aligned.
255                 //       On function entry, the stack is guaranteed to not
256                 //       be aligned to 16 bytes because of the return address
257                 //       on the stack.
258                 push RBP;
259                 mov  RBP, RSP;
260                 push R12;
261                 push R13;
262                 push R14;
263                 push R15;
264                 push RDI;
265                 push RSI;
266                 // 7 registers = 56 bytes; stack is now aligned to 16 bytes
267                 sub RSP, 160;
268                 movdqa [RSP + 144], XMM6;
269                 movdqa [RSP + 128], XMM7;
270                 movdqa [RSP + 112], XMM8;
271                 movdqa [RSP + 96], XMM9;
272                 movdqa [RSP + 80], XMM10;
273                 movdqa [RSP + 64], XMM11;
274                 movdqa [RSP + 48], XMM12;
275                 movdqa [RSP + 32], XMM13;
276                 movdqa [RSP + 16], XMM14;
277                 movdqa [RSP], XMM15;
278                 push RBX;
279                 xor  RAX,RAX;
280                 push qword ptr GS:[RAX];
281                 push qword ptr GS:8[RAX];
282                 push qword ptr GS:16[RAX];
283 
284                 // store oldp
285                 mov [RCX], RSP;
286                 // load newp to begin context switch
287                 mov RSP, RDX;
288 
289                 // load saved state from new stack
290                 pop qword ptr GS:16[RAX];
291                 pop qword ptr GS:8[RAX];
292                 pop qword ptr GS:[RAX];
293                 pop RBX;
294                 movdqa XMM15, [RSP];
295                 movdqa XMM14, [RSP + 16];
296                 movdqa XMM13, [RSP + 32];
297                 movdqa XMM12, [RSP + 48];
298                 movdqa XMM11, [RSP + 64];
299                 movdqa XMM10, [RSP + 80];
300                 movdqa XMM9, [RSP + 96];
301                 movdqa XMM8, [RSP + 112];
302                 movdqa XMM7, [RSP + 128];
303                 movdqa XMM6, [RSP + 144];
304                 add RSP, 160;
305                 pop RSI;
306                 pop RDI;
307                 pop R15;
308                 pop R14;
309                 pop R13;
310                 pop R12;
311                 pop RBP;
312 
313                 // 'return' to complete switch
314                 pop RCX;
315                 jmp RCX;
316             }
317         }
318         else version (AsmX86_Posix)
319         {
320             asm pure nothrow @nogc
321             {
322                 naked;
323 
324                 // save current stack state
325                 push EBP;
326                 mov  EBP, ESP;
327                 push EDI;
328                 push ESI;
329                 push EBX;
330                 push EAX;
331 
332                 // store oldp again with more accurate address
333                 mov EAX, dword ptr 8[EBP];
334                 mov [EAX], ESP;
335                 // load newp to begin context switch
336                 mov ESP, dword ptr 12[EBP];
337 
338                 // load saved state from new stack
339                 pop EAX;
340                 pop EBX;
341                 pop ESI;
342                 pop EDI;
343                 pop EBP;
344 
345                 // 'return' to complete switch
346                 pop ECX;
347                 jmp ECX;
348             }
349         }
350         else version (AsmX86_64_Posix)
351         {
352             asm pure nothrow @nogc
353             {
354                 naked;
355 
356                 // save current stack state
357                 push RBP;
358                 mov  RBP, RSP;
359                 push RBX;
360                 push R12;
361                 push R13;
362                 push R14;
363                 push R15;
364 
365                 // store oldp
366                 mov [RDI], RSP;
367                 // load newp to begin context switch
368                 mov RSP, RSI;
369 
370                 // load saved state from new stack
371                 pop R15;
372                 pop R14;
373                 pop R13;
374                 pop R12;
375                 pop RBX;
376                 pop RBP;
377 
378                 // 'return' to complete switch
379                 pop RCX;
380                 jmp RCX;
381             }
382         }
383         else static if ( __traits( compiles, ucontext_t ) )
384         {
385             Fiber   cfib = Fiber.getThis();
386             void*   ucur = cfib.m_ucur;
387 
388             *oldp = &ucur;
389             swapcontext( **(cast(ucontext_t***) oldp),
390                           *(cast(ucontext_t**)  newp) );
391         }
392         else
393             static assert(0, "Not implemented");
394     }
395 }
396 
397 
398 ///////////////////////////////////////////////////////////////////////////////
399 // Fiber
400 ///////////////////////////////////////////////////////////////////////////////
401 /*
402  * Documentation of Fiber internals:
403  *
404  * The main routines to implement when porting Fibers to new architectures are
405  * fiber_switchContext and initStack. Some version constants have to be defined
406  * for the new platform as well, search for "Fiber Platform Detection and Memory Allocation".
407  *
408  * Fibers are based on a concept called 'Context'. A Context describes the execution
409  * state of a Fiber or main thread which is fully described by the stack, some
410  * registers and a return address at which the Fiber/Thread should continue executing.
411  * Please note that not only each Fiber has a Context, but each thread also has got a
412  * Context which describes the threads stack and state. If you call Fiber fib; fib.call
413  * the first time in a thread you switch from Threads Context into the Fibers Context.
414  * If you call fib.yield in that Fiber you switch out of the Fibers context and back
415  * into the Thread Context. (However, this is not always the case. You can call a Fiber
416  * from within another Fiber, then you switch Contexts between the Fibers and the Thread
417  * Context is not involved)
418  *
419  * In all current implementations the registers and the return address are actually
420  * saved on a Contexts stack.
421  *
422  * The fiber_switchContext routine has got two parameters:
423  * void** a:  This is the _location_ where we have to store the current stack pointer,
424  *            the stack pointer of the currently executing Context (Fiber or Thread).
425  * void*  b:  This is the pointer to the stack of the Context which we want to switch into.
426  *            Note that we get the same pointer here as the one we stored into the void** a
427  *            in a previous call to fiber_switchContext.
428  *
429  * In the simplest case, a fiber_switchContext rountine looks like this:
430  * fiber_switchContext:
431  *     push {return Address}
432  *     push {registers}
433  *     copy {stack pointer} into {location pointed to by a}
434  *     //We have now switch to the stack of a different Context!
435  *     copy {b} into {stack pointer}
436  *     pop {registers}
437  *     pop {return Address}
438  *     jump to {return Address}
439  *
440  * The GC uses the value returned in parameter a to scan the Fibers stack. It scans from
441  * the stack base to that value. As the GC dislikes false pointers we can actually optimize
442  * this a little: By storing registers which can not contain references to memory managed
443  * by the GC outside of the region marked by the stack base pointer and the stack pointer
444  * saved in fiber_switchContext we can prevent the GC from scanning them.
445  * Such registers are usually floating point registers and the return address. In order to
446  * implement this, we return a modified stack pointer from fiber_switchContext. However,
447  * we have to remember that when we restore the registers from the stack!
448  *
449  * --------------------------- <= Stack Base
450  * |          Frame          | <= Many other stack frames
451  * |          Frame          |
452  * |-------------------------| <= The last stack frame. This one is created by fiber_switchContext
453  * | registers with pointers |
454  * |                         | <= Stack pointer. GC stops scanning here
455  * |   return address        |
456  * |floating point registers |
457  * --------------------------- <= Real Stack End
458  *
459  * fiber_switchContext:
460  *     push {registers with pointers}
461  *     copy {stack pointer} into {location pointed to by a}
462  *     push {return Address}
463  *     push {Floating point registers}
464  *     //We have now switch to the stack of a different Context!
465  *     copy {b} into {stack pointer}
466  *     //We now have to adjust the stack pointer to point to 'Real Stack End' so we can pop
467  *     //the FP registers
468  *     //+ or - depends on if your stack grows downwards or upwards
469  *     {stack pointer} = {stack pointer} +- ({FPRegisters}.sizeof + {return address}.sizeof}
470  *     pop {Floating point registers}
471  *     pop {return Address}
472  *     pop {registers with pointers}
473  *     jump to {return Address}
474  *
475  * So the question now is which registers need to be saved? This depends on the specific
476  * architecture ABI of course, but here are some general guidelines:
477  * - If a register is callee-save (if the callee modifies the register it must saved and
478  *   restored by the callee) it needs to be saved/restored in switchContext
479  * - If a register is caller-save it needn't be saved/restored. (Calling fiber_switchContext
480  *   is a function call and the compiler therefore already must save these registers before
481  *   calling fiber_switchContext)
482  * - Argument registers used for passing parameters to functions needn't be saved/restored
483  * - The return register needn't be saved/restored (fiber_switchContext hasn't got a return type)
484  * - All scratch registers needn't be saved/restored
485  * - The link register usually needn't be saved/restored (but sometimes it must be cleared -
486  *   see below for details)
487  * - The frame pointer register - if it exists - is usually callee-save
488  * - All current implementations do not save control registers
489  *
490  * What happens on the first switch into a Fiber? We never saved a state for this fiber before,
491  * but the initial state is prepared in the initStack routine. (This routine will also be called
492  * when a Fiber is being resetted). initStack must produce exactly the same stack layout as the
493  * part of fiber_switchContext which saves the registers. Pay special attention to set the stack
494  * pointer correctly if you use the GC optimization mentioned before. the return Address saved in
495  * initStack must be the address of fiber_entrypoint.
496  *
497  * There's now a small but important difference between the first context switch into a fiber and
498  * further context switches. On the first switch, Fiber.call is used and the returnAddress in
499  * fiber_switchContext will point to fiber_entrypoint. The important thing here is that this jump
500  * is a _function call_, we call fiber_entrypoint by jumping before it's function prologue. On later
501  * calls, the user used yield() in a function, and therefore the return address points into a user
502  * function, after the yield call. So here the jump in fiber_switchContext is a _function return_,
503  * not a function call!
504  *
505  * The most important result of this is that on entering a function, i.e. fiber_entrypoint, we
506  * would have to provide a return address / set the link register once fiber_entrypoint
507  * returns. Now fiber_entrypoint does never return and therefore the actual value of the return
508  * address / link register is never read/used and therefore doesn't matter. When fiber_switchContext
509  * performs a _function return_ the value in the link register doesn't matter either.
510  * However, the link register will still be saved to the stack in fiber_entrypoint and some
511  * exception handling / stack unwinding code might read it from this stack location and crash.
512  * The exact solution depends on your architecture, but see the ARM implementation for a way
513  * to deal with this issue.
514  *
515  * The ARM implementation is meant to be used as a kind of documented example implementation.
516  * Look there for a concrete example.
517  *
518  * FIXME: fiber_entrypoint might benefit from a @noreturn attribute, but D doesn't have one.
519  */
520 
521 /**
522  * This class provides a cooperative concurrency mechanism integrated with the
523  * threading and garbage collection functionality.  Calling a fiber may be
524  * considered a blocking operation that returns when the fiber yields (via
525  * Fiber.yield()).  Execution occurs within the context of the calling thread
526  * so synchronization is not necessary to guarantee memory visibility so long
527  * as the same thread calls the fiber each time.  Please note that there is no
528  * requirement that a fiber be bound to one specific thread.  Rather, fibers
529  * may be freely passed between threads so long as they are not currently
530  * executing.  Like threads, a new fiber thread may be created using either
531  * derivation or composition, as in the following example.
532  *
533  * Warning:
534  * Status registers are not saved by the current implementations. This means
535  * floating point exception status bits (overflow, divide by 0), rounding mode
536  * and similar stuff is set per-thread, not per Fiber!
537  *
538  * Warning:
539  * On ARM FPU registers are not saved if druntime was compiled as ARM_SoftFloat.
540  * If such a build is used on a ARM_SoftFP system which actually has got a FPU
541  * and other libraries are using the FPU registers (other code is compiled
542  * as ARM_SoftFP) this can cause problems. Druntime must be compiled as
543  * ARM_SoftFP in this case.
544  *
545  * Authors: Based on a design by Mikola Lysenko.
546  */
547 class Fiber
548 {
549     ///////////////////////////////////////////////////////////////////////////
550     // Initialization
551     ///////////////////////////////////////////////////////////////////////////
552 
553     version (Windows)
554         // exception handling walks the stack, invoking DbgHelp.dll which
555         // needs up to 16k of stack space depending on the version of DbgHelp.dll,
556         // the existence of debug symbols and other conditions. Avoid causing
557         // stack overflows by defaulting to a larger stack size
558         enum defaultStackPages = 8;
559     else version (OSX)
560     {
561         version (X86_64)
562             // libunwind on macOS 11 now requires more stack space than 16k, so
563             // default to a larger stack size. This is only applied to X86 as
564             // the pageSize is still 4k, however on AArch64 it is 16k.
565             enum defaultStackPages = 8;
566         else
567             enum defaultStackPages = 4;
568     }
569     else
570         enum defaultStackPages = 4;
571 
572     /**
573      * Initializes a fiber object which is associated with a static
574      * D function.
575      *
576      * Params:
577      *  fn = The fiber function.
578      *  sz = The stack size for this fiber.
579      *  guardPageSize = size of the guard page to trap fiber's stack
580      *                  overflows. Beware that using this will increase
581      *                  the number of mmaped regions on platforms using mmap
582      *                  so an OS-imposed limit may be hit.
583      *
584      * In:
585      *  fn must not be null.
586      */
587     this( void function() fn, size_t sz = pageSize * defaultStackPages,
588           size_t guardPageSize = pageSize ) nothrow
589     in
590     {
591         assert( fn );
592     }
593     do
594     {
595         allocStack( sz, guardPageSize );
596         reset( fn );
597     }
598 
599 
600     /**
601      * Initializes a fiber object which is associated with a dynamic
602      * D function.
603      *
604      * Params:
605      *  dg = The fiber function.
606      *  sz = The stack size for this fiber.
607      *  guardPageSize = size of the guard page to trap fiber's stack
608      *                  overflows. Beware that using this will increase
609      *                  the number of mmaped regions on platforms using mmap
610      *                  so an OS-imposed limit may be hit.
611      *
612      * In:
613      *  dg must not be null.
614      */
615     this( void delegate() dg, size_t sz = pageSize * defaultStackPages,
616           size_t guardPageSize = pageSize ) nothrow
617     {
618         allocStack( sz, guardPageSize );
619         reset( cast(void delegate() const) dg );
620     }
621 
622 
623     /**
624      * Cleans up any remaining resources used by this object.
625      */
626     ~this() nothrow @nogc @system
627     {
628         // NOTE: A live reference to this object will exist on its associated
629         //       stack from the first time its call() method has been called
630         //       until its execution completes with State.TERM.  Thus, the only
631         //       times this dtor should be called are either if the fiber has
632         //       terminated (and therefore has no active stack) or if the user
633         //       explicitly deletes this object.  The latter case is an error
634         //       but is not easily tested for, since State.HOLD may imply that
635         //       the fiber was just created but has never been run.  There is
636         //       not a compelling case to create a State.INIT just to offer a
637         //       means of ensuring the user isn't violating this object's
638         //       contract, so for now this requirement will be enforced by
639         //       documentation only.
640         freeStack();
641     }
642 
643 
644     ///////////////////////////////////////////////////////////////////////////
645     // General Actions
646     ///////////////////////////////////////////////////////////////////////////
647 
648 
649     /**
650      * Transfers execution to this fiber object.  The calling context will be
651      * suspended until the fiber calls Fiber.yield() or until it terminates
652      * via an unhandled exception.
653      *
654      * Params:
655      *  rethrow = Rethrow any unhandled exception which may have caused this
656      *            fiber to terminate.
657      *
658      * In:
659      *  This fiber must be in state HOLD.
660      *
661      * Throws:
662      *  Any exception not handled by the joined thread.
663      *
664      * Returns:
665      *  Any exception not handled by this fiber if rethrow = false, null
666      *  otherwise.
667      */
668     // Not marked with any attributes, even though `nothrow @nogc` works
669     // because it calls arbitrary user code. Most of the implementation
670     // is already `@nogc nothrow`, but in order for `Fiber.call` to
671     // propagate the attributes of the user's function, the Fiber
672     // class needs to be templated.
673     final Throwable call( Rethrow rethrow = Rethrow.yes )
674     {
675         return rethrow ? call!(Rethrow.yes)() : call!(Rethrow.no);
676     }
677 
678     /// ditto
679     final Throwable call( Rethrow rethrow )()
680     {
681         callImpl();
682         if ( m_unhandled )
683         {
684             Throwable t = m_unhandled;
685             m_unhandled = null;
686             static if ( rethrow )
687                 throw t;
688             else
689                 return t;
690         }
691         return null;
692     }
693 
694     private void callImpl() nothrow @nogc
695     in
696     {
697         assert( m_state == State.HOLD );
698     }
699     do
700     {
701         Fiber   cur = getThis();
702 
703         static if ( __traits( compiles, ucontext_t ) )
704             m_ucur = cur ? &cur.m_utxt : &Fiber.sm_utxt;
705 
706         setThis( this );
707         this.switchIn();
708         setThis( cur );
709 
710         static if ( __traits( compiles, ucontext_t ) )
711             m_ucur = null;
712 
713         // NOTE: If the fiber has terminated then the stack pointers must be
714         //       reset.  This ensures that the stack for this fiber is not
715         //       scanned if the fiber has terminated.  This is necessary to
716         //       prevent any references lingering on the stack from delaying
717         //       the collection of otherwise dead objects.  The most notable
718         //       being the current object, which is referenced at the top of
719         //       fiber_entryPoint.
720         if ( m_state == State.TERM )
721         {
722             m_ctxt.tstack = m_ctxt.bstack;
723         }
724     }
725 
726     /// Flag to control rethrow behavior of $(D $(LREF call))
727     enum Rethrow : bool { no, yes }
728 
729     /**
730      * Resets this fiber so that it may be re-used, optionally with a
731      * new function/delegate.  This routine should only be called for
732      * fibers that have terminated, as doing otherwise could result in
733      * scope-dependent functionality that is not executed.
734      * Stack-based classes, for example, may not be cleaned up
735      * properly if a fiber is reset before it has terminated.
736      *
737      * In:
738      *  This fiber must be in state TERM or HOLD.
739      */
740     final void reset() nothrow @nogc
741     in
742     {
743         assert( m_state == State.TERM || m_state == State.HOLD );
744     }
745     do
746     {
747         m_ctxt.tstack = m_ctxt.bstack;
748         m_state = State.HOLD;
749         initStack();
750         m_unhandled = null;
751     }
752 
753     /// ditto
754     final void reset( void function() fn ) nothrow @nogc
755     {
756         reset();
757         m_call  = fn;
758     }
759 
760     /// ditto
761     final void reset( void delegate() dg ) nothrow @nogc
762     {
763         reset();
764         m_call  = dg;
765     }
766 
767     ///////////////////////////////////////////////////////////////////////////
768     // General Properties
769     ///////////////////////////////////////////////////////////////////////////
770 
771 
772     /// A fiber may occupy one of three states: HOLD, EXEC, and TERM.
773     enum State
774     {
775         /** The HOLD state applies to any fiber that is suspended and ready to
776         be called. */
777         HOLD,
778         /** The EXEC state will be set for any fiber that is currently
779         executing. */
780         EXEC,
781         /** The TERM state is set when a fiber terminates. Once a fiber
782         terminates, it must be reset before it may be called again. */
783         TERM
784     }
785 
786 
787     /**
788      * Gets the current state of this fiber.
789      *
790      * Returns:
791      *  The state of this fiber as an enumerated value.
792      */
793     final @property State state() const @safe pure nothrow @nogc
794     {
795         return m_state;
796     }
797 
798 
799     ///////////////////////////////////////////////////////////////////////////
800     // Actions on Calling Fiber
801     ///////////////////////////////////////////////////////////////////////////
802 
803 
804     /**
805      * Forces a context switch to occur away from the calling fiber.
806      */
807     static void yield() nothrow @nogc
808     {
809         Fiber   cur = getThis();
810         assert( cur, "Fiber.yield() called with no active fiber" );
811         assert( cur.m_state == State.EXEC );
812 
813         static if ( __traits( compiles, ucontext_t ) )
814           cur.m_ucur = &cur.m_utxt;
815 
816         cur.m_state = State.HOLD;
817         cur.switchOut();
818         cur.m_state = State.EXEC;
819     }
820 
821 
822     /**
823      * Forces a context switch to occur away from the calling fiber and then
824      * throws obj in the calling fiber.
825      *
826      * Params:
827      *  t = The object to throw.
828      *
829      * In:
830      *  t must not be null.
831      */
832     static void yieldAndThrow( Throwable t ) nothrow @nogc
833     in
834     {
835         assert( t );
836     }
837     do
838     {
839         Fiber   cur = getThis();
840         assert( cur, "Fiber.yield() called with no active fiber" );
841         assert( cur.m_state == State.EXEC );
842 
843         static if ( __traits( compiles, ucontext_t ) )
844           cur.m_ucur = &cur.m_utxt;
845 
846         cur.m_unhandled = t;
847         cur.m_state = State.HOLD;
848         cur.switchOut();
849         cur.m_state = State.EXEC;
850     }
851 
852 
853     ///////////////////////////////////////////////////////////////////////////
854     // Fiber Accessors
855     ///////////////////////////////////////////////////////////////////////////
856 
857 
858     /**
859      * Provides a reference to the calling fiber or null if no fiber is
860      * currently active.
861      *
862      * Returns:
863      *  The fiber object representing the calling fiber or null if no fiber
864      *  is currently active within this thread. The result of deleting this object is undefined.
865      */
866     static Fiber getThis() @safe nothrow @nogc
867     {
868         return sm_this;
869     }
870 
871 
872     ///////////////////////////////////////////////////////////////////////////
873     // Static Initialization
874     ///////////////////////////////////////////////////////////////////////////
875 
876 
877     version (Posix)
878     {
879         static this()
880         {
881             static if ( __traits( compiles, ucontext_t ) )
882             {
883               int status = getcontext( &sm_utxt );
884               assert( status == 0 );
885             }
886         }
887     }
888 
889 private:
890 
891     //
892     // Fiber entry point.  Invokes the function or delegate passed on
893     // construction (if any).
894     //
895     final void run()
896     {
897         m_call();
898     }
899 
900     //
901     // Standard fiber data
902     //
903     Callable            m_call;
904     bool                m_isRunning;
905     Throwable           m_unhandled;
906     State               m_state;
907 
908 
909 private:
910     ///////////////////////////////////////////////////////////////////////////
911     // Stack Management
912     ///////////////////////////////////////////////////////////////////////////
913 
914 
915     //
916     // Allocate a new stack for this fiber.
917     //
918     final void allocStack( size_t sz, size_t guardPageSize ) nothrow @system
919     in
920     {
921         assert( !m_pmem && !m_ctxt );
922     }
923     do
924     {
925         // adjust alloc size to a multiple of pageSize
926         sz += pageSize - 1;
927         sz -= sz % pageSize;
928 
929         // NOTE: This instance of Thread.Context is dynamic so Fiber objects
930         //       can be collected by the GC so long as no user level references
931         //       to the object exist.  If m_ctxt were not dynamic then its
932         //       presence in the global context list would be enough to keep
933         //       this object alive indefinitely.  An alternative to allocating
934         //       room for this struct explicitly would be to mash it into the
935         //       base of the stack being allocated below.  However, doing so
936         //       requires too much special logic to be worthwhile.
937         m_ctxt = new StackContext;
938 
939         version (Windows)
940         {
941             // reserve memory for stack
942             m_pmem = VirtualAlloc( null,
943                                    sz + guardPageSize,
944                                    MEM_RESERVE,
945                                    PAGE_NOACCESS );
946             if ( !m_pmem )
947                 onOutOfMemoryError();
948 
949             version (StackGrowsDown)
950             {
951                 void* stack = m_pmem + guardPageSize;
952                 void* guard = m_pmem;
953                 void* pbase = stack + sz;
954             }
955             else
956             {
957                 void* stack = m_pmem;
958                 void* guard = m_pmem + sz;
959                 void* pbase = stack;
960             }
961 
962             // allocate reserved stack segment
963             stack = VirtualAlloc( stack,
964                                   sz,
965                                   MEM_COMMIT,
966                                   PAGE_READWRITE );
967             if ( !stack )
968                 onOutOfMemoryError();
969 
970             if (guardPageSize)
971             {
972                 // allocate reserved guard page
973                 guard = VirtualAlloc( guard,
974                                       guardPageSize,
975                                       MEM_COMMIT,
976                                       PAGE_READWRITE | PAGE_GUARD );
977                 if ( !guard )
978                     onOutOfMemoryError();
979             }
980 
981             m_ctxt.bstack = pbase;
982             m_ctxt.tstack = pbase;
983             m_size = sz;
984         }
985         else
986         {
987             version (Posix) import core.sys.posix.sys.mman; // mmap, MAP_ANON
988 
989             static if ( __traits( compiles, ucontext_t ) )
990             {
991                 // Stack size must be at least the minimum allowable by the OS.
992                 if (sz < MINSIGSTKSZ)
993                     sz = MINSIGSTKSZ;
994             }
995 
996             static if ( __traits( compiles, mmap ) )
997             {
998                 // Allocate more for the memory guard
999                 sz += guardPageSize;
1000 
1001                 int mmap_flags = MAP_PRIVATE | MAP_ANON;
1002                 version (OpenBSD)
1003                     mmap_flags |= MAP_STACK;
1004 
1005                 m_pmem = mmap( null,
1006                                sz,
1007                                PROT_READ | PROT_WRITE,
1008                                mmap_flags,
1009                                -1,
1010                                0 );
1011                 if ( m_pmem == MAP_FAILED )
1012                     m_pmem = null;
1013             }
1014             else static if ( __traits( compiles, valloc ) )
1015             {
1016                 m_pmem = valloc( sz );
1017             }
1018             else static if ( __traits( compiles, malloc ) )
1019             {
1020                 m_pmem = malloc( sz );
1021             }
1022             else
1023             {
1024                 m_pmem = null;
1025             }
1026 
1027             if ( !m_pmem )
1028                 onOutOfMemoryError();
1029 
1030             version (StackGrowsDown)
1031             {
1032                 m_ctxt.bstack = m_pmem + sz;
1033                 m_ctxt.tstack = m_pmem + sz;
1034                 void* guard = m_pmem;
1035             }
1036             else
1037             {
1038                 m_ctxt.bstack = m_pmem;
1039                 m_ctxt.tstack = m_pmem;
1040                 void* guard = m_pmem + sz - guardPageSize;
1041             }
1042             m_size = sz;
1043 
1044             static if ( __traits( compiles, mmap ) )
1045             {
1046                 if (guardPageSize)
1047                 {
1048                     // protect end of stack
1049                     if ( mprotect(guard, guardPageSize, PROT_NONE) == -1 )
1050                         abort();
1051                 }
1052             }
1053             else
1054             {
1055                 // Supported only for mmap allocated memory - results are
1056                 // undefined if applied to memory not obtained by mmap
1057             }
1058         }
1059 
1060         Thread.add( m_ctxt );
1061     }
1062 
1063 
1064     //
1065     // Free this fiber's stack.
1066     //
1067     final void freeStack() nothrow @nogc @system
1068     in
1069     {
1070         assert( m_pmem && m_ctxt );
1071     }
1072     do
1073     {
1074         // NOTE: m_ctxt is guaranteed to be alive because it is held in the
1075         //       global context list.
1076         Thread.slock.lock_nothrow();
1077         scope(exit) Thread.slock.unlock_nothrow();
1078         Thread.remove( m_ctxt );
1079 
1080         version (Windows)
1081         {
1082             VirtualFree( m_pmem, 0, MEM_RELEASE );
1083         }
1084         else
1085         {
1086             import core.sys.posix.sys.mman; // munmap
1087 
1088             static if ( __traits( compiles, mmap ) )
1089             {
1090                 munmap( m_pmem, m_size );
1091             }
1092             else static if ( __traits( compiles, valloc ) )
1093             {
1094                 free( m_pmem );
1095             }
1096             else static if ( __traits( compiles, malloc ) )
1097             {
1098                 free( m_pmem );
1099             }
1100         }
1101         m_pmem = null;
1102         m_ctxt = null;
1103     }
1104 
1105 
1106     //
1107     // Initialize the allocated stack.
1108     // Look above the definition of 'class Fiber' for some information about the implementation of this routine
1109     //
1110     final void initStack() nothrow @nogc @system
1111     in
1112     {
1113         assert( m_ctxt.tstack && m_ctxt.tstack == m_ctxt.bstack );
1114         assert( cast(size_t) m_ctxt.bstack % (void*).sizeof == 0 );
1115     }
1116     do
1117     {
1118         void* pstack = m_ctxt.tstack;
1119         scope( exit )  m_ctxt.tstack = pstack;
1120 
1121         void push( size_t val ) nothrow
1122         {
1123             version (StackGrowsDown)
1124             {
1125                 pstack -= size_t.sizeof;
1126                 *(cast(size_t*) pstack) = val;
1127             }
1128             else
1129             {
1130                 pstack += size_t.sizeof;
1131                 *(cast(size_t*) pstack) = val;
1132             }
1133         }
1134 
1135         // NOTE: On OS X the stack must be 16-byte aligned according
1136         // to the IA-32 call spec. For x86_64 the stack also needs to
1137         // be aligned to 16-byte according to SysV AMD64 ABI.
1138         version (AlignFiberStackTo16Byte)
1139         {
1140             version (StackGrowsDown)
1141             {
1142                 pstack = cast(void*)(cast(size_t)(pstack) - (cast(size_t)(pstack) & 0x0F));
1143             }
1144             else
1145             {
1146                 pstack = cast(void*)(cast(size_t)(pstack) + (cast(size_t)(pstack) & 0x0F));
1147             }
1148         }
1149 
1150         version (AsmX86_Windows)
1151         {
1152             version (StackGrowsDown) {} else static assert( false );
1153 
1154             // On Windows Server 2008 and 2008 R2, an exploit mitigation
1155             // technique known as SEHOP is activated by default. To avoid
1156             // hijacking of the exception handler chain, the presence of a
1157             // Windows-internal handler (ntdll.dll!FinalExceptionHandler) at
1158             // its end is tested by RaiseException. If it is not present, all
1159             // handlers are disregarded, and the program is thus aborted
1160             // (see http://blogs.technet.com/b/srd/archive/2009/02/02/
1161             // preventing-the-exploitation-of-seh-overwrites-with-sehop.aspx).
1162             // For new threads, this handler is installed by Windows immediately
1163             // after creation. To make exception handling work in fibers, we
1164             // have to insert it for our new stacks manually as well.
1165             //
1166             // To do this, we first determine the handler by traversing the SEH
1167             // chain of the current thread until its end, and then construct a
1168             // registration block for the last handler on the newly created
1169             // thread. We then continue to push all the initial register values
1170             // for the first context switch as for the other implementations.
1171             //
1172             // Note that this handler is never actually invoked, as we install
1173             // our own one on top of it in the fiber entry point function.
1174             // Thus, it should not have any effects on OSes not implementing
1175             // exception chain verification.
1176 
1177             alias fp_t = void function(); // Actual signature not relevant.
1178             static struct EXCEPTION_REGISTRATION
1179             {
1180                 EXCEPTION_REGISTRATION* next; // sehChainEnd if last one.
1181                 fp_t handler;
1182             }
1183             enum sehChainEnd = cast(EXCEPTION_REGISTRATION*) 0xFFFFFFFF;
1184 
1185             __gshared static fp_t finalHandler = null;
1186             if ( finalHandler is null )
1187             {
1188                 static EXCEPTION_REGISTRATION* fs0() nothrow
1189                 {
1190                     asm pure nothrow @nogc
1191                     {
1192                         naked;
1193                         mov EAX, FS:[0];
1194                         ret;
1195                     }
1196                 }
1197                 auto reg = fs0();
1198                 while ( reg.next != sehChainEnd ) reg = reg.next;
1199 
1200                 // Benign races are okay here, just to avoid re-lookup on every
1201                 // fiber creation.
1202                 finalHandler = reg.handler;
1203             }
1204 
1205             // When linking with /safeseh (supported by LDC, but not DMD)
1206             // the exception chain must not extend to the very top
1207             // of the stack, otherwise the exception chain is also considered
1208             // invalid. Reserving additional 4 bytes at the top of the stack will
1209             // keep the EXCEPTION_REGISTRATION below that limit
1210             size_t reserve = EXCEPTION_REGISTRATION.sizeof + 4;
1211             pstack -= reserve;
1212             *(cast(EXCEPTION_REGISTRATION*)pstack) =
1213                 EXCEPTION_REGISTRATION( sehChainEnd, finalHandler );
1214             auto pChainEnd = pstack;
1215 
1216             push( cast(size_t) &fiber_entryPoint );                 // EIP
1217             push( cast(size_t) m_ctxt.bstack - reserve );           // EBP
1218             push( 0x00000000 );                                     // EDI
1219             push( 0x00000000 );                                     // ESI
1220             push( 0x00000000 );                                     // EBX
1221             push( cast(size_t) pChainEnd );                         // FS:[0]
1222             push( cast(size_t) m_ctxt.bstack );                     // FS:[4]
1223             push( cast(size_t) m_ctxt.bstack - m_size );            // FS:[8]
1224             push( 0x00000000 );                                     // EAX
1225         }
1226         else version (AsmX86_64_Windows)
1227         {
1228             // Using this trampoline instead of the raw fiber_entryPoint
1229             // ensures that during context switches, source and destination
1230             // stacks have the same alignment. Otherwise, the stack would need
1231             // to be shifted by 8 bytes for the first call, as fiber_entryPoint
1232             // is an actual function expecting a stack which is not aligned
1233             // to 16 bytes.
1234             static void trampoline()
1235             {
1236                 asm pure nothrow @nogc
1237                 {
1238                     naked;
1239                     sub RSP, 32; // Shadow space (Win64 calling convention)
1240                     call fiber_entryPoint;
1241                     xor RCX, RCX; // This should never be reached, as
1242                     jmp RCX;      // fiber_entryPoint must never return.
1243                 }
1244             }
1245 
1246             push( cast(size_t) &trampoline );                       // RIP
1247             push( 0x00000000_00000000 );                            // RBP
1248             push( 0x00000000_00000000 );                            // R12
1249             push( 0x00000000_00000000 );                            // R13
1250             push( 0x00000000_00000000 );                            // R14
1251             push( 0x00000000_00000000 );                            // R15
1252             push( 0x00000000_00000000 );                            // RDI
1253             push( 0x00000000_00000000 );                            // RSI
1254             push( 0x00000000_00000000 );                            // XMM6 (high)
1255             push( 0x00000000_00000000 );                            // XMM6 (low)
1256             push( 0x00000000_00000000 );                            // XMM7 (high)
1257             push( 0x00000000_00000000 );                            // XMM7 (low)
1258             push( 0x00000000_00000000 );                            // XMM8 (high)
1259             push( 0x00000000_00000000 );                            // XMM8 (low)
1260             push( 0x00000000_00000000 );                            // XMM9 (high)
1261             push( 0x00000000_00000000 );                            // XMM9 (low)
1262             push( 0x00000000_00000000 );                            // XMM10 (high)
1263             push( 0x00000000_00000000 );                            // XMM10 (low)
1264             push( 0x00000000_00000000 );                            // XMM11 (high)
1265             push( 0x00000000_00000000 );                            // XMM11 (low)
1266             push( 0x00000000_00000000 );                            // XMM12 (high)
1267             push( 0x00000000_00000000 );                            // XMM12 (low)
1268             push( 0x00000000_00000000 );                            // XMM13 (high)
1269             push( 0x00000000_00000000 );                            // XMM13 (low)
1270             push( 0x00000000_00000000 );                            // XMM14 (high)
1271             push( 0x00000000_00000000 );                            // XMM14 (low)
1272             push( 0x00000000_00000000 );                            // XMM15 (high)
1273             push( 0x00000000_00000000 );                            // XMM15 (low)
1274             push( 0x00000000_00000000 );                            // RBX
1275             push( 0xFFFFFFFF_FFFFFFFF );                            // GS:[0]
1276             version (StackGrowsDown)
1277             {
1278                 push( cast(size_t) m_ctxt.bstack );                 // GS:[8]
1279                 push( cast(size_t) m_ctxt.bstack - m_size );        // GS:[16]
1280             }
1281             else
1282             {
1283                 push( cast(size_t) m_ctxt.bstack );                 // GS:[8]
1284                 push( cast(size_t) m_ctxt.bstack + m_size );        // GS:[16]
1285             }
1286         }
1287         else version (AsmX86_Posix)
1288         {
1289             push( 0x00000000 );                                     // Return address of fiber_entryPoint call
1290             push( cast(size_t) &fiber_entryPoint );                 // EIP
1291             push( cast(size_t) m_ctxt.bstack );                     // EBP
1292             push( 0x00000000 );                                     // EDI
1293             push( 0x00000000 );                                     // ESI
1294             push( 0x00000000 );                                     // EBX
1295             push( 0x00000000 );                                     // EAX
1296         }
1297         else version (AsmX86_64_Posix)
1298         {
1299             push( 0x00000000_00000000 );                            // Return address of fiber_entryPoint call
1300             push( cast(size_t) &fiber_entryPoint );                 // RIP
1301             push( cast(size_t) m_ctxt.bstack );                     // RBP
1302             push( 0x00000000_00000000 );                            // RBX
1303             push( 0x00000000_00000000 );                            // R12
1304             push( 0x00000000_00000000 );                            // R13
1305             push( 0x00000000_00000000 );                            // R14
1306             push( 0x00000000_00000000 );                            // R15
1307         }
1308         else version (AsmPPC_Posix)
1309         {
1310             version (StackGrowsDown)
1311             {
1312                 pstack -= int.sizeof * 5;
1313             }
1314             else
1315             {
1316                 pstack += int.sizeof * 5;
1317             }
1318 
1319             push( cast(size_t) &fiber_entryPoint );     // link register
1320             push( 0x00000000 );                         // control register
1321             push( 0x00000000 );                         // old stack pointer
1322 
1323             // GPR values
1324             version (StackGrowsDown)
1325             {
1326                 pstack -= int.sizeof * 20;
1327             }
1328             else
1329             {
1330                 pstack += int.sizeof * 20;
1331             }
1332 
1333             assert( (cast(size_t) pstack & 0x0f) == 0 );
1334         }
1335         else version (AsmPPC_Darwin)
1336         {
1337             version (StackGrowsDown) {}
1338             else static assert(false, "PowerPC Darwin only supports decrementing stacks");
1339 
1340             uint wsize = size_t.sizeof;
1341 
1342             // linkage + regs + FPRs + VRs
1343             uint space = 8 * wsize + 20 * wsize + 18 * 8 + 12 * 16;
1344             (cast(ubyte*)pstack - space)[0 .. space] = 0;
1345 
1346             pstack -= wsize * 6;
1347             *cast(size_t*)pstack = cast(size_t) &fiber_entryPoint; // LR
1348             pstack -= wsize * 22;
1349 
1350             // On Darwin PPC64 pthread self is in R13 (which is reserved).
1351             // At present, it is not safe to migrate fibers between threads, but if that
1352             // changes, then updating the value of R13 will also need to be handled.
1353             version (PPC64)
1354               *cast(size_t*)(pstack + wsize) = cast(size_t) Thread.getThis().m_addr;
1355             assert( (cast(size_t) pstack & 0x0f) == 0 );
1356         }
1357         else version (AsmMIPS_O32_Posix)
1358         {
1359             version (StackGrowsDown) {}
1360             else static assert(0);
1361 
1362             /* We keep the FP registers and the return address below
1363              * the stack pointer, so they don't get scanned by the
1364              * GC. The last frame before swapping the stack pointer is
1365              * organized like the following.
1366              *
1367              *     |-----------|<= frame pointer
1368              *     |    $gp    |
1369              *     |   $s0-8   |
1370              *     |-----------|<= stack pointer
1371              *     |    $ra    |
1372              *     |  align(8) |
1373              *     |  $f20-30  |
1374              *     |-----------|
1375              *
1376              */
1377             enum SZ_GP = 10 * size_t.sizeof; // $gp + $s0-8
1378             enum SZ_RA = size_t.sizeof;      // $ra
1379             version (MIPS_HardFloat)
1380             {
1381                 enum SZ_FP = 6 * 8;          // $f20-30
1382                 enum ALIGN = -(SZ_FP + SZ_RA) & (8 - 1);
1383             }
1384             else
1385             {
1386                 enum SZ_FP = 0;
1387                 enum ALIGN = 0;
1388             }
1389 
1390             enum BELOW = SZ_FP + ALIGN + SZ_RA;
1391             enum ABOVE = SZ_GP;
1392             enum SZ = BELOW + ABOVE;
1393 
1394             (cast(ubyte*)pstack - SZ)[0 .. SZ] = 0;
1395             pstack -= ABOVE;
1396             *cast(size_t*)(pstack - SZ_RA) = cast(size_t)&fiber_entryPoint;
1397         }
1398         else version (AsmLoongArch64_Posix)
1399         {
1400             // Like others, FP registers and return address ($r1) are kept
1401             // below the saved stack top (tstack) to hide from GC scanning.
1402             // fiber_switchContext expects newp sp to look like this:
1403             //   10: $r21 (reserved)
1404             //    9: $r22 (frame pointer)
1405             //    8: $r23
1406             //   ...
1407             //    0: $r31 <-- newp tstack
1408             //   -1: $r1  (return address)  [&fiber_entryPoint]
1409             //   -2: $f24
1410             //   ...
1411             //   -9: $f31
1412 
1413             version (StackGrowsDown) {}
1414             else
1415                 static assert(false, "Only full descending stacks supported on LoongArch64");
1416 
1417             // Only need to set return address ($r1).  Everything else is fine
1418             // zero initialized.
1419             pstack -= size_t.sizeof * 11;    // skip past space reserved for $r21-$r31
1420             push (cast(size_t) &fiber_entryPoint);
1421             pstack += size_t.sizeof;         // adjust sp (newp) above lr
1422         }
1423         else version (AsmAArch64_Posix)
1424         {
1425             // Like others, FP registers and return address (lr) are kept
1426             // below the saved stack top (tstack) to hide from GC scanning.
1427             // fiber_switchContext expects newp sp to look like this:
1428             //   19: x19
1429             //   ...
1430             //    9: x29 (fp)  <-- newp tstack
1431             //    8: x30 (lr)  [&fiber_entryPoint]
1432             //    7: d8
1433             //   ...
1434             //    0: d15
1435 
1436             version (StackGrowsDown) {}
1437             else
1438                 static assert(false, "Only full descending stacks supported on AArch64");
1439 
1440             // Only need to set return address (lr).  Everything else is fine
1441             // zero initialized.
1442             pstack -= size_t.sizeof * 11;    // skip past x19-x29
1443             push(cast(size_t) &fiber_trampoline); // see threadasm.S for docs
1444             pstack += size_t.sizeof;         // adjust sp (newp) above lr
1445         }
1446         else version (AsmARM_Posix)
1447         {
1448             /* We keep the FP registers and the return address below
1449              * the stack pointer, so they don't get scanned by the
1450              * GC. The last frame before swapping the stack pointer is
1451              * organized like the following.
1452              *
1453              *   |  |-----------|<= 'frame starts here'
1454              *   |  |     fp    | (the actual frame pointer, r11 isn't
1455              *   |  |   r10-r4  |  updated and still points to the previous frame)
1456              *   |  |-----------|<= stack pointer
1457              *   |  |     lr    |
1458              *   |  | 4byte pad |
1459              *   |  |   d15-d8  |(if FP supported)
1460              *   |  |-----------|
1461              *   Y
1462              *   stack grows down: The pointer value here is smaller than some lines above
1463              */
1464             // frame pointer can be zero, r10-r4 also zero initialized
1465             version (StackGrowsDown)
1466                 pstack -= int.sizeof * 8;
1467             else
1468                 static assert(false, "Only full descending stacks supported on ARM");
1469 
1470             // link register
1471             push( cast(size_t) &fiber_entryPoint );
1472             /*
1473              * We do not push padding and d15-d8 as those are zero initialized anyway
1474              * Position the stack pointer above the lr register
1475              */
1476             pstack += int.sizeof * 1;
1477         }
1478         else static if ( __traits( compiles, ucontext_t ) )
1479         {
1480             getcontext( &m_utxt );
1481             m_utxt.uc_stack.ss_sp   = m_pmem;
1482             m_utxt.uc_stack.ss_size = m_size;
1483             makecontext( &m_utxt, &fiber_entryPoint, 0 );
1484             // NOTE: If ucontext is being used then the top of the stack will
1485             //       be a pointer to the ucontext_t struct for that fiber.
1486             push( cast(size_t) &m_utxt );
1487         }
1488         else
1489             static assert(0, "Not implemented");
1490     }
1491 
1492 
1493     StackContext*   m_ctxt;
1494     size_t          m_size;
1495     void*           m_pmem;
1496 
1497     static if ( __traits( compiles, ucontext_t ) )
1498     {
1499         // NOTE: The static ucontext instance is used to represent the context
1500         //       of the executing thread.
1501         static ucontext_t       sm_utxt = void;
1502         ucontext_t              m_utxt  = void;
1503         ucontext_t*             m_ucur  = null;
1504     }
1505 
1506 
1507 private:
1508     ///////////////////////////////////////////////////////////////////////////
1509     // Storage of Active Fiber
1510     ///////////////////////////////////////////////////////////////////////////
1511 
1512 
1513     //
1514     // Sets a thread-local reference to the current fiber object.
1515     //
1516     static void setThis( Fiber f ) nothrow @nogc
1517     {
1518         sm_this = f;
1519     }
1520 
1521     static Fiber sm_this;
1522 
1523 
1524 private:
1525     ///////////////////////////////////////////////////////////////////////////
1526     // Context Switching
1527     ///////////////////////////////////////////////////////////////////////////
1528 
1529 
1530     //
1531     // Switches into the stack held by this fiber.
1532     //
1533     final void switchIn() nothrow @nogc @system
1534     {
1535         Thread  tobj = Thread.getThis();
1536         void**  oldp = &tobj.m_curr.tstack;
1537         void*   newp = m_ctxt.tstack;
1538 
1539         // NOTE: The order of operations here is very important.  The current
1540         //       stack top must be stored before m_lock is set, and pushContext
1541         //       must not be called until after m_lock is set.  This process
1542         //       is intended to prevent a race condition with the suspend
1543         //       mechanism used for garbage collection.  If it is not followed,
1544         //       a badly timed collection could cause the GC to scan from the
1545         //       bottom of one stack to the top of another, or to miss scanning
1546         //       a stack that still contains valid data.  The old stack pointer
1547         //       oldp will be set again before the context switch to guarantee
1548         //       that it points to exactly the correct stack location so the
1549         //       successive pop operations will succeed.
1550         *oldp = getStackTop();
1551         atomicStore!(MemoryOrder.raw)(*cast(shared)&tobj.m_lock, true);
1552         tobj.pushContext( m_ctxt );
1553 
1554         fiber_switchContext( oldp, newp );
1555 
1556         // NOTE: As above, these operations must be performed in a strict order
1557         //       to prevent Bad Things from happening.
1558         tobj.popContext();
1559         atomicStore!(MemoryOrder.raw)(*cast(shared)&tobj.m_lock, false);
1560         tobj.m_curr.tstack = tobj.m_curr.bstack;
1561     }
1562 
1563 
1564     //
1565     // Switches out of the current stack and into the enclosing stack.
1566     //
1567     final void switchOut() nothrow @nogc @system
1568     {
1569         Thread  tobj = Thread.getThis();
1570         void**  oldp = &m_ctxt.tstack;
1571         void*   newp = tobj.m_curr.within.tstack;
1572 
1573         // NOTE: The order of operations here is very important.  The current
1574         //       stack top must be stored before m_lock is set, and pushContext
1575         //       must not be called until after m_lock is set.  This process
1576         //       is intended to prevent a race condition with the suspend
1577         //       mechanism used for garbage collection.  If it is not followed,
1578         //       a badly timed collection could cause the GC to scan from the
1579         //       bottom of one stack to the top of another, or to miss scanning
1580         //       a stack that still contains valid data.  The old stack pointer
1581         //       oldp will be set again before the context switch to guarantee
1582         //       that it points to exactly the correct stack location so the
1583         //       successive pop operations will succeed.
1584         *oldp = getStackTop();
1585         atomicStore!(MemoryOrder.raw)(*cast(shared)&tobj.m_lock, true);
1586 
1587         fiber_switchContext( oldp, newp );
1588 
1589         // NOTE: As above, these operations must be performed in a strict order
1590         //       to prevent Bad Things from happening.
1591         // NOTE: If use of this fiber is multiplexed across threads, the thread
1592         //       executing here may be different from the one above, so get the
1593         //       current thread handle before unlocking, etc.
1594         tobj = Thread.getThis();
1595         atomicStore!(MemoryOrder.raw)(*cast(shared)&tobj.m_lock, false);
1596         tobj.m_curr.tstack = tobj.m_curr.bstack;
1597     }
1598 }
1599 
1600 ///
1601 unittest {
1602     int counter;
1603 
1604     class DerivedFiber : Fiber
1605     {
1606         this()
1607         {
1608             super( &run );
1609         }
1610 
1611     private :
1612         void run()
1613         {
1614             counter += 2;
1615         }
1616     }
1617 
1618     void fiberFunc()
1619     {
1620         counter += 4;
1621         Fiber.yield();
1622         counter += 8;
1623     }
1624 
1625     // create instances of each type
1626     Fiber derived = new DerivedFiber();
1627     Fiber composed = new Fiber( &fiberFunc );
1628 
1629     assert( counter == 0 );
1630 
1631     derived.call();
1632     assert( counter == 2, "Derived fiber increment." );
1633 
1634     composed.call();
1635     assert( counter == 6, "First composed fiber increment." );
1636 
1637     counter += 16;
1638     assert( counter == 22, "Calling context increment." );
1639 
1640     composed.call();
1641     assert( counter == 30, "Second composed fiber increment." );
1642 
1643     // since each fiber has run to completion, each should have state TERM
1644     assert( derived.state == Fiber.State.TERM );
1645     assert( composed.state == Fiber.State.TERM );
1646 }
1647 
1648 version (CoreUnittest)
1649 {
1650     class TestFiber : Fiber
1651     {
1652         this()
1653         {
1654             super(&run);
1655         }
1656 
1657         void run()
1658         {
1659             foreach (i; 0 .. 1000)
1660             {
1661                 sum += i;
1662                 Fiber.yield();
1663             }
1664         }
1665 
1666         enum expSum = 1000 * 999 / 2;
1667         size_t sum;
1668     }
1669 
1670     void runTen()
1671     {
1672         TestFiber[10] fibs;
1673         foreach (ref fib; fibs)
1674             fib = new TestFiber();
1675 
1676         bool cont;
1677         do {
1678             cont = false;
1679             foreach (fib; fibs) {
1680                 if (fib.state == Fiber.State.HOLD)
1681                 {
1682                     fib.call();
1683                     cont |= fib.state != Fiber.State.TERM;
1684                 }
1685             }
1686         } while (cont);
1687 
1688         foreach (fib; fibs)
1689         {
1690             assert(fib.sum == TestFiber.expSum);
1691         }
1692     }
1693 }
1694 
1695 
1696 // Single thread running separate fibers
1697 unittest
1698 {
1699     runTen();
1700 }
1701 
1702 
1703 // Multiple threads running separate fibers
1704 unittest
1705 {
1706     auto group = new ThreadGroup();
1707     foreach (_; 0 .. 4)
1708     {
1709         group.create(&runTen);
1710     }
1711     group.joinAll();
1712 }
1713 
1714 
1715 // Multiple threads running shared fibers
1716 unittest
1717 {
1718     shared bool[10] locks;
1719     TestFiber[10] fibs;
1720 
1721     void runShared()
1722     {
1723         bool cont;
1724         do {
1725             cont = false;
1726             foreach (idx; 0 .. 10)
1727             {
1728                 if (cas(&locks[idx], false, true))
1729                 {
1730                     if (fibs[idx].state == Fiber.State.HOLD)
1731                     {
1732                         fibs[idx].call();
1733                         cont |= fibs[idx].state != Fiber.State.TERM;
1734                     }
1735                     locks[idx] = false;
1736                 }
1737                 else
1738                 {
1739                     cont = true;
1740                 }
1741             }
1742         } while (cont);
1743     }
1744 
1745     foreach (ref fib; fibs)
1746     {
1747         fib = new TestFiber();
1748     }
1749 
1750     auto group = new ThreadGroup();
1751     foreach (_; 0 .. 4)
1752     {
1753         group.create(&runShared);
1754     }
1755     group.joinAll();
1756 
1757     foreach (fib; fibs)
1758     {
1759         assert(fib.sum == TestFiber.expSum);
1760     }
1761 }
1762 
1763 
1764 // Test exception handling inside fibers.
1765 unittest
1766 {
1767     enum MSG = "Test message.";
1768     string caughtMsg;
1769     (new Fiber({
1770         try
1771         {
1772             throw new Exception(MSG);
1773         }
1774         catch (Exception e)
1775         {
1776             caughtMsg = e.msg;
1777         }
1778     })).call();
1779     assert(caughtMsg == MSG);
1780 }
1781 
1782 
1783 unittest
1784 {
1785     int x = 0;
1786 
1787     (new Fiber({
1788         x++;
1789     })).call();
1790     assert( x == 1 );
1791 }
1792 
1793 nothrow unittest
1794 {
1795     new Fiber({}).call!(Fiber.Rethrow.no)();
1796 }
1797 
1798 unittest
1799 {
1800     new Fiber({}).call(Fiber.Rethrow.yes);
1801     new Fiber({}).call(Fiber.Rethrow.no);
1802 }
1803 
1804 unittest
1805 {
1806     enum MSG = "Test message.";
1807 
1808     try
1809     {
1810         (new Fiber(function() {
1811             throw new Exception( MSG );
1812         })).call();
1813         assert( false, "Expected rethrown exception." );
1814     }
1815     catch ( Throwable t )
1816     {
1817         assert( t.msg == MSG );
1818     }
1819 }
1820 
1821 // Test exception chaining when switching contexts in finally blocks.
1822 unittest
1823 {
1824     static void throwAndYield(string msg) {
1825       try {
1826         throw new Exception(msg);
1827       } finally {
1828         Fiber.yield();
1829       }
1830     }
1831 
1832     static void fiber(string name) {
1833       try {
1834         try {
1835           throwAndYield(name ~ ".1");
1836         } finally {
1837           throwAndYield(name ~ ".2");
1838         }
1839       } catch (Exception e) {
1840         assert(e.msg == name ~ ".1");
1841         assert(e.next);
1842         assert(e.next.msg == name ~ ".2");
1843         assert(!e.next.next);
1844       }
1845     }
1846 
1847     auto first = new Fiber(() => fiber("first"));
1848     auto second = new Fiber(() => fiber("second"));
1849     first.call();
1850     second.call();
1851     first.call();
1852     second.call();
1853     first.call();
1854     second.call();
1855     assert(first.state == Fiber.State.TERM);
1856     assert(second.state == Fiber.State.TERM);
1857 }
1858 
1859 // Test Fiber resetting
1860 unittest
1861 {
1862     static string method;
1863 
1864     static void foo()
1865     {
1866         method = "foo";
1867     }
1868 
1869     void bar()
1870     {
1871         method = "bar";
1872     }
1873 
1874     static void expect(Fiber fib, string s)
1875     {
1876         assert(fib.state == Fiber.State.HOLD);
1877         fib.call();
1878         assert(fib.state == Fiber.State.TERM);
1879         assert(method == s); method = null;
1880     }
1881     auto fib = new Fiber(&foo);
1882     expect(fib, "foo");
1883 
1884     fib.reset();
1885     expect(fib, "foo");
1886 
1887     fib.reset(&foo);
1888     expect(fib, "foo");
1889 
1890     fib.reset(&bar);
1891     expect(fib, "bar");
1892 
1893     fib.reset(function void(){method = "function";});
1894     expect(fib, "function");
1895 
1896     fib.reset(delegate void(){method = "delegate";});
1897     expect(fib, "delegate");
1898 }
1899 
1900 // Test unsafe reset in hold state
1901 unittest
1902 {
1903     auto fib = new Fiber(function {ubyte[2048] buf = void; Fiber.yield();}, 4096);
1904     foreach (_; 0 .. 10)
1905     {
1906         fib.call();
1907         assert(fib.state == Fiber.State.HOLD);
1908         fib.reset();
1909     }
1910 }
1911 
1912 // stress testing GC stack scanning
1913 unittest
1914 {
1915     import core.memory;
1916     import core.time : dur;
1917 
1918     static void unreferencedThreadObject()
1919     {
1920         static void sleep() { Thread.sleep(dur!"msecs"(100)); }
1921         auto thread = new Thread(&sleep).start();
1922     }
1923     unreferencedThreadObject();
1924     GC.collect();
1925 
1926     static class Foo
1927     {
1928         this(int value)
1929         {
1930             _value = value;
1931         }
1932 
1933         int bar()
1934         {
1935             return _value;
1936         }
1937 
1938         int _value;
1939     }
1940 
1941     static void collect()
1942     {
1943         auto foo = new Foo(2);
1944         assert(foo.bar() == 2);
1945         GC.collect();
1946         Fiber.yield();
1947         GC.collect();
1948         assert(foo.bar() == 2);
1949     }
1950 
1951     auto fiber = new Fiber(&collect);
1952 
1953     fiber.call();
1954     GC.collect();
1955     fiber.call();
1956 
1957     // thread reference
1958     auto foo = new Foo(2);
1959 
1960     void collect2()
1961     {
1962         assert(foo.bar() == 2);
1963         GC.collect();
1964         Fiber.yield();
1965         GC.collect();
1966         assert(foo.bar() == 2);
1967     }
1968 
1969     fiber = new Fiber(&collect2);
1970 
1971     fiber.call();
1972     GC.collect();
1973     fiber.call();
1974 
1975     static void recurse(size_t cnt)
1976     {
1977         --cnt;
1978         Fiber.yield();
1979         if (cnt)
1980         {
1981             auto fib = new Fiber(() { recurse(cnt); });
1982             fib.call();
1983             GC.collect();
1984             fib.call();
1985         }
1986     }
1987     fiber = new Fiber(() { recurse(20); });
1988     fiber.call();
1989 }
1990 
1991 
1992 version (AsmX86_64_Windows)
1993 {
1994     // Test Windows x64 calling convention
1995     unittest
1996     {
1997         void testNonvolatileRegister(alias REG)()
1998         {
1999             auto zeroRegister = new Fiber(() {
2000                 mixin("asm pure nothrow @nogc { naked; xor "~REG~", "~REG~"; ret; }");
2001             });
2002             long after;
2003 
2004             mixin("asm pure nothrow @nogc { mov "~REG~", 0xFFFFFFFFFFFFFFFF; }");
2005             zeroRegister.call();
2006             mixin("asm pure nothrow @nogc { mov after, "~REG~"; }");
2007 
2008             assert(after == -1);
2009         }
2010 
2011         void testNonvolatileRegisterSSE(alias REG)()
2012         {
2013             auto zeroRegister = new Fiber(() {
2014                 mixin("asm pure nothrow @nogc { naked; xorpd "~REG~", "~REG~"; ret; }");
2015             });
2016             long[2] before = [0xFFFFFFFF_FFFFFFFF, 0xFFFFFFFF_FFFFFFFF], after;
2017 
2018             mixin("asm pure nothrow @nogc { movdqu "~REG~", before; }");
2019             zeroRegister.call();
2020             mixin("asm pure nothrow @nogc { movdqu after, "~REG~"; }");
2021 
2022             assert(before == after);
2023         }
2024 
2025         testNonvolatileRegister!("R12")();
2026         testNonvolatileRegister!("R13")();
2027         testNonvolatileRegister!("R14")();
2028         testNonvolatileRegister!("R15")();
2029         testNonvolatileRegister!("RDI")();
2030         testNonvolatileRegister!("RSI")();
2031         testNonvolatileRegister!("RBX")();
2032 
2033         testNonvolatileRegisterSSE!("XMM6")();
2034         testNonvolatileRegisterSSE!("XMM7")();
2035         testNonvolatileRegisterSSE!("XMM8")();
2036         testNonvolatileRegisterSSE!("XMM9")();
2037         testNonvolatileRegisterSSE!("XMM10")();
2038         testNonvolatileRegisterSSE!("XMM11")();
2039         testNonvolatileRegisterSSE!("XMM12")();
2040         testNonvolatileRegisterSSE!("XMM13")();
2041         testNonvolatileRegisterSSE!("XMM14")();
2042         testNonvolatileRegisterSSE!("XMM15")();
2043     }
2044 }
2045 
2046 
2047 version (D_InlineAsm_X86_64)
2048 {
2049     unittest
2050     {
2051         void testStackAlignment()
2052         {
2053             void* pRSP;
2054             asm pure nothrow @nogc
2055             {
2056                 mov pRSP, RSP;
2057             }
2058             assert((cast(size_t)pRSP & 0xF) == 0);
2059         }
2060 
2061         auto fib = new Fiber(&testStackAlignment);
2062         fib.call();
2063     }
2064 }