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