]> CyberLeo.Net >> Repos - FreeBSD/FreeBSD.git/blob - sys/amd64/amd64/exception.S
Expand the checks for UCR3 == PMAP_NO_CR3 to enable processes to be
[FreeBSD/FreeBSD.git] / sys / amd64 / amd64 / exception.S
1 /*-
2  * Copyright (c) 1989, 1990 William F. Jolitz.
3  * Copyright (c) 1990 The Regents of the University of California.
4  * Copyright (c) 2007-2018 The FreeBSD Foundation
5  * All rights reserved.
6  *
7  * Portions of this software were developed by A. Joseph Koshy under
8  * sponsorship from the FreeBSD Foundation and Google, Inc.
9  *
10  * Portions of this software were developed by
11  * Konstantin Belousov <kib@FreeBSD.org> under sponsorship from
12  * the FreeBSD Foundation.
13  *
14  * Redistribution and use in source and binary forms, with or without
15  * modification, are permitted provided that the following conditions
16  * are met:
17  * 1. Redistributions of source code must retain the above copyright
18  *    notice, this list of conditions and the following disclaimer.
19  * 2. Redistributions in binary form must reproduce the above copyright
20  *    notice, this list of conditions and the following disclaimer in the
21  *    documentation and/or other materials provided with the distribution.
22  * 3. Neither the name of the University nor the names of its contributors
23  *    may be used to endorse or promote products derived from this software
24  *    without specific prior written permission.
25  *
26  * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
27  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
28  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
29  * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
30  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
31  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
32  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
33  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
34  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
35  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
36  * SUCH DAMAGE.
37  *
38  * $FreeBSD$
39  */
40
41 #include "opt_atpic.h"
42 #include "opt_hwpmc_hooks.h"
43
44 #include "assym.inc"
45
46 #include <machine/asmacros.h>
47 #include <machine/psl.h>
48 #include <machine/trap.h>
49 #include <machine/specialreg.h>
50
51 #ifdef KDTRACE_HOOKS
52         .bss
53         .globl  dtrace_invop_jump_addr
54         .align  8
55         .type   dtrace_invop_jump_addr,@object
56         .size   dtrace_invop_jump_addr,8
57 dtrace_invop_jump_addr:
58         .zero   8
59         .globl  dtrace_invop_calltrap_addr
60         .align  8
61         .type   dtrace_invop_calltrap_addr,@object
62         .size   dtrace_invop_calltrap_addr,8
63 dtrace_invop_calltrap_addr:
64         .zero   8
65 #endif
66         .text
67 #ifdef HWPMC_HOOKS
68         ENTRY(start_exceptions)
69 #endif
70
71 /*****************************************************************************/
72 /* Trap handling                                                             */
73 /*****************************************************************************/
74 /*
75  * Trap and fault vector routines.
76  *
77  * All traps are 'interrupt gates', SDT_SYSIGT.  An interrupt gate pushes
78  * state on the stack but also disables interrupts.  This is important for
79  * us for the use of the swapgs instruction.  We cannot be interrupted
80  * until the GS.base value is correct.  For most traps, we automatically
81  * then enable interrupts if the interrupted context had them enabled.
82  * This is equivalent to the i386 port's use of SDT_SYS386TGT.
83  *
84  * The cpu will push a certain amount of state onto the kernel stack for
85  * the current process.  See amd64/include/frame.h.
86  * This includes the current RFLAGS (status register, which includes
87  * the interrupt disable state prior to the trap), the code segment register,
88  * and the return instruction pointer are pushed by the cpu.  The cpu
89  * will also push an 'error' code for certain traps.  We push a dummy
90  * error code for those traps where the cpu doesn't in order to maintain
91  * a consistent frame.  We also push a contrived 'trap number'.
92  *
93  * The CPU does not push the general registers, so we must do that, and we
94  * must restore them prior to calling 'iret'.  The CPU adjusts %cs and %ss
95  * but does not mess with %ds, %es, %gs or %fs.  We swap the %gs base for
96  * for the kernel mode operation shortly, without changes to the selector
97  * loaded.  Since superuser long mode works with any selectors loaded into
98  * segment registers other then %cs, which makes them mostly unused in long
99  * mode, and kernel does not reference %fs, leave them alone.  The segment
100  * registers are reloaded on return to the usermode.
101  */
102
103 MCOUNT_LABEL(user)
104 MCOUNT_LABEL(btrap)
105
106 /* Traps that we leave interrupts disabled for. */
107         .macro  TRAP_NOEN       l, trapno
108         PTI_ENTRY       \l,X\l
109         .globl  X\l
110         .type   X\l,@function
111 X\l:    subq $TF_RIP,%rsp
112         movl $\trapno,TF_TRAPNO(%rsp)
113         movq $0,TF_ADDR(%rsp)
114         movq $0,TF_ERR(%rsp)
115         jmp alltraps_noen
116         .endm
117
118         TRAP_NOEN       dbg, T_TRCTRAP
119         TRAP_NOEN       bpt, T_BPTFLT
120 #ifdef KDTRACE_HOOKS
121         TRAP_NOEN       dtrace_ret, T_DTRACE_RET
122 #endif
123
124 /* Regular traps; The cpu does not supply tf_err for these. */
125         .macro  TRAP    l, trapno
126         PTI_ENTRY       \l,X\l
127         .globl  X\l
128         .type   X\l,@function
129 X\l:
130         subq $TF_RIP,%rsp
131         movl $\trapno,TF_TRAPNO(%rsp)
132         movq $0,TF_ADDR(%rsp)
133         movq $0,TF_ERR(%rsp)
134         jmp alltraps
135         .endm
136
137         TRAP    div, T_DIVIDE
138         TRAP    ofl, T_OFLOW
139         TRAP    bnd, T_BOUND
140         TRAP    ill, T_PRIVINFLT
141         TRAP    dna, T_DNA
142         TRAP    fpusegm, T_FPOPFLT
143         TRAP    rsvd, T_RESERVED
144         TRAP    fpu, T_ARITHTRAP
145         TRAP    xmm, T_XMMFLT
146
147 /* This group of traps have tf_err already pushed by the cpu. */
148         .macro  TRAP_ERR        l, trapno
149         PTI_ENTRY       \l,X\l,has_err=1
150         .globl  X\l
151         .type   X\l,@function
152 X\l:
153         subq $TF_ERR,%rsp
154         movl $\trapno,TF_TRAPNO(%rsp)
155         movq $0,TF_ADDR(%rsp)
156         jmp alltraps
157         .endm
158
159         TRAP_ERR        tss, T_TSSFLT
160         TRAP_ERR        align, T_ALIGNFLT
161
162         /*
163          * alltraps entry point.  Use swapgs if this is the first time in the
164          * kernel from userland.  Reenable interrupts if they were enabled
165          * before the trap.  This approximates SDT_SYS386TGT on the i386 port.
166          */
167         SUPERALIGN_TEXT
168         .globl  alltraps
169         .type   alltraps,@function
170 alltraps:
171         movq    %rdi,TF_RDI(%rsp)
172         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
173         jz      1f              /* already running with kernel GS.base */
174         swapgs
175         movq    PCPU(CURPCB),%rdi
176         andl    $~PCB_FULL_IRET,PCB_FLAGS(%rdi)
177 1:      SAVE_SEGS
178         movq    %rdx,TF_RDX(%rsp)
179         movq    %rax,TF_RAX(%rsp)
180         movq    %rcx,TF_RCX(%rsp)
181         testb   $SEL_RPL_MASK,TF_CS(%rsp)
182         jz      2f
183         call    handle_ibrs_entry
184 2:      testl   $PSL_I,TF_RFLAGS(%rsp)
185         jz      alltraps_pushregs_no_rax
186         sti
187 alltraps_pushregs_no_rax:
188         movq    %rsi,TF_RSI(%rsp)
189         movq    %r8,TF_R8(%rsp)
190         movq    %r9,TF_R9(%rsp)
191         movq    %rbx,TF_RBX(%rsp)
192         movq    %rbp,TF_RBP(%rsp)
193         movq    %r10,TF_R10(%rsp)
194         movq    %r11,TF_R11(%rsp)
195         movq    %r12,TF_R12(%rsp)
196         movq    %r13,TF_R13(%rsp)
197         movq    %r14,TF_R14(%rsp)
198         movq    %r15,TF_R15(%rsp)
199         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
200         cld
201         FAKE_MCOUNT(TF_RIP(%rsp))
202 #ifdef KDTRACE_HOOKS
203         /*
204          * DTrace Function Boundary Trace (fbt) probes are triggered
205          * by int3 (0xcc) which causes the #BP (T_BPTFLT) breakpoint
206          * interrupt. For all other trap types, just handle them in
207          * the usual way.
208          */
209         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
210         jnz     calltrap                /* ignore userland traps */
211         cmpl    $T_BPTFLT,TF_TRAPNO(%rsp)
212         jne     calltrap
213
214         /* Check if there is no DTrace hook registered. */
215         cmpq    $0,dtrace_invop_jump_addr
216         je      calltrap
217
218         /*
219          * Set our jump address for the jump back in the event that
220          * the breakpoint wasn't caused by DTrace at all.
221          */
222         movq    $calltrap,dtrace_invop_calltrap_addr(%rip)
223
224         /* Jump to the code hooked in by DTrace. */
225         jmpq    *dtrace_invop_jump_addr
226 #endif
227         .globl  calltrap
228         .type   calltrap,@function
229 calltrap:
230         movq    %rsp,%rdi
231         call    trap_check
232         MEXITCOUNT
233         jmp     doreti                  /* Handle any pending ASTs */
234
235         /*
236          * alltraps_noen entry point.  Unlike alltraps above, we want to
237          * leave the interrupts disabled.  This corresponds to
238          * SDT_SYS386IGT on the i386 port.
239          */
240         SUPERALIGN_TEXT
241         .globl  alltraps_noen
242         .type   alltraps_noen,@function
243 alltraps_noen:
244         movq    %rdi,TF_RDI(%rsp)
245         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
246         jz      1f /* already running with kernel GS.base */
247         swapgs
248         movq    PCPU(CURPCB),%rdi
249         andl    $~PCB_FULL_IRET,PCB_FLAGS(%rdi)
250 1:      SAVE_SEGS
251         movq    %rdx,TF_RDX(%rsp)
252         movq    %rax,TF_RAX(%rsp)
253         movq    %rcx,TF_RCX(%rsp)
254         testb   $SEL_RPL_MASK,TF_CS(%rsp)
255         jz      alltraps_pushregs_no_rax
256         call    handle_ibrs_entry
257         jmp     alltraps_pushregs_no_rax
258
259 IDTVEC(dblfault)
260         subq    $TF_ERR,%rsp
261         movl    $T_DOUBLEFLT,TF_TRAPNO(%rsp)
262         movq    $0,TF_ADDR(%rsp)
263         movq    $0,TF_ERR(%rsp)
264         movq    %rdi,TF_RDI(%rsp)
265         movq    %rsi,TF_RSI(%rsp)
266         movq    %rdx,TF_RDX(%rsp)
267         movq    %rcx,TF_RCX(%rsp)
268         movq    %r8,TF_R8(%rsp)
269         movq    %r9,TF_R9(%rsp)
270         movq    %rax,TF_RAX(%rsp)
271         movq    %rbx,TF_RBX(%rsp)
272         movq    %rbp,TF_RBP(%rsp)
273         movq    %r10,TF_R10(%rsp)
274         movq    %r11,TF_R11(%rsp)
275         movq    %r12,TF_R12(%rsp)
276         movq    %r13,TF_R13(%rsp)
277         movq    %r14,TF_R14(%rsp)
278         movq    %r15,TF_R15(%rsp)
279         SAVE_SEGS
280         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
281         cld
282         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
283         jz      1f                      /* already running with kernel GS.base */
284         swapgs
285 1:
286         movq    PCPU(KCR3),%rax
287         cmpq    $~0,%rax
288         je      2f
289         movq    %rax,%cr3
290 2:      movq    %rsp,%rdi
291         call    dblfault_handler
292 3:      hlt
293         jmp     3b
294
295         ALIGN_TEXT
296 IDTVEC(page_pti)
297         testb   $SEL_RPL_MASK,PTI_CS-2*8(%rsp)
298         jz      Xpage
299         swapgs
300         pushq   %rax
301         movq    %cr3,%rax
302         movq    %rax,PCPU(SAVED_UCR3)
303         cmpq    $~0,PCPU(UCR3)
304         jne     1f
305         popq    %rax
306         jmp     2f
307 1:      pushq   %rdx
308         PTI_UUENTRY has_err=1
309 2:      subq    $TF_ERR,%rsp
310         movq    %rdi,TF_RDI(%rsp)
311         movq    %rax,TF_RAX(%rsp)
312         movq    %rdx,TF_RDX(%rsp)
313         movq    %rcx,TF_RCX(%rsp)
314         jmp     page_u
315 IDTVEC(page)
316         subq    $TF_ERR,%rsp
317         movq    %rdi,TF_RDI(%rsp)       /* free up GP registers */
318         movq    %rax,TF_RAX(%rsp)
319         movq    %rdx,TF_RDX(%rsp)
320         movq    %rcx,TF_RCX(%rsp)
321         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
322         jz      page_cr2                /* already running with kernel GS.base */
323         swapgs
324 page_u: movq    PCPU(CURPCB),%rdi
325         andl    $~PCB_FULL_IRET,PCB_FLAGS(%rdi)
326         movq    PCPU(SAVED_UCR3),%rax
327         movq    %rax,PCB_SAVED_UCR3(%rdi)
328         call    handle_ibrs_entry
329 page_cr2:
330         movq    %cr2,%rdi               /* preserve %cr2 before ..  */
331         movq    %rdi,TF_ADDR(%rsp)      /* enabling interrupts. */
332         SAVE_SEGS
333         movl    $T_PAGEFLT,TF_TRAPNO(%rsp)
334         testl   $PSL_I,TF_RFLAGS(%rsp)
335         jz      alltraps_pushregs_no_rax
336         sti
337         jmp     alltraps_pushregs_no_rax
338
339         /*
340          * We have to special-case this one.  If we get a trap in doreti() at
341          * the iretq stage, we'll reenter with the wrong gs state.  We'll have
342          * to do a special the swapgs in this case even coming from the kernel.
343          * XXX linux has a trap handler for their equivalent of load_gs().
344          *
345          * On the stack, we have the hardware interrupt frame to return
346          * to usermode (faulted) and another frame with error code, for
347          * fault.  For PTI, copy both frames to the main thread stack.
348          * Handle the potential 16-byte alignment adjustment incurred
349          * during the second fault by copying both frames independently
350          * while unwinding the stack in between.
351          */
352         .macro PROTF_ENTRY name,trapno
353 \name\()_pti_doreti:
354         swapgs
355         cmpq    $~0,PCPU(UCR3)
356         je      1f
357         pushq   %rax
358         pushq   %rdx
359         movq    PCPU(KCR3),%rax
360         movq    %rax,%cr3
361         movq    PCPU(RSP0),%rax
362         subq    $2*PTI_SIZE-3*8,%rax /* no err, %rax, %rdx in faulted frame */
363         MOVE_STACKS     (PTI_SIZE / 8)
364         addq    $PTI_SIZE,%rax
365         movq    PTI_RSP(%rsp),%rsp
366         MOVE_STACKS     (PTI_SIZE / 8 - 3)
367         subq    $PTI_SIZE,%rax
368         movq    %rax,%rsp
369         popq    %rdx
370         popq    %rax
371 1:      swapgs
372         jmp     X\name
373 IDTVEC(\name\()_pti)
374         cmpq    $doreti_iret,PTI_RIP-2*8(%rsp)
375         je      \name\()_pti_doreti
376         testb   $SEL_RPL_MASK,PTI_CS-2*8(%rsp) /* %rax, %rdx not yet pushed */
377         jz      X\name
378         PTI_UENTRY has_err=1
379         swapgs
380 IDTVEC(\name)
381         subq    $TF_ERR,%rsp
382         movl    $\trapno,TF_TRAPNO(%rsp)
383         jmp     prot_addrf
384         .endm
385
386         PROTF_ENTRY     missing, T_SEGNPFLT
387         PROTF_ENTRY     stk, T_STKFLT
388         PROTF_ENTRY     prot, T_PROTFLT
389
390 prot_addrf:
391         movq    $0,TF_ADDR(%rsp)
392         movq    %rdi,TF_RDI(%rsp)       /* free up a GP register */
393         movq    %rax,TF_RAX(%rsp)
394         movq    %rdx,TF_RDX(%rsp)
395         movq    %rcx,TF_RCX(%rsp)
396         movw    %fs,TF_FS(%rsp)
397         movw    %gs,TF_GS(%rsp)
398         leaq    doreti_iret(%rip),%rdi
399         cmpq    %rdi,TF_RIP(%rsp)
400         je      5f                      /* kernel but with user gsbase!! */
401         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
402         jz      6f                      /* already running with kernel GS.base */
403         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
404         jz      2f
405         cmpw    $KUF32SEL,TF_FS(%rsp)
406         jne     1f
407         rdfsbase %rax
408 1:      cmpw    $KUG32SEL,TF_GS(%rsp)
409         jne     2f
410         rdgsbase %rdx
411 2:      swapgs
412         movq    PCPU(CURPCB),%rdi
413         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
414         jz      4f
415         cmpw    $KUF32SEL,TF_FS(%rsp)
416         jne     3f
417         movq    %rax,PCB_FSBASE(%rdi)
418 3:      cmpw    $KUG32SEL,TF_GS(%rsp)
419         jne     4f
420         movq    %rdx,PCB_GSBASE(%rdi)
421 4:      call    handle_ibrs_entry
422         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)  /* always full iret from GPF */
423         movw    %es,TF_ES(%rsp)
424         movw    %ds,TF_DS(%rsp)
425         testl   $PSL_I,TF_RFLAGS(%rsp)
426         jz      alltraps_pushregs_no_rax
427         sti
428         jmp     alltraps_pushregs_no_rax
429
430 5:      swapgs
431 6:      movq    PCPU(CURPCB),%rdi
432         jmp     4b
433
434 /*
435  * Fast syscall entry point.  We enter here with just our new %cs/%ss set,
436  * and the new privilige level.  We are still running on the old user stack
437  * pointer.  We have to juggle a few things around to find our stack etc.
438  * swapgs gives us access to our PCPU space only.
439  *
440  * We do not support invoking this from a custom segment registers,
441  * esp. %cs, %ss, %fs, %gs, e.g. using entries from an LDT.
442  */
443         SUPERALIGN_TEXT
444 IDTVEC(fast_syscall_pti)
445         swapgs
446         movq    %rax,PCPU(SCRATCH_RAX)
447         cmpq    $~0,PCPU(UCR3)
448         je      fast_syscall_common
449         movq    PCPU(KCR3),%rax
450         movq    %rax,%cr3
451         jmp     fast_syscall_common
452         SUPERALIGN_TEXT
453 IDTVEC(fast_syscall)
454         swapgs
455         movq    %rax,PCPU(SCRATCH_RAX)
456 fast_syscall_common:
457         movq    %rsp,PCPU(SCRATCH_RSP)
458         movq    PCPU(RSP0),%rsp
459         /* Now emulate a trapframe. Make the 8 byte alignment odd for call. */
460         subq    $TF_SIZE,%rsp
461         /* defer TF_RSP till we have a spare register */
462         movq    %r11,TF_RFLAGS(%rsp)
463         movq    %rcx,TF_RIP(%rsp)       /* %rcx original value is in %r10 */
464         movq    PCPU(SCRATCH_RSP),%r11  /* %r11 already saved */
465         movq    %r11,TF_RSP(%rsp)       /* user stack pointer */
466         movq    PCPU(SCRATCH_RAX),%rax
467         movq    %rax,TF_RAX(%rsp)       /* syscall number */
468         movq    %rdx,TF_RDX(%rsp)       /* arg 3 */
469         SAVE_SEGS
470         call    handle_ibrs_entry
471         movq    PCPU(CURPCB),%r11
472         andl    $~PCB_FULL_IRET,PCB_FLAGS(%r11)
473         sti
474         movq    $KUDSEL,TF_SS(%rsp)
475         movq    $KUCSEL,TF_CS(%rsp)
476         movq    $2,TF_ERR(%rsp)
477         movq    %rdi,TF_RDI(%rsp)       /* arg 1 */
478         movq    %rsi,TF_RSI(%rsp)       /* arg 2 */
479         movq    %r10,TF_RCX(%rsp)       /* arg 4 */
480         movq    %r8,TF_R8(%rsp)         /* arg 5 */
481         movq    %r9,TF_R9(%rsp)         /* arg 6 */
482         movq    %rbx,TF_RBX(%rsp)       /* C preserved */
483         movq    %rbp,TF_RBP(%rsp)       /* C preserved */
484         movq    %r12,TF_R12(%rsp)       /* C preserved */
485         movq    %r13,TF_R13(%rsp)       /* C preserved */
486         movq    %r14,TF_R14(%rsp)       /* C preserved */
487         movq    %r15,TF_R15(%rsp)       /* C preserved */
488         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
489         FAKE_MCOUNT(TF_RIP(%rsp))
490         movq    PCPU(CURTHREAD),%rdi
491         movq    %rsp,TD_FRAME(%rdi)
492         movl    TF_RFLAGS(%rsp),%esi
493         andl    $PSL_T,%esi
494         call    amd64_syscall
495 1:      movq    PCPU(CURPCB),%rax
496         /* Disable interrupts before testing PCB_FULL_IRET. */
497         cli
498         testl   $PCB_FULL_IRET,PCB_FLAGS(%rax)
499         jnz     4f
500         /* Check for and handle AST's on return to userland. */
501         movq    PCPU(CURTHREAD),%rax
502         testl   $TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
503         jne     3f
504         call    handle_ibrs_exit
505         /* Restore preserved registers. */
506         MEXITCOUNT
507         movq    TF_RDI(%rsp),%rdi       /* bonus; preserve arg 1 */
508         movq    TF_RSI(%rsp),%rsi       /* bonus: preserve arg 2 */
509         movq    TF_RDX(%rsp),%rdx       /* return value 2 */
510         movq    TF_RAX(%rsp),%rax       /* return value 1 */
511         movq    TF_RFLAGS(%rsp),%r11    /* original %rflags */
512         movq    TF_RIP(%rsp),%rcx       /* original %rip */
513         movq    TF_RSP(%rsp),%rsp       /* user stack pointer */
514         cmpq    $~0,PCPU(UCR3)
515         je      2f
516         movq    PCPU(UCR3),%r9
517         movq    %r9,%cr3
518         xorl    %r9d,%r9d
519 2:      swapgs
520         sysretq
521
522 3:      /* AST scheduled. */
523         sti
524         movq    %rsp,%rdi
525         call    ast
526         jmp     1b
527
528 4:      /* Requested full context restore, use doreti for that. */
529         MEXITCOUNT
530         jmp     doreti
531
532 /*
533  * Here for CYA insurance, in case a "syscall" instruction gets
534  * issued from 32 bit compatibility mode. MSR_CSTAR has to point
535  * to *something* if EFER_SCE is enabled.
536  */
537 IDTVEC(fast_syscall32)
538         sysret
539
540 /*
541  * NMI handling is special.
542  *
543  * First, NMIs do not respect the state of the processor's RFLAGS.IF
544  * bit.  The NMI handler may be entered at any time, including when
545  * the processor is in a critical section with RFLAGS.IF == 0.
546  * The processor's GS.base value could be invalid on entry to the
547  * handler.
548  *
549  * Second, the processor treats NMIs specially, blocking further NMIs
550  * until an 'iretq' instruction is executed.  We thus need to execute
551  * the NMI handler with interrupts disabled, to prevent a nested interrupt
552  * from executing an 'iretq' instruction and inadvertently taking the
553  * processor out of NMI mode.
554  *
555  * Third, the NMI handler runs on its own stack (tss_ist2). The canonical
556  * GS.base value for the processor is stored just above the bottom of its
557  * NMI stack.  For NMIs taken from kernel mode, the current value in
558  * the processor's GS.base is saved at entry to C-preserved register %r12,
559  * the canonical value for GS.base is then loaded into the processor, and
560  * the saved value is restored at exit time.  For NMIs taken from user mode,
561  * the cheaper 'SWAPGS' instructions are used for swapping GS.base.
562  */
563
564 IDTVEC(nmi)
565         subq    $TF_RIP,%rsp
566         movl    $(T_NMI),TF_TRAPNO(%rsp)
567         movq    $0,TF_ADDR(%rsp)
568         movq    $0,TF_ERR(%rsp)
569         movq    %rdi,TF_RDI(%rsp)
570         movq    %rsi,TF_RSI(%rsp)
571         movq    %rdx,TF_RDX(%rsp)
572         movq    %rcx,TF_RCX(%rsp)
573         movq    %r8,TF_R8(%rsp)
574         movq    %r9,TF_R9(%rsp)
575         movq    %rax,TF_RAX(%rsp)
576         movq    %rbx,TF_RBX(%rsp)
577         movq    %rbp,TF_RBP(%rsp)
578         movq    %r10,TF_R10(%rsp)
579         movq    %r11,TF_R11(%rsp)
580         movq    %r12,TF_R12(%rsp)
581         movq    %r13,TF_R13(%rsp)
582         movq    %r14,TF_R14(%rsp)
583         movq    %r15,TF_R15(%rsp)
584         SAVE_SEGS
585         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
586         cld
587         xorl    %ebx,%ebx
588         testb   $SEL_RPL_MASK,TF_CS(%rsp)
589         jnz     nmi_fromuserspace
590         /*
591          * We've interrupted the kernel.  Preserve GS.base in %r12,
592          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
593          */
594         movl    $MSR_GSBASE,%ecx
595         rdmsr
596         movq    %rax,%r12
597         shlq    $32,%rdx
598         orq     %rdx,%r12
599         /* Retrieve and load the canonical value for GS.base. */
600         movq    TF_SIZE(%rsp),%rdx
601         movl    %edx,%eax
602         shrq    $32,%rdx
603         wrmsr
604         movq    %cr3,%r13
605         movq    PCPU(KCR3),%rax
606         cmpq    $~0,%rax
607         je      1f
608         movq    %rax,%cr3
609 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
610         je      nmi_calltrap
611         movl    $MSR_IA32_SPEC_CTRL,%ecx
612         rdmsr
613         movl    %eax,%r14d
614         call    handle_ibrs_entry
615         jmp     nmi_calltrap
616 nmi_fromuserspace:
617         incl    %ebx
618         swapgs
619         movq    %cr3,%r13
620         movq    PCPU(KCR3),%rax
621         cmpq    $~0,%rax
622         je      1f
623         movq    %rax,%cr3
624 1:      call    handle_ibrs_entry
625         movq    PCPU(CURPCB),%rdi
626         testq   %rdi,%rdi
627         jz      3f
628         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)
629         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
630         jz      3f
631         cmpw    $KUF32SEL,TF_FS(%rsp)
632         jne     2f
633         rdfsbase %rax
634         movq    %rax,PCB_FSBASE(%rdi)
635 2:      cmpw    $KUG32SEL,TF_GS(%rsp)
636         jne     3f
637         movl    $MSR_KGSBASE,%ecx
638         rdmsr
639         shlq    $32,%rdx
640         orq     %rdx,%rax
641         movq    %rax,PCB_GSBASE(%rdi)
642 3:
643 /* Note: this label is also used by ddb and gdb: */
644 nmi_calltrap:
645         FAKE_MCOUNT(TF_RIP(%rsp))
646         movq    %rsp,%rdi
647         call    trap
648         MEXITCOUNT
649 #ifdef HWPMC_HOOKS
650         /*
651          * Capture a userspace callchain if needed.
652          *
653          * - Check if the current trap was from user mode.
654          * - Check if the current thread is valid.
655          * - Check if the thread requires a user call chain to be
656          *   captured.
657          *
658          * We are still in NMI mode at this point.
659          */
660         testl   %ebx,%ebx
661         jz      nocallchain     /* not from userspace */
662         movq    PCPU(CURTHREAD),%rax
663         orq     %rax,%rax       /* curthread present? */
664         jz      nocallchain
665         /*
666          * Move execution to the regular kernel stack, because we
667          * committed to return through doreti.
668          */
669         movq    %rsp,%rsi       /* source stack pointer */
670         movq    $TF_SIZE,%rcx
671         movq    PCPU(RSP0),%rdx
672         subq    %rcx,%rdx
673         movq    %rdx,%rdi       /* destination stack pointer */
674         shrq    $3,%rcx         /* trap frame size in long words */
675         cld
676         rep
677         movsq                   /* copy trapframe */
678         movq    %rdx,%rsp       /* we are on the regular kstack */
679
680         testl   $TDP_CALLCHAIN,TD_PFLAGS(%rax) /* flagged for capture? */
681         jz      nocallchain
682         /*
683          * A user callchain is to be captured, so:
684          * - Take the processor out of "NMI" mode by faking an "iret",
685          *   to allow for nested NMI interrupts.
686          * - Enable interrupts, so that copyin() can work.
687          */
688         movl    %ss,%eax
689         pushq   %rax            /* tf_ss */
690         pushq   %rdx            /* tf_rsp (on kernel stack) */
691         pushfq                  /* tf_rflags */
692         movl    %cs,%eax
693         pushq   %rax            /* tf_cs */
694         pushq   $outofnmi       /* tf_rip */
695         iretq
696 outofnmi:
697         /*
698          * At this point the processor has exited NMI mode and is running
699          * with interrupts turned off on the normal kernel stack.
700          *
701          * If a pending NMI gets recognized at or after this point, it
702          * will cause a kernel callchain to be traced.
703          *
704          * We turn interrupts back on, and call the user callchain capture hook.
705          */
706         movq    pmc_hook,%rax
707         orq     %rax,%rax
708         jz      nocallchain
709         movq    PCPU(CURTHREAD),%rdi            /* thread */
710         movq    $PMC_FN_USER_CALLCHAIN,%rsi     /* command */
711         movq    %rsp,%rdx                       /* frame */
712         sti
713         call    *%rax
714         cli
715 nocallchain:
716 #endif
717         testl   %ebx,%ebx       /* %ebx == 0 => return to userland */
718         jnz     doreti_exit
719         /*
720          * Restore speculation control MSR, if preserved.
721          */
722         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
723         je      1f
724         movl    %r14d,%eax
725         xorl    %edx,%edx
726         movl    $MSR_IA32_SPEC_CTRL,%ecx
727         wrmsr
728         /*
729          * Put back the preserved MSR_GSBASE value.
730          */
731 1:      movl    $MSR_GSBASE,%ecx
732         movq    %r12,%rdx
733         movl    %edx,%eax
734         shrq    $32,%rdx
735         wrmsr
736         movq    %r13,%cr3
737         RESTORE_REGS
738         addq    $TF_RIP,%rsp
739         jmp     doreti_iret
740
741 /*
742  * MC# handling is similar to NMI.
743  *
744  * As with NMIs, machine check exceptions do not respect RFLAGS.IF and
745  * can occur at any time with a GS.base value that does not correspond
746  * to the privilege level in CS.
747  *
748  * Machine checks are not unblocked by iretq, but it is best to run
749  * the handler with interrupts disabled since the exception may have
750  * interrupted a critical section.
751  *
752  * The MC# handler runs on its own stack (tss_ist3).  The canonical
753  * GS.base value for the processor is stored just above the bottom of
754  * its MC# stack.  For exceptions taken from kernel mode, the current
755  * value in the processor's GS.base is saved at entry to C-preserved
756  * register %r12, the canonical value for GS.base is then loaded into
757  * the processor, and the saved value is restored at exit time.  For
758  * exceptions taken from user mode, the cheaper 'SWAPGS' instructions
759  * are used for swapping GS.base.
760  */
761
762 IDTVEC(mchk)
763         subq    $TF_RIP,%rsp
764         movl    $(T_MCHK),TF_TRAPNO(%rsp)
765         movq    $0,TF_ADDR(%rsp)
766         movq    $0,TF_ERR(%rsp)
767         movq    %rdi,TF_RDI(%rsp)
768         movq    %rsi,TF_RSI(%rsp)
769         movq    %rdx,TF_RDX(%rsp)
770         movq    %rcx,TF_RCX(%rsp)
771         movq    %r8,TF_R8(%rsp)
772         movq    %r9,TF_R9(%rsp)
773         movq    %rax,TF_RAX(%rsp)
774         movq    %rbx,TF_RBX(%rsp)
775         movq    %rbp,TF_RBP(%rsp)
776         movq    %r10,TF_R10(%rsp)
777         movq    %r11,TF_R11(%rsp)
778         movq    %r12,TF_R12(%rsp)
779         movq    %r13,TF_R13(%rsp)
780         movq    %r14,TF_R14(%rsp)
781         movq    %r15,TF_R15(%rsp)
782         SAVE_SEGS
783         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
784         cld
785         xorl    %ebx,%ebx
786         testb   $SEL_RPL_MASK,TF_CS(%rsp)
787         jnz     mchk_fromuserspace
788         /*
789          * We've interrupted the kernel.  Preserve GS.base in %r12,
790          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
791          */
792         movl    $MSR_GSBASE,%ecx
793         rdmsr
794         movq    %rax,%r12
795         shlq    $32,%rdx
796         orq     %rdx,%r12
797         /* Retrieve and load the canonical value for GS.base. */
798         movq    TF_SIZE(%rsp),%rdx
799         movl    %edx,%eax
800         shrq    $32,%rdx
801         wrmsr
802         movq    %cr3,%r13
803         movq    PCPU(KCR3),%rax
804         cmpq    $~0,%rax
805         je      1f
806         movq    %rax,%cr3
807 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
808         je      mchk_calltrap
809         movl    $MSR_IA32_SPEC_CTRL,%ecx
810         rdmsr
811         movl    %eax,%r14d
812         call    handle_ibrs_entry
813         jmp     mchk_calltrap
814 mchk_fromuserspace:
815         incl    %ebx
816         swapgs
817         movq    %cr3,%r13
818         movq    PCPU(KCR3),%rax
819         cmpq    $~0,%rax
820         je      1f
821         movq    %rax,%cr3
822 1:      call    handle_ibrs_entry
823 /* Note: this label is also used by ddb and gdb: */
824 mchk_calltrap:
825         FAKE_MCOUNT(TF_RIP(%rsp))
826         movq    %rsp,%rdi
827         call    mca_intr
828         MEXITCOUNT
829         testl   %ebx,%ebx       /* %ebx == 0 => return to userland */
830         jnz     doreti_exit
831         /*
832          * Restore speculation control MSR, if preserved.
833          */
834         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
835         je      1f
836         movl    %r14d,%eax
837         xorl    %edx,%edx
838         movl    $MSR_IA32_SPEC_CTRL,%ecx
839         wrmsr
840         /*
841          * Put back the preserved MSR_GSBASE value.
842          */
843 1:      movl    $MSR_GSBASE,%ecx
844         movq    %r12,%rdx
845         movl    %edx,%eax
846         shrq    $32,%rdx
847         wrmsr
848         movq    %r13,%cr3
849         RESTORE_REGS
850         addq    $TF_RIP,%rsp
851         jmp     doreti_iret
852
853 ENTRY(fork_trampoline)
854         movq    %r12,%rdi               /* function */
855         movq    %rbx,%rsi               /* arg1 */
856         movq    %rsp,%rdx               /* trapframe pointer */
857         call    fork_exit
858         MEXITCOUNT
859         jmp     doreti                  /* Handle any ASTs */
860
861 /*
862  * To efficiently implement classification of trap and interrupt handlers
863  * for profiling, there must be only trap handlers between the labels btrap
864  * and bintr, and only interrupt handlers between the labels bintr and
865  * eintr.  This is implemented (partly) by including files that contain
866  * some of the handlers.  Before including the files, set up a normal asm
867  * environment so that the included files doen't need to know that they are
868  * included.
869  */
870
871 #ifdef COMPAT_FREEBSD32
872         .data
873         .p2align 4
874         .text
875         SUPERALIGN_TEXT
876
877 #include <amd64/ia32/ia32_exception.S>
878 #endif
879
880         .data
881         .p2align 4
882         .text
883         SUPERALIGN_TEXT
884 MCOUNT_LABEL(bintr)
885
886 #include <amd64/amd64/apic_vector.S>
887
888 #ifdef DEV_ATPIC
889         .data
890         .p2align 4
891         .text
892         SUPERALIGN_TEXT
893
894 #include <amd64/amd64/atpic_vector.S>
895 #endif
896
897         .text
898 MCOUNT_LABEL(eintr)
899
900 /*
901  * void doreti(struct trapframe)
902  *
903  * Handle return from interrupts, traps and syscalls.
904  */
905         .text
906         SUPERALIGN_TEXT
907         .type   doreti,@function
908         .globl  doreti
909 doreti:
910         FAKE_MCOUNT($bintr)             /* init "from" bintr -> doreti */
911         /*
912          * Check if ASTs can be handled now.
913          */
914         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* are we returning to user mode? */
915         jz      doreti_exit             /* can't handle ASTs now if not */
916
917 doreti_ast:
918         /*
919          * Check for ASTs atomically with returning.  Disabling CPU
920          * interrupts provides sufficient locking even in the SMP case,
921          * since we will be informed of any new ASTs by an IPI.
922          */
923         cli
924         movq    PCPU(CURTHREAD),%rax
925         testl   $TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
926         je      doreti_exit
927         sti
928         movq    %rsp,%rdi       /* pass a pointer to the trapframe */
929         call    ast
930         jmp     doreti_ast
931
932         /*
933          * doreti_exit: pop registers, iret.
934          *
935          *      The segment register pop is a special case, since it may
936          *      fault if (for example) a sigreturn specifies bad segment
937          *      registers.  The fault is handled in trap.c.
938          */
939 doreti_exit:
940         MEXITCOUNT
941         movq    PCPU(CURPCB),%r8
942
943         /*
944          * Do not reload segment registers for kernel.
945          * Since we do not reload segments registers with sane
946          * values on kernel entry, descriptors referenced by
947          * segments registers might be not valid.  This is fatal
948          * for user mode, but is not a problem for the kernel.
949          */
950         testb   $SEL_RPL_MASK,TF_CS(%rsp)
951         jz      ld_regs
952         testl   $PCB_FULL_IRET,PCB_FLAGS(%r8)
953         jz      ld_regs
954         andl    $~PCB_FULL_IRET,PCB_FLAGS(%r8)
955         testl   $TF_HASSEGS,TF_FLAGS(%rsp)
956         je      set_segs
957
958 do_segs:
959         /* Restore %fs and fsbase */
960         movw    TF_FS(%rsp),%ax
961         .globl  ld_fs
962 ld_fs:
963         movw    %ax,%fs
964         cmpw    $KUF32SEL,%ax
965         jne     1f
966         movl    $MSR_FSBASE,%ecx
967         movl    PCB_FSBASE(%r8),%eax
968         movl    PCB_FSBASE+4(%r8),%edx
969         .globl  ld_fsbase
970 ld_fsbase:
971         wrmsr
972 1:
973         /* Restore %gs and gsbase */
974         movw    TF_GS(%rsp),%si
975         pushfq
976         cli
977         movl    $MSR_GSBASE,%ecx
978         /* Save current kernel %gs base into %r12d:%r13d */
979         rdmsr
980         movl    %eax,%r12d
981         movl    %edx,%r13d
982         .globl  ld_gs
983 ld_gs:
984         movw    %si,%gs
985         /* Save user %gs base into %r14d:%r15d */
986         rdmsr
987         movl    %eax,%r14d
988         movl    %edx,%r15d
989         /* Restore kernel %gs base */
990         movl    %r12d,%eax
991         movl    %r13d,%edx
992         wrmsr
993         popfq
994         /*
995          * Restore user %gs base, either from PCB if used for TLS, or
996          * from the previously saved msr read.
997          */
998         movl    $MSR_KGSBASE,%ecx
999         cmpw    $KUG32SEL,%si
1000         jne     1f
1001         movl    PCB_GSBASE(%r8),%eax
1002         movl    PCB_GSBASE+4(%r8),%edx
1003         jmp     ld_gsbase
1004 1:
1005         movl    %r14d,%eax
1006         movl    %r15d,%edx
1007         .globl  ld_gsbase
1008 ld_gsbase:
1009         wrmsr   /* May trap if non-canonical, but only for TLS. */
1010         .globl  ld_es
1011 ld_es:
1012         movw    TF_ES(%rsp),%es
1013         .globl  ld_ds
1014 ld_ds:
1015         movw    TF_DS(%rsp),%ds
1016 ld_regs:
1017         RESTORE_REGS
1018         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
1019         jz      2f                      /* keep running with kernel GS.base */
1020         cli
1021         call    handle_ibrs_exit_rs
1022         cmpq    $~0,PCPU(UCR3)
1023         je      1f
1024         pushq   %rdx
1025         movq    PCPU(PTI_RSP0),%rdx
1026         subq    $PTI_SIZE,%rdx
1027         movq    %rax,PTI_RAX(%rdx)
1028         popq    %rax
1029         movq    %rax,PTI_RDX(%rdx)
1030         movq    TF_RIP(%rsp),%rax
1031         movq    %rax,PTI_RIP(%rdx)
1032         movq    TF_CS(%rsp),%rax
1033         movq    %rax,PTI_CS(%rdx)
1034         movq    TF_RFLAGS(%rsp),%rax
1035         movq    %rax,PTI_RFLAGS(%rdx)
1036         movq    TF_RSP(%rsp),%rax
1037         movq    %rax,PTI_RSP(%rdx)
1038         movq    TF_SS(%rsp),%rax
1039         movq    %rax,PTI_SS(%rdx)
1040         movq    PCPU(UCR3),%rax
1041         swapgs
1042         movq    %rdx,%rsp
1043         movq    %rax,%cr3
1044         popq    %rdx
1045         popq    %rax
1046         addq    $8,%rsp
1047         jmp     doreti_iret
1048 1:      swapgs
1049 2:      addq    $TF_RIP,%rsp
1050         .globl  doreti_iret
1051 doreti_iret:
1052         iretq
1053
1054 set_segs:
1055         movw    $KUDSEL,%ax
1056         movw    %ax,TF_DS(%rsp)
1057         movw    %ax,TF_ES(%rsp)
1058         movw    $KUF32SEL,TF_FS(%rsp)
1059         movw    $KUG32SEL,TF_GS(%rsp)
1060         jmp     do_segs
1061
1062         /*
1063          * doreti_iret_fault.  Alternative return code for
1064          * the case where we get a fault in the doreti_exit code
1065          * above.  trap() (amd64/amd64/trap.c) catches this specific
1066          * case, sends the process a signal and continues in the
1067          * corresponding place in the code below.
1068          */
1069         ALIGN_TEXT
1070         .globl  doreti_iret_fault
1071 doreti_iret_fault:
1072         subq    $TF_RIP,%rsp            /* space including tf_err, tf_trapno */
1073         movq    %rax,TF_RAX(%rsp)
1074         movq    %rdx,TF_RDX(%rsp)
1075         movq    %rcx,TF_RCX(%rsp)
1076         call    handle_ibrs_entry
1077         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1078         jz      1f
1079         sti
1080 1:
1081         SAVE_SEGS
1082         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
1083         movq    %rdi,TF_RDI(%rsp)
1084         movq    %rsi,TF_RSI(%rsp)
1085         movq    %r8,TF_R8(%rsp)
1086         movq    %r9,TF_R9(%rsp)
1087         movq    %rbx,TF_RBX(%rsp)
1088         movq    %rbp,TF_RBP(%rsp)
1089         movq    %r10,TF_R10(%rsp)
1090         movq    %r11,TF_R11(%rsp)
1091         movq    %r12,TF_R12(%rsp)
1092         movq    %r13,TF_R13(%rsp)
1093         movq    %r14,TF_R14(%rsp)
1094         movq    %r15,TF_R15(%rsp)
1095         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1096         movq    $0,TF_ERR(%rsp) /* XXX should be the error code */
1097         movq    $0,TF_ADDR(%rsp)
1098         FAKE_MCOUNT(TF_RIP(%rsp))
1099         jmp     calltrap
1100
1101         ALIGN_TEXT
1102         .globl  ds_load_fault
1103 ds_load_fault:
1104         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1105         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1106         jz      1f
1107         sti
1108 1:
1109         movq    %rsp,%rdi
1110         call    trap
1111         movw    $KUDSEL,TF_DS(%rsp)
1112         jmp     doreti
1113
1114         ALIGN_TEXT
1115         .globl  es_load_fault
1116 es_load_fault:
1117         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1118         testl   $PSL_I,TF_RFLAGS(%rsp)
1119         jz      1f
1120         sti
1121 1:
1122         movq    %rsp,%rdi
1123         call    trap
1124         movw    $KUDSEL,TF_ES(%rsp)
1125         jmp     doreti
1126
1127         ALIGN_TEXT
1128         .globl  fs_load_fault
1129 fs_load_fault:
1130         testl   $PSL_I,TF_RFLAGS(%rsp)
1131         jz      1f
1132         sti
1133 1:
1134         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1135         movq    %rsp,%rdi
1136         call    trap
1137         movw    $KUF32SEL,TF_FS(%rsp)
1138         jmp     doreti
1139
1140         ALIGN_TEXT
1141         .globl  gs_load_fault
1142 gs_load_fault:
1143         popfq
1144         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1145         testl   $PSL_I,TF_RFLAGS(%rsp)
1146         jz      1f
1147         sti
1148 1:
1149         movq    %rsp,%rdi
1150         call    trap
1151         movw    $KUG32SEL,TF_GS(%rsp)
1152         jmp     doreti
1153
1154         ALIGN_TEXT
1155         .globl  fsbase_load_fault
1156 fsbase_load_fault:
1157         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1158         testl   $PSL_I,TF_RFLAGS(%rsp)
1159         jz      1f
1160         sti
1161 1:
1162         movq    %rsp,%rdi
1163         call    trap
1164         movq    PCPU(CURTHREAD),%r8
1165         movq    TD_PCB(%r8),%r8
1166         movq    $0,PCB_FSBASE(%r8)
1167         jmp     doreti
1168
1169         ALIGN_TEXT
1170         .globl  gsbase_load_fault
1171 gsbase_load_fault:
1172         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1173         testl   $PSL_I,TF_RFLAGS(%rsp)
1174         jz      1f
1175         sti
1176 1:
1177         movq    %rsp,%rdi
1178         call    trap
1179         movq    PCPU(CURTHREAD),%r8
1180         movq    TD_PCB(%r8),%r8
1181         movq    $0,PCB_GSBASE(%r8)
1182         jmp     doreti
1183
1184 #ifdef HWPMC_HOOKS
1185         ENTRY(end_exceptions)
1186 #endif