]> CyberLeo.Net >> Repos - FreeBSD/FreeBSD.git/blob - sys/amd64/amd64/exception.S
Upgrade Unbound to 1.7.3. More to follow.
[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         /* Restore preserved registers. */
516         MEXITCOUNT
517         movq    TF_RDI(%rsp),%rdi       /* bonus; preserve arg 1 */
518         movq    TF_RSI(%rsp),%rsi       /* bonus: preserve arg 2 */
519         movq    TF_RDX(%rsp),%rdx       /* return value 2 */
520         movq    TF_RAX(%rsp),%rax       /* return value 1 */
521         movq    TF_RFLAGS(%rsp),%r11    /* original %rflags */
522         movq    TF_RIP(%rsp),%rcx       /* original %rip */
523         movq    TF_RSP(%rsp),%rsp       /* user stack pointer */
524         cmpq    $~0,PCPU(UCR3)
525         je      2f
526         movq    PCPU(UCR3),%r9
527         movq    %r9,%cr3
528         xorl    %r9d,%r9d
529 2:      swapgs
530         sysretq
531
532 3:      /* AST scheduled. */
533         sti
534         movq    %rsp,%rdi
535         call    ast
536         jmp     1b
537
538 4:      /* Requested full context restore, use doreti for that. */
539         MEXITCOUNT
540         jmp     doreti
541
542 /*
543  * Here for CYA insurance, in case a "syscall" instruction gets
544  * issued from 32 bit compatibility mode. MSR_CSTAR has to point
545  * to *something* if EFER_SCE is enabled.
546  */
547 IDTVEC(fast_syscall32)
548         sysret
549
550 /*
551  * DB# handler is very similar to NM#, because 'mov/pop %ss' delay
552  * generation of exception until the next instruction is executed,
553  * which might be a kernel entry.  So we must execute the handler
554  * on IST stack and be ready for non-kernel GSBASE.
555  */
556 IDTVEC(dbg)
557         subq    $TF_RIP,%rsp
558         movl    $(T_TRCTRAP),TF_TRAPNO(%rsp)
559         movq    $0,TF_ADDR(%rsp)
560         movq    $0,TF_ERR(%rsp)
561         movq    %rdi,TF_RDI(%rsp)
562         movq    %rsi,TF_RSI(%rsp)
563         movq    %rdx,TF_RDX(%rsp)
564         movq    %rcx,TF_RCX(%rsp)
565         movq    %r8,TF_R8(%rsp)
566         movq    %r9,TF_R9(%rsp)
567         movq    %rax,TF_RAX(%rsp)
568         movq    %rbx,TF_RBX(%rsp)
569         movq    %rbp,TF_RBP(%rsp)
570         movq    %r10,TF_R10(%rsp)
571         movq    %r11,TF_R11(%rsp)
572         movq    %r12,TF_R12(%rsp)
573         movq    %r13,TF_R13(%rsp)
574         movq    %r14,TF_R14(%rsp)
575         movq    %r15,TF_R15(%rsp)
576         SAVE_SEGS
577         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
578         pushfq
579         andq    $~(PSL_D | PSL_AC),(%rsp)
580         popfq
581         testb   $SEL_RPL_MASK,TF_CS(%rsp)
582         jnz     dbg_fromuserspace
583         /*
584          * We've interrupted the kernel.  Preserve GS.base in %r12,
585          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
586          */
587         movl    $MSR_GSBASE,%ecx
588         rdmsr
589         movq    %rax,%r12
590         shlq    $32,%rdx
591         orq     %rdx,%r12
592         /* Retrieve and load the canonical value for GS.base. */
593         movq    TF_SIZE(%rsp),%rdx
594         movl    %edx,%eax
595         shrq    $32,%rdx
596         wrmsr
597         movq    %cr3,%r13
598         movq    PCPU(KCR3),%rax
599         cmpq    $~0,%rax
600         je      1f
601         movq    %rax,%cr3
602 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
603         je      2f
604         movl    $MSR_IA32_SPEC_CTRL,%ecx
605         rdmsr
606         movl    %eax,%r14d
607         call    handle_ibrs_entry
608 2:      FAKE_MCOUNT(TF_RIP(%rsp))
609         movq    %rsp,%rdi
610         call    trap
611         MEXITCOUNT
612         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
613         je      3f
614         movl    %r14d,%eax
615         xorl    %edx,%edx
616         movl    $MSR_IA32_SPEC_CTRL,%ecx
617         wrmsr
618         /*
619          * Put back the preserved MSR_GSBASE value.
620          */
621 3:      movl    $MSR_GSBASE,%ecx
622         movq    %r12,%rdx
623         movl    %edx,%eax
624         shrq    $32,%rdx
625         wrmsr
626         movq    %r13,%cr3
627         RESTORE_REGS
628         addq    $TF_RIP,%rsp
629         jmp     doreti_iret
630 dbg_fromuserspace:
631         /*
632          * Switch to kernel GSBASE and kernel page table, and copy frame
633          * from the IST stack to the normal kernel stack, since trap()
634          * re-enables interrupts, and since we might trap on DB# while
635          * in trap().
636          */
637         swapgs
638         movq    PCPU(KCR3),%rax
639         cmpq    $~0,%rax
640         je      1f
641         movq    %rax,%cr3
642 1:      movq    PCPU(RSP0),%rax
643         movl    $TF_SIZE,%ecx
644         subq    %rcx,%rax
645         movq    %rax,%rdi
646         movq    %rsp,%rsi
647         rep;movsb
648         movq    %rax,%rsp
649         call    handle_ibrs_entry
650         movq    PCPU(CURPCB),%rdi
651         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)
652         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
653         jz      3f
654         cmpw    $KUF32SEL,TF_FS(%rsp)
655         jne     2f
656         rdfsbase %rax
657         movq    %rax,PCB_FSBASE(%rdi)
658 2:      cmpw    $KUG32SEL,TF_GS(%rsp)
659         jne     3f
660         movl    $MSR_KGSBASE,%ecx
661         rdmsr
662         shlq    $32,%rdx
663         orq     %rdx,%rax
664         movq    %rax,PCB_GSBASE(%rdi)
665 3:      jmp     calltrap
666
667 /*
668  * NMI handling is special.
669  *
670  * First, NMIs do not respect the state of the processor's RFLAGS.IF
671  * bit.  The NMI handler may be entered at any time, including when
672  * the processor is in a critical section with RFLAGS.IF == 0.
673  * The processor's GS.base value could be invalid on entry to the
674  * handler.
675  *
676  * Second, the processor treats NMIs specially, blocking further NMIs
677  * until an 'iretq' instruction is executed.  We thus need to execute
678  * the NMI handler with interrupts disabled, to prevent a nested interrupt
679  * from executing an 'iretq' instruction and inadvertently taking the
680  * processor out of NMI mode.
681  *
682  * Third, the NMI handler runs on its own stack (tss_ist2). The canonical
683  * GS.base value for the processor is stored just above the bottom of its
684  * NMI stack.  For NMIs taken from kernel mode, the current value in
685  * the processor's GS.base is saved at entry to C-preserved register %r12,
686  * the canonical value for GS.base is then loaded into the processor, and
687  * the saved value is restored at exit time.  For NMIs taken from user mode,
688  * the cheaper 'SWAPGS' instructions are used for swapping GS.base.
689  */
690
691 IDTVEC(nmi)
692         subq    $TF_RIP,%rsp
693         movl    $(T_NMI),TF_TRAPNO(%rsp)
694         movq    $0,TF_ADDR(%rsp)
695         movq    $0,TF_ERR(%rsp)
696         movq    %rdi,TF_RDI(%rsp)
697         movq    %rsi,TF_RSI(%rsp)
698         movq    %rdx,TF_RDX(%rsp)
699         movq    %rcx,TF_RCX(%rsp)
700         movq    %r8,TF_R8(%rsp)
701         movq    %r9,TF_R9(%rsp)
702         movq    %rax,TF_RAX(%rsp)
703         movq    %rbx,TF_RBX(%rsp)
704         movq    %rbp,TF_RBP(%rsp)
705         movq    %r10,TF_R10(%rsp)
706         movq    %r11,TF_R11(%rsp)
707         movq    %r12,TF_R12(%rsp)
708         movq    %r13,TF_R13(%rsp)
709         movq    %r14,TF_R14(%rsp)
710         movq    %r15,TF_R15(%rsp)
711         SAVE_SEGS
712         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
713         pushfq
714         andq    $~(PSL_D | PSL_AC),(%rsp)
715         popfq
716         xorl    %ebx,%ebx
717         testb   $SEL_RPL_MASK,TF_CS(%rsp)
718         jnz     nmi_fromuserspace
719         /*
720          * We've interrupted the kernel.  Preserve GS.base in %r12,
721          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
722          */
723         movl    $MSR_GSBASE,%ecx
724         rdmsr
725         movq    %rax,%r12
726         shlq    $32,%rdx
727         orq     %rdx,%r12
728         /* Retrieve and load the canonical value for GS.base. */
729         movq    TF_SIZE(%rsp),%rdx
730         movl    %edx,%eax
731         shrq    $32,%rdx
732         wrmsr
733         movq    %cr3,%r13
734         movq    PCPU(KCR3),%rax
735         cmpq    $~0,%rax
736         je      1f
737         movq    %rax,%cr3
738 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
739         je      nmi_calltrap
740         movl    $MSR_IA32_SPEC_CTRL,%ecx
741         rdmsr
742         movl    %eax,%r14d
743         call    handle_ibrs_entry
744         jmp     nmi_calltrap
745 nmi_fromuserspace:
746         incl    %ebx
747         swapgs
748         movq    %cr3,%r13
749         movq    PCPU(KCR3),%rax
750         cmpq    $~0,%rax
751         je      1f
752         movq    %rax,%cr3
753 1:      call    handle_ibrs_entry
754         movq    PCPU(CURPCB),%rdi
755         testq   %rdi,%rdi
756         jz      3f
757         orl     $PCB_FULL_IRET,PCB_FLAGS(%rdi)
758         testb   $CPUID_STDEXT_FSGSBASE,cpu_stdext_feature(%rip)
759         jz      3f
760         cmpw    $KUF32SEL,TF_FS(%rsp)
761         jne     2f
762         rdfsbase %rax
763         movq    %rax,PCB_FSBASE(%rdi)
764 2:      cmpw    $KUG32SEL,TF_GS(%rsp)
765         jne     3f
766         movl    $MSR_KGSBASE,%ecx
767         rdmsr
768         shlq    $32,%rdx
769         orq     %rdx,%rax
770         movq    %rax,PCB_GSBASE(%rdi)
771 3:
772 /* Note: this label is also used by ddb and gdb: */
773 nmi_calltrap:
774         FAKE_MCOUNT(TF_RIP(%rsp))
775         movq    %rsp,%rdi
776         call    trap
777         MEXITCOUNT
778 #ifdef HWPMC_HOOKS
779         /*
780          * Capture a userspace callchain if needed.
781          *
782          * - Check if the current trap was from user mode.
783          * - Check if the current thread is valid.
784          * - Check if the thread requires a user call chain to be
785          *   captured.
786          *
787          * We are still in NMI mode at this point.
788          */
789         testl   %ebx,%ebx
790         jz      nocallchain     /* not from userspace */
791         movq    PCPU(CURTHREAD),%rax
792         orq     %rax,%rax       /* curthread present? */
793         jz      nocallchain
794         /*
795          * Move execution to the regular kernel stack, because we
796          * committed to return through doreti.
797          */
798         movq    %rsp,%rsi       /* source stack pointer */
799         movq    $TF_SIZE,%rcx
800         movq    PCPU(RSP0),%rdx
801         subq    %rcx,%rdx
802         movq    %rdx,%rdi       /* destination stack pointer */
803         shrq    $3,%rcx         /* trap frame size in long words */
804         pushfq
805         andq    $~(PSL_D | PSL_AC),(%rsp)
806         popfq
807         rep
808         movsq                   /* copy trapframe */
809         movq    %rdx,%rsp       /* we are on the regular kstack */
810
811         testl   $TDP_CALLCHAIN,TD_PFLAGS(%rax) /* flagged for capture? */
812         jz      nocallchain
813         /*
814          * A user callchain is to be captured, so:
815          * - Take the processor out of "NMI" mode by faking an "iret",
816          *   to allow for nested NMI interrupts.
817          * - Enable interrupts, so that copyin() can work.
818          */
819         movl    %ss,%eax
820         pushq   %rax            /* tf_ss */
821         pushq   %rdx            /* tf_rsp (on kernel stack) */
822         pushfq                  /* tf_rflags */
823         movl    %cs,%eax
824         pushq   %rax            /* tf_cs */
825         pushq   $outofnmi       /* tf_rip */
826         iretq
827 outofnmi:
828         /*
829          * At this point the processor has exited NMI mode and is running
830          * with interrupts turned off on the normal kernel stack.
831          *
832          * If a pending NMI gets recognized at or after this point, it
833          * will cause a kernel callchain to be traced.
834          *
835          * We turn interrupts back on, and call the user callchain capture hook.
836          */
837         movq    pmc_hook,%rax
838         orq     %rax,%rax
839         jz      nocallchain
840         movq    PCPU(CURTHREAD),%rdi            /* thread */
841         movq    $PMC_FN_USER_CALLCHAIN,%rsi     /* command */
842         movq    %rsp,%rdx                       /* frame */
843         sti
844         call    *%rax
845         cli
846 nocallchain:
847 #endif
848         testl   %ebx,%ebx       /* %ebx == 0 => return to userland */
849         jnz     doreti_exit
850         /*
851          * Restore speculation control MSR, if preserved.
852          */
853         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
854         je      1f
855         movl    %r14d,%eax
856         xorl    %edx,%edx
857         movl    $MSR_IA32_SPEC_CTRL,%ecx
858         wrmsr
859         /*
860          * Put back the preserved MSR_GSBASE value.
861          */
862 1:      movl    $MSR_GSBASE,%ecx
863         movq    %r12,%rdx
864         movl    %edx,%eax
865         shrq    $32,%rdx
866         wrmsr
867         cmpb    $0, nmi_flush_l1d_sw(%rip)
868         je      2f
869         call    flush_l1d_sw            /* bhyve L1TF assist */
870 2:      movq    %r13,%cr3
871         RESTORE_REGS
872         addq    $TF_RIP,%rsp
873         jmp     doreti_iret
874
875 /*
876  * MC# handling is similar to NMI.
877  *
878  * As with NMIs, machine check exceptions do not respect RFLAGS.IF and
879  * can occur at any time with a GS.base value that does not correspond
880  * to the privilege level in CS.
881  *
882  * Machine checks are not unblocked by iretq, but it is best to run
883  * the handler with interrupts disabled since the exception may have
884  * interrupted a critical section.
885  *
886  * The MC# handler runs on its own stack (tss_ist3).  The canonical
887  * GS.base value for the processor is stored just above the bottom of
888  * its MC# stack.  For exceptions taken from kernel mode, the current
889  * value in the processor's GS.base is saved at entry to C-preserved
890  * register %r12, the canonical value for GS.base is then loaded into
891  * the processor, and the saved value is restored at exit time.  For
892  * exceptions taken from user mode, the cheaper 'SWAPGS' instructions
893  * are used for swapping GS.base.
894  */
895
896 IDTVEC(mchk)
897         subq    $TF_RIP,%rsp
898         movl    $(T_MCHK),TF_TRAPNO(%rsp)
899         movq    $0,TF_ADDR(%rsp)
900         movq    $0,TF_ERR(%rsp)
901         movq    %rdi,TF_RDI(%rsp)
902         movq    %rsi,TF_RSI(%rsp)
903         movq    %rdx,TF_RDX(%rsp)
904         movq    %rcx,TF_RCX(%rsp)
905         movq    %r8,TF_R8(%rsp)
906         movq    %r9,TF_R9(%rsp)
907         movq    %rax,TF_RAX(%rsp)
908         movq    %rbx,TF_RBX(%rsp)
909         movq    %rbp,TF_RBP(%rsp)
910         movq    %r10,TF_R10(%rsp)
911         movq    %r11,TF_R11(%rsp)
912         movq    %r12,TF_R12(%rsp)
913         movq    %r13,TF_R13(%rsp)
914         movq    %r14,TF_R14(%rsp)
915         movq    %r15,TF_R15(%rsp)
916         SAVE_SEGS
917         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
918         pushfq
919         andq    $~(PSL_D | PSL_AC),(%rsp)
920         popfq
921         xorl    %ebx,%ebx
922         testb   $SEL_RPL_MASK,TF_CS(%rsp)
923         jnz     mchk_fromuserspace
924         /*
925          * We've interrupted the kernel.  Preserve GS.base in %r12,
926          * %cr3 in %r13, and possibly lower half of MSR_IA32_SPEC_CTL in %r14d.
927          */
928         movl    $MSR_GSBASE,%ecx
929         rdmsr
930         movq    %rax,%r12
931         shlq    $32,%rdx
932         orq     %rdx,%r12
933         /* Retrieve and load the canonical value for GS.base. */
934         movq    TF_SIZE(%rsp),%rdx
935         movl    %edx,%eax
936         shrq    $32,%rdx
937         wrmsr
938         movq    %cr3,%r13
939         movq    PCPU(KCR3),%rax
940         cmpq    $~0,%rax
941         je      1f
942         movq    %rax,%cr3
943 1:      testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
944         je      mchk_calltrap
945         movl    $MSR_IA32_SPEC_CTRL,%ecx
946         rdmsr
947         movl    %eax,%r14d
948         call    handle_ibrs_entry
949         jmp     mchk_calltrap
950 mchk_fromuserspace:
951         incl    %ebx
952         swapgs
953         movq    %cr3,%r13
954         movq    PCPU(KCR3),%rax
955         cmpq    $~0,%rax
956         je      1f
957         movq    %rax,%cr3
958 1:      call    handle_ibrs_entry
959 /* Note: this label is also used by ddb and gdb: */
960 mchk_calltrap:
961         FAKE_MCOUNT(TF_RIP(%rsp))
962         movq    %rsp,%rdi
963         call    mca_intr
964         MEXITCOUNT
965         testl   %ebx,%ebx       /* %ebx == 0 => return to userland */
966         jnz     doreti_exit
967         /*
968          * Restore speculation control MSR, if preserved.
969          */
970         testl   $CPUID_STDEXT3_IBPB,cpu_stdext_feature3(%rip)
971         je      1f
972         movl    %r14d,%eax
973         xorl    %edx,%edx
974         movl    $MSR_IA32_SPEC_CTRL,%ecx
975         wrmsr
976         /*
977          * Put back the preserved MSR_GSBASE value.
978          */
979 1:      movl    $MSR_GSBASE,%ecx
980         movq    %r12,%rdx
981         movl    %edx,%eax
982         shrq    $32,%rdx
983         wrmsr
984         movq    %r13,%cr3
985         RESTORE_REGS
986         addq    $TF_RIP,%rsp
987         jmp     doreti_iret
988
989 ENTRY(fork_trampoline)
990         movq    %r12,%rdi               /* function */
991         movq    %rbx,%rsi               /* arg1 */
992         movq    %rsp,%rdx               /* trapframe pointer */
993         call    fork_exit
994         MEXITCOUNT
995         jmp     doreti                  /* Handle any ASTs */
996
997 /*
998  * To efficiently implement classification of trap and interrupt handlers
999  * for profiling, there must be only trap handlers between the labels btrap
1000  * and bintr, and only interrupt handlers between the labels bintr and
1001  * eintr.  This is implemented (partly) by including files that contain
1002  * some of the handlers.  Before including the files, set up a normal asm
1003  * environment so that the included files doen't need to know that they are
1004  * included.
1005  */
1006
1007 #ifdef COMPAT_FREEBSD32
1008         .data
1009         .p2align 4
1010         .text
1011         SUPERALIGN_TEXT
1012
1013 #include <amd64/ia32/ia32_exception.S>
1014 #endif
1015
1016         .data
1017         .p2align 4
1018         .text
1019         SUPERALIGN_TEXT
1020 MCOUNT_LABEL(bintr)
1021
1022 #include <amd64/amd64/apic_vector.S>
1023
1024 #ifdef DEV_ATPIC
1025         .data
1026         .p2align 4
1027         .text
1028         SUPERALIGN_TEXT
1029
1030 #include <amd64/amd64/atpic_vector.S>
1031 #endif
1032
1033         .text
1034 MCOUNT_LABEL(eintr)
1035
1036 /*
1037  * void doreti(struct trapframe)
1038  *
1039  * Handle return from interrupts, traps and syscalls.
1040  */
1041         .text
1042         SUPERALIGN_TEXT
1043         .type   doreti,@function
1044         .globl  doreti
1045 doreti:
1046         FAKE_MCOUNT($bintr)             /* init "from" bintr -> doreti */
1047         /*
1048          * Check if ASTs can be handled now.
1049          */
1050         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* are we returning to user mode? */
1051         jz      doreti_exit             /* can't handle ASTs now if not */
1052
1053 doreti_ast:
1054         /*
1055          * Check for ASTs atomically with returning.  Disabling CPU
1056          * interrupts provides sufficient locking even in the SMP case,
1057          * since we will be informed of any new ASTs by an IPI.
1058          */
1059         cli
1060         movq    PCPU(CURTHREAD),%rax
1061         testl   $TDF_ASTPENDING | TDF_NEEDRESCHED,TD_FLAGS(%rax)
1062         je      doreti_exit
1063         sti
1064         movq    %rsp,%rdi       /* pass a pointer to the trapframe */
1065         call    ast
1066         jmp     doreti_ast
1067
1068         /*
1069          * doreti_exit: pop registers, iret.
1070          *
1071          *      The segment register pop is a special case, since it may
1072          *      fault if (for example) a sigreturn specifies bad segment
1073          *      registers.  The fault is handled in trap.c.
1074          */
1075 doreti_exit:
1076         MEXITCOUNT
1077         movq    PCPU(CURPCB),%r8
1078
1079         /*
1080          * Do not reload segment registers for kernel.
1081          * Since we do not reload segments registers with sane
1082          * values on kernel entry, descriptors referenced by
1083          * segments registers might be not valid.  This is fatal
1084          * for user mode, but is not a problem for the kernel.
1085          */
1086         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1087         jz      ld_regs
1088         testl   $PCB_FULL_IRET,PCB_FLAGS(%r8)
1089         jz      ld_regs
1090         andl    $~PCB_FULL_IRET,PCB_FLAGS(%r8)
1091         testl   $TF_HASSEGS,TF_FLAGS(%rsp)
1092         je      set_segs
1093
1094 do_segs:
1095         /* Restore %fs and fsbase */
1096         movw    TF_FS(%rsp),%ax
1097         .globl  ld_fs
1098 ld_fs:
1099         movw    %ax,%fs
1100         cmpw    $KUF32SEL,%ax
1101         jne     1f
1102         movl    $MSR_FSBASE,%ecx
1103         movl    PCB_FSBASE(%r8),%eax
1104         movl    PCB_FSBASE+4(%r8),%edx
1105         .globl  ld_fsbase
1106 ld_fsbase:
1107         wrmsr
1108 1:
1109         /* Restore %gs and gsbase */
1110         movw    TF_GS(%rsp),%si
1111         pushfq
1112         cli
1113         movl    $MSR_GSBASE,%ecx
1114         /* Save current kernel %gs base into %r12d:%r13d */
1115         rdmsr
1116         movl    %eax,%r12d
1117         movl    %edx,%r13d
1118         .globl  ld_gs
1119 ld_gs:
1120         movw    %si,%gs
1121         /* Save user %gs base into %r14d:%r15d */
1122         rdmsr
1123         movl    %eax,%r14d
1124         movl    %edx,%r15d
1125         /* Restore kernel %gs base */
1126         movl    %r12d,%eax
1127         movl    %r13d,%edx
1128         wrmsr
1129         popfq
1130         /*
1131          * Restore user %gs base, either from PCB if used for TLS, or
1132          * from the previously saved msr read.
1133          */
1134         movl    $MSR_KGSBASE,%ecx
1135         cmpw    $KUG32SEL,%si
1136         jne     1f
1137         movl    PCB_GSBASE(%r8),%eax
1138         movl    PCB_GSBASE+4(%r8),%edx
1139         jmp     ld_gsbase
1140 1:
1141         movl    %r14d,%eax
1142         movl    %r15d,%edx
1143         .globl  ld_gsbase
1144 ld_gsbase:
1145         wrmsr   /* May trap if non-canonical, but only for TLS. */
1146         .globl  ld_es
1147 ld_es:
1148         movw    TF_ES(%rsp),%es
1149         .globl  ld_ds
1150 ld_ds:
1151         movw    TF_DS(%rsp),%ds
1152 ld_regs:
1153         RESTORE_REGS
1154         testb   $SEL_RPL_MASK,TF_CS(%rsp) /* Did we come from kernel? */
1155         jz      2f                      /* keep running with kernel GS.base */
1156         cli
1157         call    handle_ibrs_exit_rs
1158         cmpq    $~0,PCPU(UCR3)
1159         je      1f
1160         pushq   %rdx
1161         movq    PCPU(PTI_RSP0),%rdx
1162         subq    $PTI_SIZE,%rdx
1163         movq    %rax,PTI_RAX(%rdx)
1164         popq    %rax
1165         movq    %rax,PTI_RDX(%rdx)
1166         movq    TF_RIP(%rsp),%rax
1167         movq    %rax,PTI_RIP(%rdx)
1168         movq    TF_CS(%rsp),%rax
1169         movq    %rax,PTI_CS(%rdx)
1170         movq    TF_RFLAGS(%rsp),%rax
1171         movq    %rax,PTI_RFLAGS(%rdx)
1172         movq    TF_RSP(%rsp),%rax
1173         movq    %rax,PTI_RSP(%rdx)
1174         movq    TF_SS(%rsp),%rax
1175         movq    %rax,PTI_SS(%rdx)
1176         movq    PCPU(UCR3),%rax
1177         swapgs
1178         movq    %rdx,%rsp
1179         movq    %rax,%cr3
1180         popq    %rdx
1181         popq    %rax
1182         addq    $8,%rsp
1183         jmp     doreti_iret
1184 1:      swapgs
1185 2:      addq    $TF_RIP,%rsp
1186         .globl  doreti_iret
1187 doreti_iret:
1188         iretq
1189
1190 set_segs:
1191         movw    $KUDSEL,%ax
1192         movw    %ax,TF_DS(%rsp)
1193         movw    %ax,TF_ES(%rsp)
1194         movw    $KUF32SEL,TF_FS(%rsp)
1195         movw    $KUG32SEL,TF_GS(%rsp)
1196         jmp     do_segs
1197
1198         /*
1199          * doreti_iret_fault.  Alternative return code for
1200          * the case where we get a fault in the doreti_exit code
1201          * above.  trap() (amd64/amd64/trap.c) catches this specific
1202          * case, sends the process a signal and continues in the
1203          * corresponding place in the code below.
1204          */
1205         ALIGN_TEXT
1206         .globl  doreti_iret_fault
1207 doreti_iret_fault:
1208         subq    $TF_RIP,%rsp            /* space including tf_err, tf_trapno */
1209         movq    %rax,TF_RAX(%rsp)
1210         movq    %rdx,TF_RDX(%rsp)
1211         movq    %rcx,TF_RCX(%rsp)
1212         call    handle_ibrs_entry
1213         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1214         jz      1f
1215         sti
1216 1:
1217         SAVE_SEGS
1218         movl    $TF_HASSEGS,TF_FLAGS(%rsp)
1219         movq    %rdi,TF_RDI(%rsp)
1220         movq    %rsi,TF_RSI(%rsp)
1221         movq    %r8,TF_R8(%rsp)
1222         movq    %r9,TF_R9(%rsp)
1223         movq    %rbx,TF_RBX(%rsp)
1224         movq    %rbp,TF_RBP(%rsp)
1225         movq    %r10,TF_R10(%rsp)
1226         movq    %r11,TF_R11(%rsp)
1227         movq    %r12,TF_R12(%rsp)
1228         movq    %r13,TF_R13(%rsp)
1229         movq    %r14,TF_R14(%rsp)
1230         movq    %r15,TF_R15(%rsp)
1231         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1232         movq    $0,TF_ERR(%rsp) /* XXX should be the error code */
1233         movq    $0,TF_ADDR(%rsp)
1234         FAKE_MCOUNT(TF_RIP(%rsp))
1235         jmp     calltrap
1236
1237         ALIGN_TEXT
1238         .globl  ds_load_fault
1239 ds_load_fault:
1240         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1241         testb   $SEL_RPL_MASK,TF_CS(%rsp)
1242         jz      1f
1243         sti
1244 1:
1245         movq    %rsp,%rdi
1246         call    trap
1247         movw    $KUDSEL,TF_DS(%rsp)
1248         jmp     doreti
1249
1250         ALIGN_TEXT
1251         .globl  es_load_fault
1252 es_load_fault:
1253         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1254         testl   $PSL_I,TF_RFLAGS(%rsp)
1255         jz      1f
1256         sti
1257 1:
1258         movq    %rsp,%rdi
1259         call    trap
1260         movw    $KUDSEL,TF_ES(%rsp)
1261         jmp     doreti
1262
1263         ALIGN_TEXT
1264         .globl  fs_load_fault
1265 fs_load_fault:
1266         testl   $PSL_I,TF_RFLAGS(%rsp)
1267         jz      1f
1268         sti
1269 1:
1270         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1271         movq    %rsp,%rdi
1272         call    trap
1273         movw    $KUF32SEL,TF_FS(%rsp)
1274         jmp     doreti
1275
1276         ALIGN_TEXT
1277         .globl  gs_load_fault
1278 gs_load_fault:
1279         popfq
1280         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1281         testl   $PSL_I,TF_RFLAGS(%rsp)
1282         jz      1f
1283         sti
1284 1:
1285         movq    %rsp,%rdi
1286         call    trap
1287         movw    $KUG32SEL,TF_GS(%rsp)
1288         jmp     doreti
1289
1290         ALIGN_TEXT
1291         .globl  fsbase_load_fault
1292 fsbase_load_fault:
1293         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1294         testl   $PSL_I,TF_RFLAGS(%rsp)
1295         jz      1f
1296         sti
1297 1:
1298         movq    %rsp,%rdi
1299         call    trap
1300         movq    PCPU(CURTHREAD),%r8
1301         movq    TD_PCB(%r8),%r8
1302         movq    $0,PCB_FSBASE(%r8)
1303         jmp     doreti
1304
1305         ALIGN_TEXT
1306         .globl  gsbase_load_fault
1307 gsbase_load_fault:
1308         movl    $T_PROTFLT,TF_TRAPNO(%rsp)
1309         testl   $PSL_I,TF_RFLAGS(%rsp)
1310         jz      1f
1311         sti
1312 1:
1313         movq    %rsp,%rdi
1314         call    trap
1315         movq    PCPU(CURTHREAD),%r8
1316         movq    TD_PCB(%r8),%r8
1317         movq    $0,PCB_GSBASE(%r8)
1318         jmp     doreti
1319
1320 #ifdef HWPMC_HOOKS
1321         ENTRY(end_exceptions)
1322 #endif