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