xref: /onnv-gate/usr/src/uts/i86pc/ml/mpcore.s (revision 13136:67d1861e02c1)
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
29#include <sys/asm_linkage.h>
30#include <sys/asm_misc.h>
31#include <sys/regset.h>
32#include <sys/privregs.h>
33#include <sys/x86_archext.h>
34
35#if !defined(__lint)
36#include <sys/segments.h>
37#include "assym.h"
38#endif
39
40/*
41 *	Our assumptions:
42 *		- We are running in real mode.
43 *		- Interrupts are disabled.
44 *		- Selectors are equal (cs == ds == ss) for all real mode code
45 *		- The GDT, IDT, ktss and page directory has been built for us
46 *
47 *	Our actions:
48 *	Start CPU:
49 *		- We start using our GDT by loading correct values in the
50 *		  selector registers (cs=KCS_SEL, ds=es=ss=KDS_SEL, fs=KFS_SEL,
51 *		  gs=KGS_SEL).
52 *		- We change over to using our IDT.
53 *		- We load the default LDT into the hardware LDT register.
54 *		- We load the default TSS into the hardware task register.
55 *		- call mp_startup(void) indirectly through the T_PC
56 *	Stop CPU:
57 *		- Put CPU into halted state with interrupts disabled
58 *
59 */
60
61#if defined(__lint)
62
63void
64real_mode_start_cpu(void)
65{}
66
67void
68real_mode_stop_cpu_stage1(void)
69{}
70
71void
72real_mode_stop_cpu_stage2(void)
73{}
74
75#else	/* __lint */
76
77#if defined(__amd64)
78
79	ENTRY_NP(real_mode_start_cpu)
80
81#if !defined(__GNUC_AS__)
82
83	/*
84	 * For vulcan as we need to do a .code32 and mentally invert the
85	 * meaning of the addr16 and data16 prefixes to get 32-bit access when
86	 * generating code to be executed in 16-bit mode (sigh...)
87	 */
88	.code32
89	cli
90	movw		%cs, %ax
91	movw		%ax, %ds	/* load cs into ds */
92	movw		%ax, %ss	/* and into ss */
93
94	/*
95	 * Helps in debugging by giving us the fault address.
96	 *
97	 * Remember to patch a hlt (0xf4) at cmntrap to get a good stack.
98	 */
99	D16 movl	$0xffc, %esp
100	movl		%cr0, %eax
101
102	/*
103	 * Enable protected-mode, write protect, and alignment mask
104	 */
105	D16 orl		$[CR0_PE|CR0_WP|CR0_AM], %eax
106	movl		%eax, %cr0
107
108	/*
109	 * Do a jmp immediately after writing to cr0 when enabling protected
110	 * mode to clear the real mode prefetch queue (per Intel's docs)
111	 */
112	jmp		pestart
113
114pestart:
115	/*
116 	 * 16-bit protected mode is now active, so prepare to turn on long
117	 * mode.
118	 *
119	 * Note that we currently assume that if we're attempting to run a
120	 * kernel compiled with (__amd64) #defined, the target CPU has long
121	 * mode support.
122	 */
123
124#if 0
125	/*
126	 * If there's a chance this might not be true, the following test should
127	 * be done, with the no_long_mode branch then doing something
128	 * appropriate:
129	 */
130
131	D16 movl	$0x80000000, %eax	/* get largest extended CPUID */
132	cpuid
133	D16 cmpl	$0x80000000, %eax	/* check if > 0x80000000 */
134	jbe		no_long_mode		/* nope, no long mode */
135	D16 movl	$0x80000001, %eax
136	cpuid					/* get extended feature flags */
137	btl		$29, %edx		/* check for long mode */
138	jnc		no_long_mode		/* long mode not supported */
139#endif
140
141	/*
142 	 * Add any initial cr4 bits
143	 */
144	movl		%cr4, %eax
145	A16 D16 orl	CR4OFF, %eax
146
147	/*
148	 * Enable PAE mode (CR4.PAE)
149	 */
150	D16 orl		$CR4_PAE, %eax
151	movl		%eax, %cr4
152
153	/*
154	 * Point cr3 to the 64-bit long mode page tables.
155	 *
156	 * Note that these MUST exist in 32-bit space, as we don't have
157	 * a way to load %cr3 with a 64-bit base address for the page tables
158	 * until the CPU is actually executing in 64-bit long mode.
159	 */
160	A16 D16 movl	CR3OFF, %eax
161	movl		%eax, %cr3
162
163	/*
164	 * Set long mode enable in EFER (EFER.LME = 1)
165	 */
166	D16 movl	$MSR_AMD_EFER, %ecx
167	rdmsr
168	D16 orl		$AMD_EFER_LME, %eax
169	wrmsr
170
171	/*
172	 * Finally, turn on paging (CR0.PG = 1) to activate long mode.
173	 */
174	movl		%cr0, %eax
175	D16 orl		$CR0_PG, %eax
176	movl		%eax, %cr0
177
178	/*
179	 * The instruction after enabling paging in CR0 MUST be a branch.
180	 */
181	jmp		long_mode_active
182
183long_mode_active:
184	/*
185	 * Long mode is now active but since we're still running with the
186	 * original 16-bit CS we're actually in 16-bit compatability mode.
187	 *
188	 * We have to load an intermediate GDT and IDT here that we know are
189	 * in 32-bit space before we can use the kernel's GDT and IDT, which
190	 * may be in the 64-bit address space, and since we're in compatability
191	 * mode, we only have access to 16 and 32-bit instructions at the
192	 * moment.
193	 */
194	A16 D16 lgdt	TEMPGDTOFF	/* load temporary GDT */
195	A16 D16 lidt	TEMPIDTOFF	/* load temporary IDT */
196
197	/*
198 	 * Do a far transfer to 64-bit mode.  Set the CS selector to a 64-bit
199	 * long mode selector (CS.L=1) in the temporary 32-bit GDT and jump
200	 * to the real mode platter address of long_mode 64 as until the 64-bit
201	 * CS is in place we don't have access to 64-bit instructions and thus
202	 * can't reference a 64-bit %rip.
203	 */
204	D16 	pushl 	$TEMP_CS64_SEL
205	A16 D16 pushl	LM64OFF
206	D16 lret
207
208	.globl	long_mode_64
209long_mode_64:
210	.code64
211	/*
212	 * We are now running in long mode with a 64-bit CS (EFER.LMA=1,
213	 * CS.L=1) so we now have access to 64-bit instructions.
214	 *
215	 * First, set the 64-bit GDT base.
216	 */
217	.globl	rm_platter_pa
218	movl	rm_platter_pa, %eax
219
220	lgdtq	GDTROFF(%rax)		/* load 64-bit GDT */
221
222	/*
223	 * Save the CPU number in %r11; get the value here since it's saved in
224	 * the real mode platter.
225	 */
226	movl	CPUNOFF(%rax), %r11d
227
228	/*
229	 * Add rm_platter_pa to %rsp to point it to the same location as seen
230	 * from 64-bit mode.
231	 */
232	addq	%rax, %rsp
233
234	/*
235	 * Now do an lretq to load CS with the appropriate selector for the
236	 * kernel's 64-bit GDT and to start executing 64-bit setup code at the
237	 * virtual address where boot originally loaded this code rather than
238	 * the copy in the real mode platter's rm_code array as we've been
239	 * doing so far.
240	 */
241	pushq	$KCS_SEL
242	pushq	$kernel_cs_code
243	lretq
244	.globl real_mode_start_cpu_end
245real_mode_start_cpu_end:
246	nop
247
248kernel_cs_code:
249	/*
250	 * Complete the balance of the setup we need to before executing
251	 * 64-bit kernel code (namely init rsp, TSS, LGDT, FS and GS).
252	 */
253	.globl	rm_platter_va
254	movq	rm_platter_va, %rax
255
256	lidtq	IDTROFF(%rax)
257
258	movw	$KDS_SEL, %ax
259	movw	%ax, %ds
260	movw	%ax, %es
261	movw	%ax, %ss
262
263	movw	$KTSS_SEL, %ax		/* setup kernel TSS */
264	ltr	%ax
265
266	xorw	%ax, %ax		/* clear LDTR */
267	lldt	%ax
268
269	/*
270	 * Set GS to the address of the per-cpu structure as contained in
271	 * cpu[cpu_number].
272	 *
273	 * Unfortunately there's no way to set the 64-bit gsbase with a mov,
274	 * so we have to stuff the low 32 bits in %eax and the high 32 bits in
275	 * %edx, then call wrmsr.
276	 */
277	leaq	cpu(%rip), %rdi
278	movl	(%rdi, %r11, 8), %eax
279	movl	4(%rdi, %r11, 8), %edx
280	movl	$MSR_AMD_GSBASE, %ecx
281	wrmsr
282
283	/*
284	 * Init FS and KernelGSBase.
285	 *
286	 * Based on code in mlsetup(), set them both to 8G (which shouldn't be
287	 * valid until some 64-bit processes run); this will then cause an
288	 * exception in any code that tries to index off them before they are
289	 * properly setup.
290	 */
291	xorl	%eax, %eax		/* low 32 bits = 0 */
292	movl	$2, %edx		/* high 32 bits = 2 */
293	movl	$MSR_AMD_FSBASE, %ecx
294	wrmsr
295
296	movl	$MSR_AMD_KGSBASE, %ecx
297	wrmsr
298
299	/*
300	 * Init %rsp to the exception stack set in tss_ist1 and create a legal
301	 * AMD64 ABI stack frame
302	 */
303	movq	%gs:CPU_TSS, %rax
304	movq	TSS_IST1(%rax), %rsp
305	pushq	$0		/* null return address */
306	pushq	$0		/* null frame pointer terminates stack trace */
307	movq	%rsp, %rbp	/* stack aligned on 16-byte boundary */
308
309	movq	%cr0, %rax
310	andq    $-1![CR0_TS|CR0_EM], %rax	/* clr emulate math chip bit */
311	orq     $[CR0_MP|CR0_NE], %rax
312	movq    %rax, %cr0			/* set machine status word */
313
314	/*
315	 * Before going any further, enable usage of page table NX bit if
316	 * that's how our page tables are set up.
317	 */
318	bt	$X86FSET_NX, x86_featureset(%rip)
319	jnc	1f
320	movl	$MSR_AMD_EFER, %ecx
321	rdmsr
322	orl	$AMD_EFER_NXE, %eax
323	wrmsr
3241:
325
326	/*
327	 * Complete the rest of the setup and call mp_startup().
328	 */
329	movq	%gs:CPU_THREAD, %rax	/* get thread ptr */
330	call	*T_PC(%rax)		/* call mp_startup */
331	/* not reached */
332	int	$20			/* whoops, returned somehow! */
333#else	/* __GNUC_AS__ */
334
335	/*
336	 * NOTE:  The GNU assembler automatically does the right thing to
337	 *	  generate data size operand prefixes based on the code size
338	 *	  generation mode (e.g. .code16, .code32, .code64) and as such
339	 *	  prefixes need not be used on instructions EXCEPT in the case
340	 *	  of address prefixes for code for which the reference is not
341	 *	  automatically of the default operand size.
342	 */
343	.code16
344	cli
345	movw		%cs, %ax
346	movw		%ax, %ds	/* load cs into ds */
347	movw		%ax, %ss	/* and into ss */
348
349	/*
350	 * Helps in debugging by giving us the fault address.
351	 *
352	 * Remember to patch a hlt (0xf4) at cmntrap to get a good stack.
353	 */
354	movl		$0xffc, %esp
355	movl		%cr0, %eax
356
357	/*
358	 * Enable protected-mode, write protect, and alignment mask
359	 */
360	orl		$(CR0_PE|CR0_WP|CR0_AM), %eax
361	movl		%eax, %cr0
362
363	/*
364	 * Do a jmp immediately after writing to cr0 when enabling protected
365	 * mode to clear the real mode prefetch queue (per Intel's docs)
366	 */
367	jmp		pestart
368
369pestart:
370	/*
371 	 * 16-bit protected mode is now active, so prepare to turn on long
372	 * mode.
373	 *
374	 * Note that we currently assume that if we're attempting to run a
375	 * kernel compiled with (__amd64) #defined, the target CPU has long
376	 * mode support.
377	 */
378
379#if 0
380	/*
381	 * If there's a chance this might not be true, the following test should
382	 * be done, with the no_long_mode branch then doing something
383	 * appropriate:
384	 */
385
386	movl		$0x80000000, %eax	/* get largest extended CPUID */
387	cpuid
388	cmpl		$0x80000000, %eax	/* check if > 0x80000000 */
389	jbe		no_long_mode		/* nope, no long mode */
390	movl		$0x80000001, %eax
391	cpuid					/* get extended feature flags */
392	btl		$29, %edx		/* check for long mode */
393	jnc		no_long_mode		/* long mode not supported */
394#endif
395
396	/*
397 	 * Add any initial cr4 bits
398	 */
399	movl		%cr4, %eax
400	addr32 orl	CR4OFF, %eax
401
402	/*
403	 * Enable PAE mode (CR4.PAE)
404	 */
405	orl		$CR4_PAE, %eax
406	movl		%eax, %cr4
407
408	/*
409	 * Point cr3 to the 64-bit long mode page tables.
410	 *
411	 * Note that these MUST exist in 32-bit space, as we don't have
412	 * a way to load %cr3 with a 64-bit base address for the page tables
413	 * until the CPU is actually executing in 64-bit long mode.
414	 */
415	addr32 movl	CR3OFF, %eax
416	movl		%eax, %cr3
417
418	/*
419	 * Set long mode enable in EFER (EFER.LME = 1)
420	 */
421	movl	$MSR_AMD_EFER, %ecx
422	rdmsr
423	orl	$AMD_EFER_LME, %eax
424	wrmsr
425
426	/*
427	 * Finally, turn on paging (CR0.PG = 1) to activate long mode.
428	 */
429	movl	%cr0, %eax
430	orl	$CR0_PG, %eax
431	movl	%eax, %cr0
432
433	/*
434	 * The instruction after enabling paging in CR0 MUST be a branch.
435	 */
436	jmp	long_mode_active
437
438long_mode_active:
439	/*
440	 * Long mode is now active but since we're still running with the
441	 * original 16-bit CS we're actually in 16-bit compatability mode.
442	 *
443	 * We have to load an intermediate GDT and IDT here that we know are
444	 * in 32-bit space before we can use the kernel's GDT and IDT, which
445	 * may be in the 64-bit address space, and since we're in compatability
446	 * mode, we only have access to 16 and 32-bit instructions at the
447	 * moment.
448	 */
449	addr32 lgdtl	TEMPGDTOFF	/* load temporary GDT */
450	addr32 lidtl	TEMPIDTOFF	/* load temporary IDT */
451
452	/*
453 	 * Do a far transfer to 64-bit mode.  Set the CS selector to a 64-bit
454	 * long mode selector (CS.L=1) in the temporary 32-bit GDT and jump
455	 * to the real mode platter address of long_mode 64 as until the 64-bit
456	 * CS is in place we don't have access to 64-bit instructions and thus
457	 * can't reference a 64-bit %rip.
458	 */
459	pushl 		$TEMP_CS64_SEL
460	addr32 pushl	LM64OFF
461	lretl
462
463	.globl	long_mode_64
464long_mode_64:
465	.code64
466	/*
467	 * We are now running in long mode with a 64-bit CS (EFER.LMA=1,
468	 * CS.L=1) so we now have access to 64-bit instructions.
469	 *
470	 * First, set the 64-bit GDT base.
471	 */
472	.globl	rm_platter_pa
473	movl	rm_platter_pa, %eax
474	lgdtq	GDTROFF(%rax)		/* load 64-bit GDT */
475
476	/*
477	 * Save the CPU number in %r11; get the value here since it's saved in
478	 * the real mode platter.
479	 */
480	movl	CPUNOFF(%rax), %r11d
481
482	/*
483	 * Add rm_platter_pa to %rsp to point it to the same location as seen
484	 * from 64-bit mode.
485	 */
486	addq	%rax, %rsp
487
488	/*
489	 * Now do an lretq to load CS with the appropriate selector for the
490	 * kernel's 64-bit GDT and to start executing 64-bit setup code at the
491	 * virtual address where boot originally loaded this code rather than
492	 * the copy in the real mode platter's rm_code array as we've been
493	 * doing so far.
494	 */
495	pushq	$KCS_SEL
496	pushq	$kernel_cs_code
497	lretq
498	.globl real_mode_start_cpu_end
499real_mode_start_cpu_end:
500	nop
501
502kernel_cs_code:
503	/*
504	 * Complete the balance of the setup we need to before executing
505	 * 64-bit kernel code (namely init rsp, TSS, LGDT, FS and GS).
506	 */
507	.globl	rm_platter_va
508	movq	rm_platter_va, %rax
509	lidtq	IDTROFF(%rax)
510
511	movw	$KDS_SEL, %ax
512	movw	%ax, %ds
513	movw	%ax, %es
514	movw	%ax, %ss
515
516	movw	$KTSS_SEL, %ax		/* setup kernel TSS */
517	ltr	%ax
518
519	xorw	%ax, %ax		/* clear LDTR */
520	lldt	%ax
521
522	/*
523	 * Set GS to the address of the per-cpu structure as contained in
524	 * cpu[cpu_number].
525	 *
526	 * Unfortunately there's no way to set the 64-bit gsbase with a mov,
527	 * so we have to stuff the low 32 bits in %eax and the high 32 bits in
528	 * %edx, then call wrmsr.
529	 */
530	leaq	cpu(%rip), %rdi
531	movl	(%rdi, %r11, 8), %eax
532	movl	4(%rdi, %r11, 8), %edx
533	movl	$MSR_AMD_GSBASE, %ecx
534	wrmsr
535
536	/*
537	 * Init FS and KernelGSBase.
538	 *
539	 * Based on code in mlsetup(), set them both to 8G (which shouldn't be
540	 * valid until some 64-bit processes run); this will then cause an
541	 * exception in any code that tries to index off them before they are
542	 * properly setup.
543	 */
544	xorl	%eax, %eax		/* low 32 bits = 0 */
545	movl	$2, %edx		/* high 32 bits = 2 */
546	movl	$MSR_AMD_FSBASE, %ecx
547	wrmsr
548
549	movl	$MSR_AMD_KGSBASE, %ecx
550	wrmsr
551
552	/*
553	 * Init %rsp to the exception stack set in tss_ist1 and create a legal
554	 * AMD64 ABI stack frame
555	 */
556	movq	%gs:CPU_TSS, %rax
557	movq	TSS_IST1(%rax), %rsp
558	pushq	$0		/* null return address */
559	pushq	$0		/* null frame pointer terminates stack trace */
560	movq	%rsp, %rbp	/* stack aligned on 16-byte boundary */
561
562	movq	%cr0, %rax
563	andq    $~(CR0_TS|CR0_EM), %rax	/* clear emulate math chip bit */
564	orq     $(CR0_MP|CR0_NE), %rax
565	movq    %rax, %cr0		/* set machine status word */
566
567	/*
568	 * Before going any further, enable usage of page table NX bit if
569	 * that's how our page tables are set up.
570	 */
571	bt	$X86FSET_NX, x86_featureset(%rip)
572	jnc	1f
573	movl	$MSR_AMD_EFER, %ecx
574	rdmsr
575	orl	$AMD_EFER_NXE, %eax
576	wrmsr
5771:
578
579	/*
580	 * Complete the rest of the setup and call mp_startup().
581	 */
582	movq	%gs:CPU_THREAD, %rax	/* get thread ptr */
583	call	*T_PC(%rax)		/* call mp_startup */
584	/* not reached */
585	int	$20			/* whoops, returned somehow! */
586#endif	/* !__GNUC_AS__ */
587
588	SET_SIZE(real_mode_start_cpu)
589
590#elif defined(__i386)
591
592	ENTRY_NP(real_mode_start_cpu)
593
594#if !defined(__GNUC_AS__)
595
596	cli
597	D16 movw	%cs, %eax
598	movw		%eax, %ds	/* load cs into ds */
599	movw		%eax, %ss	/* and into ss */
600
601	/*
602	 * Helps in debugging by giving us the fault address.
603	 *
604	 * Remember to patch a hlt (0xf4) at cmntrap to get a good stack.
605	 */
606	D16 movl	$0xffc, %esp
607
608 	D16 A16 lgdt	%cs:GDTROFF
609 	D16 A16 lidt	%cs:IDTROFF
610	D16 A16 movl	%cs:CR4OFF, %eax	/* set up CR4, if desired */
611	D16 andl	%eax, %eax
612	D16 A16 je	no_cr4
613
614	D16 movl	%eax, %ecx
615	D16 movl	%cr4, %eax
616	D16 orl		%ecx, %eax
617	D16 movl	%eax, %cr4
618no_cr4:
619	D16 A16 movl	%cs:CR3OFF, %eax
620	A16 movl	%eax, %cr3
621	movl		%cr0, %eax
622
623	/*
624	 * Enable protected-mode, paging, write protect, and alignment mask
625	 */
626	D16 orl		$[CR0_PG|CR0_PE|CR0_WP|CR0_AM], %eax
627	movl		%eax, %cr0
628	jmp		pestart
629
630pestart:
631	D16 pushl	$KCS_SEL
632	D16 pushl	$kernel_cs_code
633	D16 lret
634	.globl real_mode_start_cpu_end
635real_mode_start_cpu_end:
636	nop
637
638	.globl	kernel_cs_code
639kernel_cs_code:
640	/*
641	 * At this point we are with kernel's cs and proper eip.
642	 *
643	 * We will be executing not from the copy in real mode platter,
644	 * but from the original code where boot loaded us.
645	 *
646	 * By this time GDT and IDT are loaded as is cr3.
647	 */
648	movw	$KFS_SEL,%eax
649	movw	%eax,%fs
650	movw	$KGS_SEL,%eax
651	movw	%eax,%gs
652	movw	$KDS_SEL,%eax
653	movw	%eax,%ds
654	movw	%eax,%es
655	movl	%gs:CPU_TSS,%esi
656	movw	%eax,%ss
657	movl	TSS_ESP0(%esi),%esp
658	movw	$KTSS_SEL,%ax
659	ltr	%ax
660	xorw	%ax, %ax		/* clear LDTR */
661	lldt	%ax
662	movl	%cr0,%edx
663	andl    $-1![CR0_TS|CR0_EM],%edx  /* clear emulate math chip bit */
664	orl     $[CR0_MP|CR0_NE],%edx
665	movl    %edx,%cr0		  /* set machine status word */
666
667	/*
668	 * Before going any further, enable usage of page table NX bit if
669	 * that's how our page tables are set up.
670	 */
671	bt	$X86FSET_NX, x86_featureset
672	jnc	1f
673	movl	%cr4, %ecx
674	andl	$CR4_PAE, %ecx
675	jz	1f
676	movl	$MSR_AMD_EFER, %ecx
677	rdmsr
678	orl	$AMD_EFER_NXE, %eax
679	wrmsr
6801:
681	movl	%gs:CPU_THREAD, %eax	/* get thread ptr */
682	call	*T_PC(%eax)		/* call mp_startup */
683	/* not reached */
684	int	$20			/* whoops, returned somehow! */
685
686#else
687
688	cli
689	mov		%cs, %ax
690	mov		%eax, %ds	/* load cs into ds */
691	mov		%eax, %ss	/* and into ss */
692
693	/*
694	 * Helps in debugging by giving us the fault address.
695	 *
696	 * Remember to patch a hlt (0xf4) at cmntrap to get a good stack.
697	 */
698	D16 mov		$0xffc, %esp
699
700	D16 A16 lgdtl	%cs:GDTROFF
701	D16 A16 lidtl	%cs:IDTROFF
702	D16 A16 mov	%cs:CR4OFF, %eax	/* set up CR4, if desired */
703	D16 and		%eax, %eax
704	D16 A16 je	no_cr4
705
706	D16 mov		%eax, %ecx
707	D16 mov		%cr4, %eax
708	D16 or		%ecx, %eax
709	D16 mov		%eax, %cr4
710no_cr4:
711	D16 A16 mov	%cs:CR3OFF, %eax
712	A16 mov		%eax, %cr3
713	mov		%cr0, %eax
714
715	/*
716	 * Enable protected-mode, paging, write protect, and alignment mask
717	 */
718	D16 or		$(CR0_PG|CR0_PE|CR0_WP|CR0_AM), %eax
719	mov		%eax, %cr0
720	jmp		pestart
721
722pestart:
723	D16 pushl	$KCS_SEL
724	D16 pushl	$kernel_cs_code
725	D16 lret
726	.globl real_mode_start_cpu_end
727real_mode_start_cpu_end:
728	nop
729	.globl	kernel_cs_code
730kernel_cs_code:
731	/*
732	 * At this point we are with kernel's cs and proper eip.
733	 *
734	 * We will be executing not from the copy in real mode platter,
735	 * but from the original code where boot loaded us.
736	 *
737	 * By this time GDT and IDT are loaded as is cr3.
738	 */
739	mov	$KFS_SEL, %ax
740	mov	%eax, %fs
741	mov	$KGS_SEL, %ax
742	mov	%eax, %gs
743	mov	$KDS_SEL, %ax
744	mov	%eax, %ds
745	mov	%eax, %es
746	mov	%gs:CPU_TSS, %esi
747	mov	%eax, %ss
748	mov	TSS_ESP0(%esi), %esp
749	mov	$(KTSS_SEL), %ax
750	ltr	%ax
751	xorw	%ax, %ax		/* clear LDTR */
752	lldt	%ax
753	mov	%cr0, %edx
754	and	$~(CR0_TS|CR0_EM), %edx	/* clear emulate math chip bit */
755	or	$(CR0_MP|CR0_NE), %edx
756	mov	%edx, %cr0		/* set machine status word */
757
758	/*
759	 * Before going any farther, enable usage of page table NX bit if
760	 * that's how our page tables are set up.
761	 */
762	bt	$X86FSET_NX, x86_featureset
763	jnc	1f
764	movl	%cr4, %ecx
765	andl	$CR4_PAE, %ecx
766	jz	1f
767	movl	$MSR_AMD_EFER, %ecx
768	rdmsr
769	orl	$AMD_EFER_NXE, %eax
770	wrmsr
7711:
772	mov	%gs:CPU_THREAD, %eax	/* get thread ptr */
773	call	*T_PC(%eax)		/* call mp_startup */
774	/* not reached */
775	int	$20			/* whoops, returned somehow! */
776#endif
777
778	SET_SIZE(real_mode_start_cpu)
779
780#endif	/* __amd64 */
781
782#if defined(__amd64)
783
784	ENTRY_NP(real_mode_stop_cpu_stage1)
785
786#if !defined(__GNUC_AS__)
787
788	/*
789	 * For vulcan as we need to do a .code32 and mentally invert the
790	 * meaning of the addr16 and data16 prefixes to get 32-bit access when
791	 * generating code to be executed in 16-bit mode (sigh...)
792	 */
793	.code32
794	cli
795	movw		%cs, %ax
796	movw		%ax, %ds	/* load cs into ds */
797	movw		%ax, %ss	/* and into ss */
798
799	/*
800	 * Jump to the stage 2 code in the rm_platter_va->rm_cpu_halt_code
801	 */
802	movw		$CPUHALTCODEOFF, %ax
803	.byte		0xff, 0xe0	/* jmp *%ax */
804
805#else	/* __GNUC_AS__ */
806
807	/*
808	 * NOTE:  The GNU assembler automatically does the right thing to
809	 *	  generate data size operand prefixes based on the code size
810	 *	  generation mode (e.g. .code16, .code32, .code64) and as such
811	 *	  prefixes need not be used on instructions EXCEPT in the case
812	 *	  of address prefixes for code for which the reference is not
813	 *	  automatically of the default operand size.
814	 */
815	.code16
816	cli
817	movw		%cs, %ax
818	movw		%ax, %ds	/* load cs into ds */
819	movw		%ax, %ss	/* and into ss */
820
821	/*
822	 * Jump to the stage 2 code in the rm_platter_va->rm_cpu_halt_code
823	 */
824	movw		$CPUHALTCODEOFF, %ax
825	jmp		*%ax
826
827#endif	/* !__GNUC_AS__ */
828
829	.globl real_mode_stop_cpu_stage1_end
830real_mode_stop_cpu_stage1_end:
831	nop
832
833	SET_SIZE(real_mode_stop_cpu_stage1)
834
835#elif defined(__i386)
836
837	ENTRY_NP(real_mode_stop_cpu_stage1)
838
839#if !defined(__GNUC_AS__)
840
841	cli
842	D16 movw	%cs, %eax
843	movw		%eax, %ds	/* load cs into ds */
844	movw		%eax, %ss	/* and into ss */
845
846	/*
847	 * Jump to the stage 2 code in the rm_platter_va->rm_cpu_halt_code
848	 */
849	movw		$CPUHALTCODEOFF, %ax
850	.byte		0xff, 0xe0	/* jmp *%ax */
851
852#else	/* __GNUC_AS__ */
853
854	cli
855	mov		%cs, %ax
856	mov		%eax, %ds	/* load cs into ds */
857	mov		%eax, %ss	/* and into ss */
858
859	/*
860	 * Jump to the stage 2 code in the rm_platter_va->rm_cpu_halt_code
861	 */
862	movw		$CPUHALTCODEOFF, %ax
863	jmp		*%ax
864
865#endif	/* !__GNUC_AS__ */
866
867	.globl real_mode_stop_cpu_stage1_end
868real_mode_stop_cpu_stage1_end:
869	nop
870
871	SET_SIZE(real_mode_stop_cpu_stage1)
872
873#endif	/* __amd64 */
874
875	ENTRY_NP(real_mode_stop_cpu_stage2)
876
877	movw		$0xdead, %ax
878	movw		%ax, CPUHALTEDOFF
879
880real_mode_stop_cpu_loop:
881	/*
882	 * Put CPU into halted state.
883	 * Only INIT, SMI, NMI could break the loop.
884	 */
885	hlt
886	jmp		real_mode_stop_cpu_loop
887
888	.globl real_mode_stop_cpu_stage2_end
889real_mode_stop_cpu_stage2_end:
890	nop
891
892	SET_SIZE(real_mode_stop_cpu_stage2)
893
894#endif	/* __lint */
895