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