xref: /illumos-gate/usr/src/uts/i86pc/ml/mpcore.S (revision ddb365bfc9e868ad24ccdcb0dc91af18b10df082)
1/*
2 * CDDL HEADER START
3 *
4 * The contents of this file are subject to the terms of the
5 * Common Development and Distribution License (the "License").
6 * You may not use this file except in compliance with the License.
7 *
8 * You can obtain a copy of the license at usr/src/OPENSOLARIS.LICENSE
9 * or http://www.opensolaris.org/os/licensing.
10 * See the License for the specific language governing permissions
11 * and limitations under the License.
12 *
13 * When distributing Covered Code, include this CDDL HEADER in each
14 * file and include the License file at usr/src/OPENSOLARIS.LICENSE.
15 * If applicable, add the following below this CDDL HEADER, with the
16 * fields enclosed by brackets "[]" replaced with your own identifying
17 * information: Portions Copyright [yyyy] [name of copyright owner]
18 *
19 * CDDL HEADER END
20 */
21/*
22 * Copyright (c) 1992, 2010, Oracle and/or its affiliates. All rights reserved.
23 */
24/*
25 * Copyright (c) 2010, Intel Corporation.
26 * All rights reserved.
27 *
28 * Copyright 2019 Joyent, Inc.
29 * Copyright 2020 OmniOS Community Edition (OmniOSce) Association.
30 */
31
32#include <sys/asm_linkage.h>
33#include <sys/asm_misc.h>
34#include <sys/regset.h>
35#include <sys/privregs.h>
36#include <sys/x86_archext.h>
37
38#include <sys/segments.h>
39#include "assym.h"
40
41/*
42 *	Our assumptions:
43 *		- We are running in real mode.
44 *		- Interrupts are disabled.
45 *		- Selectors are equal (cs == ds == ss) for all real mode code
46 *		- The GDT, IDT, ktss and page directory has been built for us
47 *
48 *	Our actions:
49 *	Start CPU:
50 *		- We start using our GDT by loading correct values in the
51 *		  selector registers (cs=KCS_SEL, ds=es=ss=KDS_SEL, fs=KFS_SEL,
52 *		  gs=KGS_SEL).
53 *		- We change over to using our IDT.
54 *		- We load the default LDT into the hardware LDT register.
55 *		- We load the default TSS into the hardware task register.
56 *		- call mp_startup(void) indirectly through the T_PC
57 *	Stop CPU:
58 *		- Put CPU into halted state with interrupts disabled
59 *
60 */
61
62	ENTRY_NP(real_mode_start_cpu)
63
64	/*
65	 * NOTE:  The GNU assembler automatically does the right thing to
66	 *	  generate data size operand prefixes based on the code size
67	 *	  generation mode (e.g. .code16, .code32, .code64) and as such
68	 *	  prefixes need not be used on instructions EXCEPT in the case
69	 *	  of address prefixes for code for which the reference is not
70	 *	  automatically of the default operand size.
71	 */
72	.code16
73	cli
74	movw		%cs, %ax
75	movw		%ax, %ds	/* load cs into ds */
76	movw		%ax, %ss	/* and into ss */
77
78	/*
79	 * Helps in debugging by giving us the fault address.
80	 *
81	 * Remember to patch a hlt (0xf4) at cmntrap to get a good stack.
82	 */
83	movl		$0xffc, %esp
84	movl		%cr0, %eax
85
86	/*
87	 * Enable protected-mode, write protect, and alignment mask
88	 */
89	orl		$(CR0_PE|CR0_WP|CR0_AM), %eax
90	movl		%eax, %cr0
91
92	/*
93	 * Do a jmp immediately after writing to cr0 when enabling protected
94	 * mode to clear the real mode prefetch queue (per Intel's docs)
95	 */
96	jmp		pestart
97
98pestart:
99	/*
100	 * 16-bit protected mode is now active, so prepare to turn on long
101	 * mode.
102	 */
103
104	/*
105	 * Add any initial cr4 bits
106	 */
107	movl		%cr4, %eax
108	addr32 orl	CR4OFF, %eax
109
110	/*
111	 * Enable PAE mode (CR4.PAE)
112	 */
113	orl		$CR4_PAE, %eax
114	movl		%eax, %cr4
115
116	/*
117	 * Point cr3 to the 64-bit long mode page tables.
118	 *
119	 * Note that these MUST exist in 32-bit space, as we don't have
120	 * a way to load %cr3 with a 64-bit base address for the page tables
121	 * until the CPU is actually executing in 64-bit long mode.
122	 */
123	addr32 movl	CR3OFF, %eax
124	movl		%eax, %cr3
125
126	/*
127	 * Set long mode enable in EFER (EFER.LME = 1)
128	 */
129	movl	$MSR_AMD_EFER, %ecx
130	rdmsr
131	orl	$AMD_EFER_LME, %eax
132	wrmsr
133
134	/*
135	 * Finally, turn on paging (CR0.PG = 1) to activate long mode.
136	 */
137	movl	%cr0, %eax
138	orl	$CR0_PG, %eax
139	movl	%eax, %cr0
140
141	/*
142	 * The instruction after enabling paging in CR0 MUST be a branch.
143	 */
144	jmp	long_mode_active
145
146long_mode_active:
147	/*
148	 * Long mode is now active but since we're still running with the
149	 * original 16-bit CS we're actually in 16-bit compatability mode.
150	 *
151	 * We have to load an intermediate GDT and IDT here that we know are
152	 * in 32-bit space before we can use the kernel's GDT and IDT, which
153	 * may be in the 64-bit address space, and since we're in compatability
154	 * mode, we only have access to 16 and 32-bit instructions at the
155	 * moment.
156	 */
157	addr32 lgdtl	TEMPGDTOFF	/* load temporary GDT */
158	addr32 lidtl	TEMPIDTOFF	/* load temporary IDT */
159
160	/*
161	 * Do a far transfer to 64-bit mode.  Set the CS selector to a 64-bit
162	 * long mode selector (CS.L=1) in the temporary 32-bit GDT and jump
163	 * to the real mode platter address of long_mode 64 as until the 64-bit
164	 * CS is in place we don't have access to 64-bit instructions and thus
165	 * can't reference a 64-bit %rip.
166	 */
167	pushl		$TEMP_CS64_SEL
168	addr32 pushl	LM64OFF
169	lretl
170
171	.globl	long_mode_64
172long_mode_64:
173	.code64
174	/*
175	 * We are now running in long mode with a 64-bit CS (EFER.LMA=1,
176	 * CS.L=1) so we now have access to 64-bit instructions.
177	 *
178	 * First, set the 64-bit GDT base.
179	 */
180	.globl	rm_platter_pa
181	movl	rm_platter_pa, %eax
182	lgdtq	GDTROFF(%rax)		/* load 64-bit GDT */
183
184	/*
185	 * Save the CPU number in %r11; get the value here since it's saved in
186	 * the real mode platter.
187	 */
188	movl	CPUNOFF(%rax), %r11d
189
190	/*
191	 * Add rm_platter_pa to %rsp to point it to the same location as seen
192	 * from 64-bit mode.
193	 */
194	addq	%rax, %rsp
195
196	/*
197	 * Now do an lretq to load CS with the appropriate selector for the
198	 * kernel's 64-bit GDT and to start executing 64-bit setup code at the
199	 * virtual address where boot originally loaded this code rather than
200	 * the copy in the real mode platter's rm_code array as we've been
201	 * doing so far.
202	 */
203	pushq	$KCS_SEL
204	pushq	$kernel_cs_code
205	lretq
206	.globl real_mode_start_cpu_end
207real_mode_start_cpu_end:
208	nop
209
210kernel_cs_code:
211	/*
212	 * Complete the balance of the setup we need to before executing
213	 * 64-bit kernel code (namely init rsp, TSS, LGDT, FS and GS).
214	 */
215	.globl	rm_platter_va
216	movq	rm_platter_va, %rax
217	lidtq	IDTROFF(%rax)
218
219	movw	$KDS_SEL, %ax
220	movw	%ax, %ds
221	movw	%ax, %es
222	movw	%ax, %ss
223
224	movw	$KTSS_SEL, %ax		/* setup kernel TSS */
225	ltr	%ax
226
227	xorw	%ax, %ax		/* clear LDTR */
228	lldt	%ax
229
230	/*
231	 * Set GS to the address of the per-cpu structure as contained in
232	 * cpu[cpu_number].
233	 *
234	 * Unfortunately there's no way to set the 64-bit gsbase with a mov,
235	 * so we have to stuff the low 32 bits in %eax and the high 32 bits in
236	 * %edx, then call wrmsr.
237	 */
238	leaq	cpu(%rip), %rdi
239	movl	(%rdi, %r11, 8), %eax
240	movl	4(%rdi, %r11, 8), %edx
241	movl	$MSR_AMD_GSBASE, %ecx
242	wrmsr
243
244	/*
245	 * Init FS and KernelGSBase.
246	 *
247	 * Based on code in mlsetup(), set them both to 8G (which shouldn't be
248	 * valid until some 64-bit processes run); this will then cause an
249	 * exception in any code that tries to index off them before they are
250	 * properly setup.
251	 */
252	xorl	%eax, %eax		/* low 32 bits = 0 */
253	movl	$2, %edx		/* high 32 bits = 2 */
254	movl	$MSR_AMD_FSBASE, %ecx
255	wrmsr
256
257	movl	$MSR_AMD_KGSBASE, %ecx
258	wrmsr
259
260	/*
261	 * Init %rsp to the exception stack set in tss_ist1 and create a legal
262	 * AMD64 ABI stack frame
263	 */
264	movq	%gs:CPU_TSS, %rax
265	movq	TSS_IST1(%rax), %rsp
266	pushq	$0		/* null return address */
267	pushq	$0		/* null frame pointer terminates stack trace */
268	movq	%rsp, %rbp	/* stack aligned on 16-byte boundary */
269
270	movq	%cr0, %rax
271	andq    $~(CR0_TS|CR0_EM), %rax	/* clear emulate math chip bit */
272	orq     $(CR0_MP|CR0_NE), %rax
273	movq    %rax, %cr0		/* set machine status word */
274
275	/*
276	 * Before going any further, enable usage of page table NX bit if
277	 * that's how our page tables are set up.
278	 */
279	btl	$X86FSET_NX, x86_featureset(%rip)
280	jnc	1f
281	movl	$MSR_AMD_EFER, %ecx
282	rdmsr
283	orl	$AMD_EFER_NXE, %eax
284	wrmsr
2851:
286
287	/*
288	 * Complete the rest of the setup and call mp_startup().
289	 */
290	movq	%gs:CPU_THREAD, %rax	/* get thread ptr */
291	movq	T_PC(%rax), %rax
292	INDIRECT_CALL_REG(rax)		/* call mp_startup_boot */
293	/* not reached */
294	int	$20			/* whoops, returned somehow! */
295
296	SET_SIZE(real_mode_start_cpu)
297
298	ENTRY_NP(real_mode_stop_cpu_stage1)
299
300	/*
301	 * NOTE:  The GNU assembler automatically does the right thing to
302	 *	  generate data size operand prefixes based on the code size
303	 *	  generation mode (e.g. .code16, .code32, .code64) and as such
304	 *	  prefixes need not be used on instructions EXCEPT in the case
305	 *	  of address prefixes for code for which the reference is not
306	 *	  automatically of the default operand size.
307	 */
308	.code16
309	cli
310	movw		%cs, %ax
311	movw		%ax, %ds	/* load cs into ds */
312	movw		%ax, %ss	/* and into ss */
313
314	/*
315	 * Jump to the stage 2 code in the rm_platter_va->rm_cpu_halt_code
316	 */
317	movw		$CPUHALTCODEOFF, %ax
318	jmp		*%ax
319
320	.globl real_mode_stop_cpu_stage1_end
321real_mode_stop_cpu_stage1_end:
322	nop
323
324	SET_SIZE(real_mode_stop_cpu_stage1)
325
326	ENTRY_NP(real_mode_stop_cpu_stage2)
327
328	movw		$0xdead, %ax
329	movw		%ax, CPUHALTEDOFF
330
331real_mode_stop_cpu_loop:
332	/*
333	 * Put CPU into halted state.
334	 * Only INIT, SMI, NMI could break the loop.
335	 */
336	hlt
337	jmp		real_mode_stop_cpu_loop
338
339	.globl real_mode_stop_cpu_stage2_end
340real_mode_stop_cpu_stage2_end:
341	nop
342
343	SET_SIZE(real_mode_stop_cpu_stage2)
344