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