]> CyberLeo.Net >> Repos - FreeBSD/FreeBSD.git/blob - sys/amd64/amd64/exception.S
Upgrade our copies of clang, llvm, lld, lldb, compiler-rt, libc++,
[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/psl.h>
47 #include <machine/asmacros.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       bpt, T_BPTFLT
119 #ifdef KDTRACE_HOOKS
120         TRAP_NOEN       dtrace_ret, T_DTRACE_RET
121 #endif
122
123 /* Regular traps; The cpu does not supply tf_err for these. */
124         .macro  TRAP    l, trapno
125         PTI_ENTRY       \l,X\l
126         .globl  X\l
127         .type   X\l,@function
128 X\l:
129         subq $TF_RIP,%rsp
130         movl $\trapno,TF_TRAPNO(%rsp)
131         movq $0,TF_ADDR(%rsp)
132         movq $0,TF_ERR(%rsp)
133         jmp alltraps
134         .endm
135
136         TRAP    div, T_DIVIDE
137         TRAP    ofl, T_OFLOW
138         TRAP    bnd, T_BOUND
139         TRAP    ill, T_PRIVINFLT
140         TRAP    dna, T_DNA
141         TRAP    fpusegm, T_FPOPFLT
142         TRAP    rsvd, T_RESERVED
143         TRAP    fpu, T_ARITHTRAP
144         TRAP    xmm, T_XMMFLT
145
146 /* This group of traps have tf_err already pushed by the cpu. */
147         .macro  TRAP_ERR        l, trapno
148         PTI_ENTRY       \l,X\l,has_err=1
149         .globl  X\l
150         .type   X\l,@function
151 X\l:
152         subq $TF_ERR,%rsp
153         movl $\trapno,TF_TRAPNO(%rsp)
154         movq $0,TF_ADDR(%rsp)
155         jmp alltraps
156         .endm
157
158         TRAP_ERR        tss, T_TSSFLT
159         TRAP_ERR        align, T_ALIGNFLT
160
161         /*
162          * alltraps entry point.  Use swapgs if this is the first time in the
163          * kernel from userland.  Reenable interrupts if they were enabled
164          * before the trap.  This approximates SDT_SYS386TGT on the i386 port.
165          */
166         SUPERALIGN_TEXT
167         .globl  alltraps
168         .type   alltraps,@function
169 alltraps:
170         movq    %rdi,TF_RDI(%rsp)
171         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
172         jz      1f              /* already running with kernel GS.base */
173         swapgs
174         movq    PCPU(CURPCB),%rdi
175         andl    $~PCB_FULL_IRET,PCB_FLAGS(%rdi)
176 1:      SAVE_SEGS
177         movq    %rdx,TF_RDX(%rsp)
178         movq    %rax,TF_RAX(%rsp)
179         movq    %rcx,TF_RCX(%rsp)
180         testb   $SEL_RPL_MASK,TF_CS(%rsp)
181         jz      2f
182         call    handle_ibrs_entry
183 2:      testl   $PSL_I,TF_RFLAGS(%rsp)
184         jz      alltraps_pushregs_no_rax
185         sti
186 alltraps_pushregs_no_rax:
187         movq    %rsi,TF_RSI(%rsp)
188         movq    %r8,TF_R8(%rsp)
189         movq    %r9,TF_R9(%rsp)
190         movq    %rbx,TF_RBX(%rsp)
191         movq    %rbp,TF_RBP(%rsp)
192         movq    %r10,TF_R10(%rsp)
193         movq    %r11,TF_R11(%rsp)
194         movq    %r12,TF_R12(%rsp)
195         movq    %r13,TF_R13(%rsp)
196         movq    %r14,TF_R14(%rsp)
197         movq    %r15,TF_R15(%rsp)
198         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
199         pushfq
200         andq    $~(PSL_D | PSL_AC),(%rsp)
201         popfq
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         pushfq
283         andq    $~(PSL_D | PSL_AC),(%rsp)
284         popfq
285         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
286         jz      1f                      /* already running with kernel GS.base */
287         swapgs
288 1:
289         movq    PCPU(KCR3),%rax
290         cmpq    $~0,%rax
291         je      2f
292         movq    %rax,%cr3
293 2:      movq    %rsp,%rdi
294         call    dblfault_handler
295 3:      hlt
296         jmp     3b
297
298         ALIGN_TEXT
299 IDTVEC(page_pti)
300         testb   $SEL_RPL_MASK,PTI_CS-2*8(%rsp)
301         jz      Xpage
302         swapgs
303         pushq   %rax
304         movq    %cr3,%rax
305         movq    %rax,PCPU(SAVED_UCR3)
306         cmpq    $~0,PCPU(UCR3)
307         jne     1f
308         popq    %rax
309         jmp     2f
310 1:      pushq   %rdx
311         PTI_UUENTRY has_err=1
312 2:      subq    $TF_ERR,%rsp
313         movq    %rdi,TF_RDI(%rsp)
314         movq    %rax,TF_RAX(%rsp)
315         movq    %rdx,TF_RDX(%rsp)
316         movq    %rcx,TF_RCX(%rsp)
317         jmp     page_u
318 IDTVEC(page)
319         subq    $TF_ERR,%rsp
320         movq    %rdi,TF_RDI(%rsp)       /* free up GP registers */
321         movq    %rax,TF_RAX(%rsp)
322         movq    %rdx,TF_RDX(%rsp)
323         movq    %rcx,TF_RCX(%rsp)
324         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
325         jz      page_cr2                /* already running with kernel GS.base */
326         swapgs
327 page_u: movq    PCPU(CURPCB),%rdi
328         andl    $~PCB_FULL_IRET,PCB_FLAGS(%rdi)
329         movq    PCPU(SAVED_UCR3),%rax
330         movq    %rax,PCB_SAVED_UCR3(%rdi)
331         call    handle_ibrs_entry
332 page_cr2:
333         movq    %cr2,%rdi               /* preserve %cr2 before ..  */
334         movq    %rdi,TF_ADDR(%rsp)      /* enabling interrupts. */
335         SAVE_SEGS
336         movl    $T_PAGEFLT,TF_TRAPNO(%rsp)
337         testl   $PSL_I,TF_RFLAGS(%rsp)
338         jz      alltraps_pushregs_no_rax
339         sti
340         jmp     alltraps_pushregs_no_rax
341
342         /*
343          * We have to special-case this one.  If we get a trap in doreti() at
344          * the iretq stage, we'll reenter with the wrong gs state.  We'll have
345          * to do a special the swapgs in this case even coming from the kernel.
346          * XXX linux has a trap handler for their equivalent of load_gs().
347          *
348          * On the stack, we have the hardware interrupt frame to return
349          * to usermode (faulted) and another frame with error code, for
350          * fault.  For PTI, copy both frames to the main thread stack.
351          * Handle the potential 16-byte alignment adjustment incurred
352          * during the second fault by copying both frames independently
353          * while unwinding the stack in between.
354          */
355         .macro PROTF_ENTRY name,trapno
356 \name\()_pti_doreti:
357         swapgs
358         cmpq    $~0,PCPU(UCR3)
359         je      1f
360         pushq   %rax
361         pushq   %rdx
362         movq    PCPU(KCR3),%rax
363         movq    %rax,%cr3
364         movq    PCPU(RSP0),%rax
365         subq    $2*PTI_SIZE-3*8,%rax /* no err, %rax, %rdx in faulted frame */
366         MOVE_STACKS     (PTI_SIZE / 8)
367         addq    $PTI_SIZE,%rax
368         movq    PTI_RSP(%rsp),%rsp
369         MOVE_STACKS     (PTI_SIZE / 8 - 3)
370         subq    $PTI_SIZE,%rax
371         movq    %rax,%rsp
372         popq    %rdx
373         popq    %rax
374 1:      swapgs
375         jmp     X\name
376 IDTVEC(\name\()_pti)
377         cmpq    $doreti_iret,PTI_RIP-2*8(%rsp)
378         je      \name\()_pti_doreti
379         testb   $SEL_RPL_MASK,PTI_CS-2*8(%rsp) /* %rax, %rdx not yet pushed */
380         jz      X\name
381         PTI_UENTRY has_err=1
382         swapgs
383 IDTVEC(\name)
384         subq    $TF_ERR,%rsp
385         movl    $\trapno,TF_TRAPNO(%rsp)
386         jmp     prot_addrf
387         .endm
388
389         PROTF_ENTRY     missing, T_SEGNPFLT
390         PROTF_ENTRY     stk, T_STKFLT
391         PROTF_ENTRY     prot, T_PROTFLT
392
393 prot_addrf:
394         movq    $0,TF_ADDR(%rsp)
395         movq    %rdi,TF_RDI(%rsp)       /* free up a GP register */
396         movq    %rax,TF_RAX(%rsp)
397         movq    %rdx,TF_RDX(%rsp)
398         movq    %rcx,TF_RCX(%rsp)
399         movw    %fs,TF_FS(%rsp)
400         movw    %gs,TF_GS(%rsp)
401         leaq    doreti_iret(%rip),%rdi
402         cmpq    %rdi,TF_RIP(%rsp)
403         je      5f                      /* kernel but with user gsbase!! */
404         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
405         jz      6f                      /* already running with kernel GS.base */
406         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
407         jz      2f
408         cmpw    $KUF32SEL,TF_FS(%rsp)
409         jne     1f
410         rdfsbase %rax
411 1:      cmpw    $KUG32SEL,TF_GS(%rsp)
412         jne     2f
413         rdgsbase %rdx
414 2:      swapgs
415         movq    PCPU(CURPCB),%rdi
416         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
417         jz      4f
418         cmpw    $KUF32SEL,TF_FS(%rsp)
419         jne     3f
420         movq    %rax,PCB_FSBASE(%rdi)
421 3:      cmpw    $KUG32SEL,TF_GS(%rsp)
422         jne     4f
423         movq    %rdx,PCB_GSBASE(%rdi)
424 4:      call    handle_ibrs_entry
425         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)  /* always full iret from GPF */
426         movw    %es,TF_ES(%rsp)
427         movw    %ds,TF_DS(%rsp)
428         testl   $PSL_I,TF_RFLAGS(%rsp)
429         jz      alltraps_pushregs_no_rax
430         sti
431         jmp     alltraps_pushregs_no_rax
432
433 5:      swapgs
434 6:      movq    PCPU(CURPCB),%rdi
435         jmp     4b
436
437 /*
438  * Fast syscall entry point.  We enter here with just our new %cs/%ss set,
439  * and the new privilige level.  We are still running on the old user stack
440  * pointer.  We have to juggle a few things around to find our stack etc.
441  * swapgs gives us access to our PCPU space only.
442  *
443  * We do not support invoking this from a custom segment registers,
444  * esp. %cs, %ss, %fs, %gs, e.g. using entries from an LDT.
445  */
446         SUPERALIGN_TEXT
447 IDTVEC(fast_syscall_pti)
448         swapgs
449         movq    %rax,PCPU(SCRATCH_RAX)
450         cmpq    $~0,PCPU(UCR3)
451         je      fast_syscall_common
452         movq    PCPU(KCR3),%rax
453         movq    %rax,%cr3
454         jmp     fast_syscall_common
455         SUPERALIGN_TEXT
456 IDTVEC(fast_syscall)
457         swapgs
458         movq    %rax,PCPU(SCRATCH_RAX)
459 fast_syscall_common:
460         movq    %rsp,PCPU(SCRATCH_RSP)
461         movq    PCPU(RSP0),%rsp
462         /* Now emulate a trapframe. Make the 8 byte alignment odd for call. */
463         subq    $TF_SIZE,%rsp
464         /* defer TF_RSP till we have a spare register */
465         movq    %r11,TF_RFLAGS(%rsp)
466         movq    %rcx,TF_RIP(%rsp)       /* %rcx original value is in %r10 */
467         movq    PCPU(SCRATCH_RSP),%r11  /* %r11 already saved */
468         movq    %r11,TF_RSP(%rsp)       /* user stack pointer */
469         movq    PCPU(SCRATCH_RAX),%rax
470         /*
471          * Save a few arg registers early to free them for use in
472          * handle_ibrs_entry().  %r10 is especially tricky.  It is not an
473          * arg register, but it holds the arg register %rcx.  Profiling
474          * preserves %rcx, but may clobber %r10.  Profiling may also
475          * clobber %r11, but %r11 (original %eflags) has been saved.
476          */
477         movq    %rax,TF_RAX(%rsp)       /* syscall number */
478         movq    %rdx,TF_RDX(%rsp)       /* arg 3 */
479         movq    %r10,TF_RCX(%rsp)       /* arg 4 */
480         SAVE_SEGS
481         call    handle_ibrs_entry
482         movq    PCPU(CURPCB),%r11
483         andl    $~PCB_FULL_IRET,PCB_FLAGS(%r11)
484         sti
485         movq    $KUDSEL,TF_SS(%rsp)
486         movq    $KUCSEL,TF_CS(%rsp)
487         movq    $2,TF_ERR(%rsp)
488         movq    %rdi,TF_RDI(%rsp)       /* arg 1 */
489         movq    %rsi,TF_RSI(%rsp)       /* arg 2 */
490         movq    %r8,TF_R8(%rsp)         /* arg 5 */
491         movq    %r9,TF_R9(%rsp)         /* arg 6 */
492         movq    %rbx,TF_RBX(%rsp)       /* C preserved */
493         movq    %rbp,TF_RBP(%rsp)       /* C preserved */
494         movq    %r12,TF_R12(%rsp)       /* C preserved */
495         movq    %r13,TF_R13(%rsp)       /* C preserved */
496         movq    %r14,TF_R14(%rsp)       /* C preserved */
497         movq    %r15,TF_R15(%rsp)       /* C preserved */
498         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
499         FAKE_MCOUNT(TF_RIP(%rsp))
500         movq    PCPU(CURTHREAD),%rdi
501         movq    %rsp,TD_FRAME(%rdi)
502         movl    TF_RFLAGS(%rsp),%esi
503         andl    $PSL_T,%esi
504         call    amd64_syscall
505 1:      movq    PCPU(CURPCB),%rax
506         /* Disable interrupts before testing PCB_FULL_IRET. */
507         cli
508         testl   $PCB_FULL_IRET,PCB_FLAGS(%rax)
509         jnz     4f
510         /* Check for and handle AST's on return to userland. */
511         movq    PCPU(CURTHREAD),%rax
512         testl   $TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
513         jne     3f
514         call    handle_ibrs_exit
515         callq   *mds_handler
516         /* Restore preserved registers. */
517         MEXITCOUNT
518         movq    TF_RDI(%rsp),%rdi       /* bonus; preserve arg 1 */
519         movq    TF_RSI(%rsp),%rsi       /* bonus: preserve arg 2 */
520         movq    TF_RDX(%rsp),%rdx       /* return value 2 */
521         movq    TF_RAX(%rsp),%rax       /* return value 1 */
522         movq    TF_RFLAGS(%rsp),%r11    /* original %rflags */
523         movq    TF_RIP(%rsp),%rcx       /* original %rip */
524         movq    TF_RSP(%rsp),%rsp       /* user stack pointer */
525         xorl    %r8d,%r8d               /* zero the rest of GPRs */
526         xorl    %r10d,%r10d
527         cmpq    $~0,PCPU(UCR3)
528         je      2f
529         movq    PCPU(UCR3),%r9
530         movq    %r9,%cr3
531 2:      xorl    %r9d,%r9d
532         swapgs
533         sysretq
534
535 3:      /* AST scheduled. */
536         sti
537         movq    %rsp,%rdi
538         call    ast
539         jmp     1b
540
541 4:      /* Requested full context restore, use doreti for that. */
542         MEXITCOUNT
543         jmp     doreti
544
545 /*
546  * Here for CYA insurance, in case a "syscall" instruction gets
547  * issued from 32 bit compatibility mode. MSR_CSTAR has to point
548  * to *something* if EFER_SCE is enabled.
549  */
550 IDTVEC(fast_syscall32)
551         sysret
552
553 /*
554  * DB# handler is very similar to NM#, because 'mov/pop %ss' delay
555  * generation of exception until the next instruction is executed,
556  * which might be a kernel entry.  So we must execute the handler
557  * on IST stack and be ready for non-kernel GSBASE.
558  */
559 IDTVEC(dbg)
560         subq    $TF_RIP,%rsp
561         movl    $(T_TRCTRAP),TF_TRAPNO(%rsp)
562         movq    $0,TF_ADDR(%rsp)
563         movq    $0,TF_ERR(%rsp)
564         movq    %rdi,TF_RDI(%rsp)
565         movq    %rsi,TF_RSI(%rsp)
566         movq    %rdx,TF_RDX(%rsp)
567         movq    %rcx,TF_RCX(%rsp)
568         movq    %r8,TF_R8(%rsp)
569         movq    %r9,TF_R9(%rsp)
570         movq    %rax,TF_RAX(%rsp)
571         movq    %rbx,TF_RBX(%rsp)
572         movq    %rbp,TF_RBP(%rsp)
573         movq    %r10,TF_R10(%rsp)
574         movq    %r11,TF_R11(%rsp)
575         movq    %r12,TF_R12(%rsp)
576         movq    %r13,TF_R13(%rsp)
577         movq    %r14,TF_R14(%rsp)
578         movq    %r15,TF_R15(%rsp)
579         SAVE_SEGS
580         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
581         pushfq
582         andq    $~(PSL_D | PSL_AC),(%rsp)
583         popfq
584         testb   $SEL_RPL_MASK,TF_CS(%rsp)
585         jnz     dbg_fromuserspace
586         /*
587          * We've interrupted the kernel.  Preserve GS.base in %r12,
588          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
589          */
590         movl    $MSR_GSBASE,%ecx
591         rdmsr
592         movq    %rax,%r12
593         shlq    $32,%rdx
594         orq     %rdx,%r12
595         /* Retrieve and load the canonical value for GS.base. */
596         movq    TF_SIZE(%rsp),%rdx
597         movl    %edx,%eax
598         shrq    $32,%rdx
599         wrmsr
600         movq    %cr3,%r13
601         movq    PCPU(KCR3),%rax
602         cmpq    $~0,%rax
603         je      1f
604         movq    %rax,%cr3
605 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
606         je      2f
607         movl    $MSR_IA32_SPEC_CTRL,%ecx
608         rdmsr
609         movl    %eax,%r14d
610         call    handle_ibrs_entry
611 2:      FAKE_MCOUNT(TF_RIP(%rsp))
612         movq    %rsp,%rdi
613         call    trap
614         MEXITCOUNT
615         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
616         je      3f
617         movl    %r14d,%eax
618         xorl    %edx,%edx
619         movl    $MSR_IA32_SPEC_CTRL,%ecx
620         wrmsr
621         /*
622          * Put back the preserved MSR_GSBASE value.
623          */
624 3:      movl    $MSR_GSBASE,%ecx
625         movq    %r12,%rdx
626         movl    %edx,%eax
627         shrq    $32,%rdx
628         wrmsr
629         movq    %r13,%cr3
630         RESTORE_REGS
631         addq    $TF_RIP,%rsp
632         jmp     doreti_iret
633 dbg_fromuserspace:
634         /*
635          * Switch to kernel GSBASE and kernel page table, and copy frame
636          * from the IST stack to the normal kernel stack, since trap()
637          * re-enables interrupts, and since we might trap on DB# while
638          * in trap().
639          */
640         swapgs
641         movq    PCPU(KCR3),%rax
642         cmpq    $~0,%rax
643         je      1f
644         movq    %rax,%cr3
645 1:      movq    PCPU(RSP0),%rax
646         movl    $TF_SIZE,%ecx
647         subq    %rcx,%rax
648         movq    %rax,%rdi
649         movq    %rsp,%rsi
650         rep;movsb
651         movq    %rax,%rsp
652         call    handle_ibrs_entry
653         movq    PCPU(CURPCB),%rdi
654         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)
655         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
656         jz      3f
657         cmpw    $KUF32SEL,TF_FS(%rsp)
658         jne     2f
659         rdfsbase %rax
660         movq    %rax,PCB_FSBASE(%rdi)
661 2:      cmpw    $KUG32SEL,TF_GS(%rsp)
662         jne     3f
663         movl    $MSR_KGSBASE,%ecx
664         rdmsr
665         shlq    $32,%rdx
666         orq     %rdx,%rax
667         movq    %rax,PCB_GSBASE(%rdi)
668 3:      jmp     calltrap
669
670 /*
671  * NMI handling is special.
672  *
673  * First, NMIs do not respect the state of the processor's RFLAGS.IF
674  * bit.  The NMI handler may be entered at any time, including when
675  * the processor is in a critical section with RFLAGS.IF == 0.
676  * The processor's GS.base value could be invalid on entry to the
677  * handler.
678  *
679  * Second, the processor treats NMIs specially, blocking further NMIs
680  * until an 'iretq' instruction is executed.  We thus need to execute
681  * the NMI handler with interrupts disabled, to prevent a nested interrupt
682  * from executing an 'iretq' instruction and inadvertently taking the
683  * processor out of NMI mode.
684  *
685  * Third, the NMI handler runs on its own stack (tss_ist2). The canonical
686  * GS.base value for the processor is stored just above the bottom of its
687  * NMI stack.  For NMIs taken from kernel mode, the current value in
688  * the processor's GS.base is saved at entry to C-preserved register %r12,
689  * the canonical value for GS.base is then loaded into the processor, and
690  * the saved value is restored at exit time.  For NMIs taken from user mode,
691  * the cheaper 'SWAPGS' instructions are used for swapping GS.base.
692  */
693
694 IDTVEC(nmi)
695         subq    $TF_RIP,%rsp
696         movl    $(T_NMI),TF_TRAPNO(%rsp)
697         movq    $0,TF_ADDR(%rsp)
698         movq    $0,TF_ERR(%rsp)
699         movq    %rdi,TF_RDI(%rsp)
700         movq    %rsi,TF_RSI(%rsp)
701         movq    %rdx,TF_RDX(%rsp)
702         movq    %rcx,TF_RCX(%rsp)
703         movq    %r8,TF_R8(%rsp)
704         movq    %r9,TF_R9(%rsp)
705         movq    %rax,TF_RAX(%rsp)
706         movq    %rbx,TF_RBX(%rsp)
707         movq    %rbp,TF_RBP(%rsp)
708         movq    %r10,TF_R10(%rsp)
709         movq    %r11,TF_R11(%rsp)
710         movq    %r12,TF_R12(%rsp)
711         movq    %r13,TF_R13(%rsp)
712         movq    %r14,TF_R14(%rsp)
713         movq    %r15,TF_R15(%rsp)
714         SAVE_SEGS
715         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
716         pushfq
717         andq    $~(PSL_D | PSL_AC),(%rsp)
718         popfq
719         xorl    %ebx,%ebx
720         testb   $SEL_RPL_MASK,TF_CS(%rsp)
721         jnz     nmi_fromuserspace
722         /*
723          * We've interrupted the kernel.  Preserve GS.base in %r12,
724          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
725          */
726         movl    $MSR_GSBASE,%ecx
727         rdmsr
728         movq    %rax,%r12
729         shlq    $32,%rdx
730         orq     %rdx,%r12
731         /* Retrieve and load the canonical value for GS.base. */
732         movq    TF_SIZE(%rsp),%rdx
733         movl    %edx,%eax
734         shrq    $32,%rdx
735         wrmsr
736         movq    %cr3,%r13
737         movq    PCPU(KCR3),%rax
738         cmpq    $~0,%rax
739         je      1f
740         movq    %rax,%cr3
741 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
742         je      nmi_calltrap
743         movl    $MSR_IA32_SPEC_CTRL,%ecx
744         rdmsr
745         movl    %eax,%r14d
746         call    handle_ibrs_entry
747         jmp     nmi_calltrap
748 nmi_fromuserspace:
749         incl    %ebx
750         swapgs
751         movq    %cr3,%r13
752         movq    PCPU(KCR3),%rax
753         cmpq    $~0,%rax
754         je      1f
755         movq    %rax,%cr3
756 1:      call    handle_ibrs_entry
757         movq    PCPU(CURPCB),%rdi
758         testq   %rdi,%rdi
759         jz      3f
760         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)
761         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
762         jz      3f
763         cmpw    $KUF32SEL,TF_FS(%rsp)
764         jne     2f
765         rdfsbase %rax
766         movq    %rax,PCB_FSBASE(%rdi)
767 2:      cmpw    $KUG32SEL,TF_GS(%rsp)
768         jne     3f
769         movl    $MSR_KGSBASE,%ecx
770         rdmsr
771         shlq    $32,%rdx
772         orq     %rdx,%rax
773         movq    %rax,PCB_GSBASE(%rdi)
774 3:
775 /* Note: this label is also used by ddb and gdb: */
776 nmi_calltrap:
777         FAKE_MCOUNT(TF_RIP(%rsp))
778         movq    %rsp,%rdi
779         call    trap
780         MEXITCOUNT
781 #ifdef HWPMC_HOOKS
782         /*
783          * Capture a userspace callchain if needed.
784          *
785          * - Check if the current trap was from user mode.
786          * - Check if the current thread is valid.
787          * - Check if the thread requires a user call chain to be
788          *   captured.
789          *
790          * We are still in NMI mode at this point.
791          */
792         testl   %ebx,%ebx
793         jz      nocallchain     /* not from userspace */
794         movq    PCPU(CURTHREAD),%rax
795         orq     %rax,%rax       /* curthread present? */
796         jz      nocallchain
797         /*
798          * Move execution to the regular kernel stack, because we
799          * committed to return through doreti.
800          */
801         movq    %rsp,%rsi       /* source stack pointer */
802         movq    $TF_SIZE,%rcx
803         movq    PCPU(RSP0),%rdx
804         subq    %rcx,%rdx
805         movq    %rdx,%rdi       /* destination stack pointer */
806         shrq    $3,%rcx         /* trap frame size in long words */
807         pushfq
808         andq    $~(PSL_D | PSL_AC),(%rsp)
809         popfq
810         rep
811         movsq                   /* copy trapframe */
812         movq    %rdx,%rsp       /* we are on the regular kstack */
813
814         testl   $TDP_CALLCHAIN,TD_PFLAGS(%rax) /* flagged for capture? */
815         jz      nocallchain
816         /*
817          * A user callchain is to be captured, so:
818          * - Take the processor out of "NMI" mode by faking an "iret",
819          *   to allow for nested NMI interrupts.
820          * - Enable interrupts, so that copyin() can work.
821          */
822         movl    %ss,%eax
823         pushq   %rax            /* tf_ss */
824         pushq   %rdx            /* tf_rsp (on kernel stack) */
825         pushfq                  /* tf_rflags */
826         movl    %cs,%eax
827         pushq   %rax            /* tf_cs */
828         pushq   $outofnmi       /* tf_rip */
829         iretq
830 outofnmi:
831         /*
832          * At this point the processor has exited NMI mode and is running
833          * with interrupts turned off on the normal kernel stack.
834          *
835          * If a pending NMI gets recognized at or after this point, it
836          * will cause a kernel callchain to be traced.
837          *
838          * We turn interrupts back on, and call the user callchain capture hook.
839          */
840         movq    pmc_hook,%rax
841         orq     %rax,%rax
842         jz      nocallchain
843         movq    PCPU(CURTHREAD),%rdi            /* thread */
844         movq    $PMC_FN_USER_CALLCHAIN,%rsi     /* command */
845         movq    %rsp,%rdx                       /* frame */
846         sti
847         call    *%rax
848         cli
849 nocallchain:
850 #endif
851         testl   %ebx,%ebx       /* %ebx == 0 => return to userland */
852         jnz     doreti_exit
853         /*
854          * Restore speculation control MSR, if preserved.
855          */
856         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
857         je      1f
858         movl    %r14d,%eax
859         xorl    %edx,%edx
860         movl    $MSR_IA32_SPEC_CTRL,%ecx
861         wrmsr
862         /*
863          * Put back the preserved MSR_GSBASE value.
864          */
865 1:      movl    $MSR_GSBASE,%ecx
866         movq    %r12,%rdx
867         movl    %edx,%eax
868         shrq    $32,%rdx
869         wrmsr
870         cmpb    $0, nmi_flush_l1d_sw(%rip)
871         je      2f
872         call    flush_l1d_sw            /* bhyve L1TF assist */
873 2:      movq    %r13,%cr3
874         RESTORE_REGS
875         addq    $TF_RIP,%rsp
876         jmp     doreti_iret
877
878 /*
879  * MC# handling is similar to NMI.
880  *
881  * As with NMIs, machine check exceptions do not respect RFLAGS.IF and
882  * can occur at any time with a GS.base value that does not correspond
883  * to the privilege level in CS.
884  *
885  * Machine checks are not unblocked by iretq, but it is best to run
886  * the handler with interrupts disabled since the exception may have
887  * interrupted a critical section.
888  *
889  * The MC# handler runs on its own stack (tss_ist3).  The canonical
890  * GS.base value for the processor is stored just above the bottom of
891  * its MC# stack.  For exceptions taken from kernel mode, the current
892  * value in the processor's GS.base is saved at entry to C-preserved
893  * register %r12, the canonical value for GS.base is then loaded into
894  * the processor, and the saved value is restored at exit time.  For
895  * exceptions taken from user mode, the cheaper 'SWAPGS' instructions
896  * are used for swapping GS.base.
897  */
898
899 IDTVEC(mchk)
900         subq    $TF_RIP,%rsp
901         movl    $(T_MCHK),TF_TRAPNO(%rsp)
902         movq    $0,TF_ADDR(%rsp)
903         movq    $0,TF_ERR(%rsp)
904         movq    %rdi,TF_RDI(%rsp)
905         movq    %rsi,TF_RSI(%rsp)
906         movq    %rdx,TF_RDX(%rsp)
907         movq    %rcx,TF_RCX(%rsp)
908         movq    %r8,TF_R8(%rsp)
909         movq    %r9,TF_R9(%rsp)
910         movq    %rax,TF_RAX(%rsp)
911         movq    %rbx,TF_RBX(%rsp)
912         movq    %rbp,TF_RBP(%rsp)
913         movq    %r10,TF_R10(%rsp)
914         movq    %r11,TF_R11(%rsp)
915         movq    %r12,TF_R12(%rsp)
916         movq    %r13,TF_R13(%rsp)
917         movq    %r14,TF_R14(%rsp)
918         movq    %r15,TF_R15(%rsp)
919         SAVE_SEGS
920         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
921         pushfq
922         andq    $~(PSL_D | PSL_AC),(%rsp)
923         popfq
924         xorl    %ebx,%ebx
925         testb   $SEL_RPL_MASK,TF_CS(%rsp)
926         jnz     mchk_fromuserspace
927         /*
928          * We've interrupted the kernel.  Preserve GS.base in %r12,
929          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
930          */
931         movl    $MSR_GSBASE,%ecx
932         rdmsr
933         movq    %rax,%r12
934         shlq    $32,%rdx
935         orq     %rdx,%r12
936         /* Retrieve and load the canonical value for GS.base. */
937         movq    TF_SIZE(%rsp),%rdx
938         movl    %edx,%eax
939         shrq    $32,%rdx
940         wrmsr
941         movq    %cr3,%r13
942         movq    PCPU(KCR3),%rax
943         cmpq    $~0,%rax
944         je      1f
945         movq    %rax,%cr3
946 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
947         je      mchk_calltrap
948         movl    $MSR_IA32_SPEC_CTRL,%ecx
949         rdmsr
950         movl    %eax,%r14d
951         call    handle_ibrs_entry
952         jmp     mchk_calltrap
953 mchk_fromuserspace:
954         incl    %ebx
955         swapgs
956         movq    %cr3,%r13
957         movq    PCPU(KCR3),%rax
958         cmpq    $~0,%rax
959         je      1f
960         movq    %rax,%cr3
961 1:      call    handle_ibrs_entry
962 /* Note: this label is also used by ddb and gdb: */
963 mchk_calltrap:
964         FAKE_MCOUNT(TF_RIP(%rsp))
965         movq    %rsp,%rdi
966         call    mca_intr
967         MEXITCOUNT
968         testl   %ebx,%ebx       /* %ebx == 0 => return to userland */
969         jnz     doreti_exit
970         /*
971          * Restore speculation control MSR, if preserved.
972          */
973         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
974         je      1f
975         movl    %r14d,%eax
976         xorl    %edx,%edx
977         movl    $MSR_IA32_SPEC_CTRL,%ecx
978         wrmsr
979         /*
980          * Put back the preserved MSR_GSBASE value.
981          */
982 1:      movl    $MSR_GSBASE,%ecx
983         movq    %r12,%rdx
984         movl    %edx,%eax
985         shrq    $32,%rdx
986         wrmsr
987         movq    %r13,%cr3
988         RESTORE_REGS
989         addq    $TF_RIP,%rsp
990         jmp     doreti_iret
991
992 ENTRY(fork_trampoline)
993         movq    %r12,%rdi               /* function */
994         movq    %rbx,%rsi               /* arg1 */
995         movq    %rsp,%rdx               /* trapframe pointer */
996         call    fork_exit
997         MEXITCOUNT
998         jmp     doreti                  /* Handle any ASTs */
999
1000 /*
1001  * To efficiently implement classification of trap and interrupt handlers
1002  * for profiling, there must be only trap handlers between the labels btrap
1003  * and bintr, and only interrupt handlers between the labels bintr and
1004  * eintr.  This is implemented (partly) by including files that contain
1005  * some of the handlers.  Before including the files, set up a normal asm
1006  * environment so that the included files doen't need to know that they are
1007  * included.
1008  */
1009
1010 #ifdef COMPAT_FREEBSD32
1011         .data
1012         .p2align 4
1013         .text
1014         SUPERALIGN_TEXT
1015
1016 #include <amd64/ia32/ia32_exception.S>
1017 #endif
1018
1019         .data
1020         .p2align 4
1021         .text
1022         SUPERALIGN_TEXT
1023 MCOUNT_LABEL(bintr)
1024
1025 #include <amd64/amd64/apic_vector.S>
1026
1027 #ifdef DEV_ATPIC
1028         .data
1029         .p2align 4
1030         .text
1031         SUPERALIGN_TEXT
1032
1033 #include <amd64/amd64/atpic_vector.S>
1034 #endif
1035
1036         .text
1037 MCOUNT_LABEL(eintr)
1038
1039 /*
1040  * void doreti(struct trapframe)
1041  *
1042  * Handle return from interrupts, traps and syscalls.
1043  */
1044         .text
1045         SUPERALIGN_TEXT
1046         .type   doreti,@function
1047         .globl  doreti
1048 doreti:
1049         FAKE_MCOUNT($bintr)             /* init "from" bintr -> doreti */
1050         /*
1051          * Check if ASTs can be handled now.
1052          */
1053         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* are we returning to user mode? */
1054         jz      doreti_exit             /* can't handle ASTs now if not */
1055
1056 doreti_ast:
1057         /*
1058          * Check for ASTs atomically with returning.  Disabling CPU
1059          * interrupts provides sufficient locking even in the SMP case,
1060          * since we will be informed of any new ASTs by an IPI.
1061          */
1062         cli
1063         movq    PCPU(CURTHREAD),%rax
1064         testl   $TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
1065         je      doreti_exit
1066         sti
1067         movq    %rsp,%rdi       /* pass a pointer to the trapframe */
1068         call    ast
1069         jmp     doreti_ast
1070
1071         /*
1072          * doreti_exit: pop registers, iret.
1073          *
1074          *      The segment register pop is a special case, since it may
1075          *      fault if (for example) a sigreturn specifies bad segment
1076          *      registers.  The fault is handled in trap.c.
1077          */
1078 doreti_exit:
1079         MEXITCOUNT
1080         movq    PCPU(CURPCB),%r8
1081
1082         /*
1083          * Do not reload segment registers for kernel.
1084          * Since we do not reload segments registers with sane
1085          * values on kernel entry, descriptors referenced by
1086          * segments registers might be not valid.  This is fatal
1087          * for user mode, but is not a problem for the kernel.
1088          */
1089         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1090         jz      ld_regs
1091         testl   $PCB_FULL_IRET,PCB_FLAGS(%r8)
1092         jz      ld_regs
1093         andl    $~PCB_FULL_IRET,PCB_FLAGS(%r8)
1094         testl   $TF_HASSEGS,TF_FLAGS(%rsp)
1095         je      set_segs
1096
1097 do_segs:
1098         /* Restore %fs and fsbase */
1099         movw    TF_FS(%rsp),%ax
1100         .globl  ld_fs
1101 ld_fs:
1102         movw    %ax,%fs
1103         cmpw    $KUF32SEL,%ax
1104         jne     1f
1105         movl    $MSR_FSBASE,%ecx
1106         movl    PCB_FSBASE(%r8),%eax
1107         movl    PCB_FSBASE+4(%r8),%edx
1108         .globl  ld_fsbase
1109 ld_fsbase:
1110         wrmsr
1111 1:
1112         /* Restore %gs and gsbase */
1113         movw    TF_GS(%rsp),%si
1114         pushfq
1115         cli
1116         movl    $MSR_GSBASE,%ecx
1117         /* Save current kernel %gs base into %r12d:%r13d */
1118         rdmsr
1119         movl    %eax,%r12d
1120         movl    %edx,%r13d
1121         .globl  ld_gs
1122 ld_gs:
1123         movw    %si,%gs
1124         /* Save user %gs base into %r14d:%r15d */
1125         rdmsr
1126         movl    %eax,%r14d
1127         movl    %edx,%r15d
1128         /* Restore kernel %gs base */
1129         movl    %r12d,%eax
1130         movl    %r13d,%edx
1131         wrmsr
1132         popfq
1133         /*
1134          * Restore user %gs base, either from PCB if used for TLS, or
1135          * from the previously saved msr read.
1136          */
1137         movl    $MSR_KGSBASE,%ecx
1138         cmpw    $KUG32SEL,%si
1139         jne     1f
1140         movl    PCB_GSBASE(%r8),%eax
1141         movl    PCB_GSBASE+4(%r8),%edx
1142         jmp     ld_gsbase
1143 1:
1144         movl    %r14d,%eax
1145         movl    %r15d,%edx
1146         .globl  ld_gsbase
1147 ld_gsbase:
1148         wrmsr   /* May trap if non-canonical, but only for TLS. */
1149         .globl  ld_es
1150 ld_es:
1151         movw    TF_ES(%rsp),%es
1152         .globl  ld_ds
1153 ld_ds:
1154         movw    TF_DS(%rsp),%ds
1155 ld_regs:
1156         RESTORE_REGS
1157         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
1158         jz      2f                      /* keep running with kernel GS.base */
1159         cli
1160         call    handle_ibrs_exit_rs
1161         callq   *mds_handler
1162         cmpq    $~0,PCPU(UCR3)
1163         je      1f
1164         pushq   %rdx
1165         movq    PCPU(PTI_RSP0),%rdx
1166         subq    $PTI_SIZE,%rdx
1167         movq    %rax,PTI_RAX(%rdx)
1168         popq    %rax
1169         movq    %rax,PTI_RDX(%rdx)
1170         movq    TF_RIP(%rsp),%rax
1171         movq    %rax,PTI_RIP(%rdx)
1172         movq    TF_CS(%rsp),%rax
1173         movq    %rax,PTI_CS(%rdx)
1174         movq    TF_RFLAGS(%rsp),%rax
1175         movq    %rax,PTI_RFLAGS(%rdx)
1176         movq    TF_RSP(%rsp),%rax
1177         movq    %rax,PTI_RSP(%rdx)
1178         movq    TF_SS(%rsp),%rax
1179         movq    %rax,PTI_SS(%rdx)
1180         movq    PCPU(UCR3),%rax
1181         swapgs
1182         movq    %rdx,%rsp
1183         movq    %rax,%cr3
1184         popq    %rdx
1185         popq    %rax
1186         addq    $8,%rsp
1187         jmp     doreti_iret
1188 1:      swapgs
1189 2:      addq    $TF_RIP,%rsp
1190         .globl  doreti_iret
1191 doreti_iret:
1192         iretq
1193
1194 set_segs:
1195         movw    $KUDSEL,%ax
1196         movw    %ax,TF_DS(%rsp)
1197         movw    %ax,TF_ES(%rsp)
1198         movw    $KUF32SEL,TF_FS(%rsp)
1199         movw    $KUG32SEL,TF_GS(%rsp)
1200         jmp     do_segs
1201
1202         /*
1203          * doreti_iret_fault.  Alternative return code for
1204          * the case where we get a fault in the doreti_exit code
1205          * above.  trap() (amd64/amd64/trap.c) catches this specific
1206          * case, sends the process a signal and continues in the
1207          * corresponding place in the code below.
1208          */
1209         ALIGN_TEXT
1210         .globl  doreti_iret_fault
1211 doreti_iret_fault:
1212         subq    $TF_RIP,%rsp            /* space including tf_err, tf_trapno */
1213         movq    %rax,TF_RAX(%rsp)
1214         movq    %rdx,TF_RDX(%rsp)
1215         movq    %rcx,TF_RCX(%rsp)
1216         call    handle_ibrs_entry
1217         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1218         jz      1f
1219         sti
1220 1:
1221         SAVE_SEGS
1222         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
1223         movq    %rdi,TF_RDI(%rsp)
1224         movq    %rsi,TF_RSI(%rsp)
1225         movq    %r8,TF_R8(%rsp)
1226         movq    %r9,TF_R9(%rsp)
1227         movq    %rbx,TF_RBX(%rsp)
1228         movq    %rbp,TF_RBP(%rsp)
1229         movq    %r10,TF_R10(%rsp)
1230         movq    %r11,TF_R11(%rsp)
1231         movq    %r12,TF_R12(%rsp)
1232         movq    %r13,TF_R13(%rsp)
1233         movq    %r14,TF_R14(%rsp)
1234         movq    %r15,TF_R15(%rsp)
1235         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1236         movq    $0,TF_ERR(%rsp) /* XXX should be the error code */
1237         movq    $0,TF_ADDR(%rsp)
1238         FAKE_MCOUNT(TF_RIP(%rsp))
1239         jmp     calltrap
1240
1241         ALIGN_TEXT
1242         .globl  ds_load_fault
1243 ds_load_fault:
1244         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1245         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1246         jz      1f
1247         sti
1248 1:
1249         movq    %rsp,%rdi
1250         call    trap
1251         movw    $KUDSEL,TF_DS(%rsp)
1252         jmp     doreti
1253
1254         ALIGN_TEXT
1255         .globl  es_load_fault
1256 es_load_fault:
1257         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1258         testl   $PSL_I,TF_RFLAGS(%rsp)
1259         jz      1f
1260         sti
1261 1:
1262         movq    %rsp,%rdi
1263         call    trap
1264         movw    $KUDSEL,TF_ES(%rsp)
1265         jmp     doreti
1266
1267         ALIGN_TEXT
1268         .globl  fs_load_fault
1269 fs_load_fault:
1270         testl   $PSL_I,TF_RFLAGS(%rsp)
1271         jz      1f
1272         sti
1273 1:
1274         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1275         movq    %rsp,%rdi
1276         call    trap
1277         movw    $KUF32SEL,TF_FS(%rsp)
1278         jmp     doreti
1279
1280         ALIGN_TEXT
1281         .globl  gs_load_fault
1282 gs_load_fault:
1283         popfq
1284         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1285         testl   $PSL_I,TF_RFLAGS(%rsp)
1286         jz      1f
1287         sti
1288 1:
1289         movq    %rsp,%rdi
1290         call    trap
1291         movw    $KUG32SEL,TF_GS(%rsp)
1292         jmp     doreti
1293
1294         ALIGN_TEXT
1295         .globl  fsbase_load_fault
1296 fsbase_load_fault:
1297         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1298         testl   $PSL_I,TF_RFLAGS(%rsp)
1299         jz      1f
1300         sti
1301 1:
1302         movq    %rsp,%rdi
1303         call    trap
1304         movq    PCPU(CURTHREAD),%r8
1305         movq    TD_PCB(%r8),%r8
1306         movq    $0,PCB_FSBASE(%r8)
1307         jmp     doreti
1308
1309         ALIGN_TEXT
1310         .globl  gsbase_load_fault
1311 gsbase_load_fault:
1312         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1313         testl   $PSL_I,TF_RFLAGS(%rsp)
1314         jz      1f
1315         sti
1316 1:
1317         movq    %rsp,%rdi
1318         call    trap
1319         movq    PCPU(CURTHREAD),%r8
1320         movq    TD_PCB(%r8),%r8
1321         movq    $0,PCB_GSBASE(%r8)
1322         jmp     doreti
1323
1324 #ifdef HWPMC_HOOKS
1325         ENTRY(end_exceptions)
1326 #endif