locore.s revision 134
1/*-
2 * Copyright (c) 1990 The Regents of the University of California.
3 * All rights reserved.
4 *
5 * This code is derived from software contributed to Berkeley by
6 * William Jolitz.
7 *
8 * Redistribution and use in source and binary forms, with or without
9 * modification, are permitted provided that the following conditions
10 * are met:
11 * 1. Redistributions of source code must retain the above copyright
12 *    notice, this list of conditions and the following disclaimer.
13 * 2. Redistributions in binary form must reproduce the above copyright
14 *    notice, this list of conditions and the following disclaimer in the
15 *    documentation and/or other materials provided with the distribution.
16 * 3. All advertising materials mentioning features or use of this software
17 *    must display the following acknowledgement:
18 *	This product includes software developed by the University of
19 *	California, Berkeley and its contributors.
20 * 4. Neither the name of the University nor the names of its contributors
21 *    may be used to endorse or promote products derived from this software
22 *    without specific prior written permission.
23 *
24 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
25 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
26 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
27 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
28 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
29 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
30 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
31 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
32 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
33 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
34 * SUCH DAMAGE.
35 *
36 *	@(#)locore.s	7.3 (Berkeley) 5/13/91
37 *
38 * PATCHES MAGIC                LEVEL   PATCH THAT GOT US HERE
39 * --------------------         -----   ----------------------
40 * CURRENT PATCH LEVEL:         5       00158
41 * --------------------         -----   ----------------------
42 *
43 * 06 Aug 92	Pace Willisson		Allow VGA memory to be mapped
44 * 28 Nov 92	Frank MacLachlan	Aligned addresses and data
45 *					on 32bit boundaries.
46 * 25 Mar 93	Kevin Lahey		Add syscall counter for vmstat
47 * 20 Apr 93	Bruce Evans		New npx-0.5 code
48 * 25 Apr 93	Bruce Evans		Support new interrupt code (intr-0.1)
49 */
50
51
52/*
53 * locore.s:	4BSD machine support for the Intel 386
54 *		Preliminary version
55 *		Written by William F. Jolitz, 386BSD Project
56 */
57
58#include "assym.s"
59#include "machine/psl.h"
60#include "machine/pte.h"
61
62#include "errno.h"
63
64#include "machine/trap.h"
65
66#include "machine/specialreg.h"
67#include "i386/isa/debug.h"
68
69#define	KDSEL		0x10
70#define	SEL_RPL_MASK	0x0003
71#define	TRAPF_CS_OFF	(13 * 4)
72
73/*
74 * Note: This version greatly munged to avoid various assembler errors
75 * that may be fixed in newer versions of gas. Perhaps newer versions
76 * will have more pleasant appearance.
77 */
78
79	.set	IDXSHIFT,10
80	.set	SYSTEM,0xFE000000	# virtual address of system start
81	/*note: gas copys sign bit (e.g. arithmetic >>), can't do SYSTEM>>22! */
82	.set	SYSPDROFF,0x3F8		# Page dir index of System Base
83
84
85/*
86 * Macros
87 */
88#define	ALIGN_DATA	.align	2
89#define	ALIGN_TEXT	.align	2,0x90	/* 4-byte boundaries, NOP-filled */
90#define	SUPERALIGN_TEXT	.align	4,0x90	/* 16-byte boundaries better for 486 */
91
92#define	LENTRY(name)		ALIGN_TEXT; .globl name; name:
93#define	ENTRY(name)		ALIGN_TEXT; .globl _/**/name; _/**/name:
94#define	ALTENTRY(name)		.globl _/**/name; _/**/name:
95
96/* NB: NOP now preserves registers so NOPs can be inserted anywhere */
97/* XXX: NOP and FASTER_NOP are misleadingly named */
98#ifdef BROKEN_HARDWARE_AND_OR_SOFTWARE /* XXX - rarely necessary */
99#define	FASTER_NOP	pushl %eax ; inb $0x84,%al ; popl %eax
100#define	NOP	pushl %eax ; inb $0x84,%al ; inb $0x84,%al ; popl %eax
101#else
102#define	FASTER_NOP
103#define	NOP
104#endif
105
106/*
107 * PTmap is recursive pagemap at top of virtual address space.
108 * Within PTmap, the page directory can be found (third indirection).
109 */
110	.set	PDRPDROFF,0x3F7		# Page dir index of Page dir
111	.globl	_PTmap, _PTD, _PTDpde, _Sysmap
112	.set	_PTmap,0xFDC00000
113	.set	_PTD,0xFDFF7000
114	.set	_Sysmap,0xFDFF8000
115	.set	_PTDpde,0xFDFF7000+4*PDRPDROFF
116
117/*
118 * APTmap, APTD is the alternate recursive pagemap.
119 * It's used when modifying another process's page tables.
120 */
121	.set	APDRPDROFF,0x3FE		# Page dir index of Page dir
122	.globl	_APTmap, _APTD, _APTDpde
123	.set	_APTmap,0xFF800000
124	.set	_APTD,0xFFBFE000
125	.set	_APTDpde,0xFDFF7000+4*APDRPDROFF
126
127/*
128 * Access to each processes kernel stack is via a region of
129 * per-process address space (at the beginning), immediatly above
130 * the user process stack.
131 */
132	.globl	_kstack
133	.set	_kstack, USRSTACK
134	.set	PPDROFF,0x3F6
135	.set	PPTEOFF,0x400-UPAGES	# 0x3FE
136
137
138/*****************************************************************************/
139/* Globals                                                                   */
140/*****************************************************************************/
141
142	.data
143	.globl	_boothowto, _bootdev, _curpcb
144	.globl	__ucodesel,__udatasel
145
146	.globl	_cpu, _cold, _atdevbase, _atdevphys
147_cpu:	.long	0		# are we 386, 386sx, or 486
148_cold:	.long	1		# cold till we are not
149_atdevbase:	.long	0	# location of start of iomem in virtual
150_atdevphys:	.long	0	# location of device mapping ptes (phys)
151
152	.globl	_IdlePTD, _KPTphys
153_IdlePTD:	.long	0
154_KPTphys:	.long	0
155
156	.globl	_cyloffset, _proc0paddr
157_cyloffset:	.long	0
158_proc0paddr:	.long	0
159
160#ifdef SHOW_A_LOT
161bit_colors:	.byte	GREEN,RED,0,0
162#endif
163
164	.space 512
165tmpstk:
166
167
168	.text
169/*****************************************************************************/
170/* System Initialisation                                                     */
171/*****************************************************************************/
172
173/*
174 * start: jumped to directly from the boot blocks
175 */
176LENTRY(start)
177	movw	$0x1234,%ax
178	movw	%ax,0x472	# warm boot
179	jmp	1f
180	.space	0x500		# skip over warm boot shit
181
182	/*
183	 * pass parameters on stack (howto, bootdev, unit, cyloffset)
184	 * note: (%esp) is return address of boot
185	 * ( if we want to hold onto /boot, it's physical %esp up to _end)
186	 */
187
188 1:	movl	4(%esp),%eax
189	movl	%eax,_boothowto-SYSTEM
190	movl	8(%esp),%eax
191	movl	%eax,_bootdev-SYSTEM
192	movl	12(%esp),%eax
193	movl	%eax, _cyloffset-SYSTEM
194
195	/*
196	 * Finished with old stack; load new %esp now instead of later so
197	 * we can trace this code without having to worry about the trace
198	 * trap clobbering the memory test or the zeroing of the bss+bootstrap
199	 * page tables.
200	 *
201	 * XXX - wdboot clears the bss after testing that this is safe.
202	 * This is too wasteful - memory below 640K is scarce.  The boot
203	 * program should check:
204	 *	text+data <= &stack_variable - more_space_for_stack
205	 *	text+data+bss+pad+space_for_page_tables <= end_of_memory
206	 * Oops, the gdt is in the carcass of the boot program so clearing
207	 * the rest of memory is still not possible.
208	 */
209	movl	$ tmpstk-SYSTEM,%esp	# bootstrap stack end location
210
211#ifdef garbage
212	/* count up memory */
213
214	xorl	%eax,%eax		# start with base memory at 0x0
215	#movl	$ 0xA0000/NBPG,%ecx	# look every 4K up to 640K
216	movl	$ 0xA0,%ecx		# look every 4K up to 640K
2171:	movl	(%eax),%ebx		# save location to check
218	movl	$0xa55a5aa5,(%eax)	# write test pattern
219	/* flush stupid cache here! (with bcopy (0,0,512*1024) ) */
220	cmpl	$0xa55a5aa5,(%eax)	# does not check yet for rollover
221	jne	2f
222	movl	%ebx,(%eax)		# restore memory
223	addl	$ NBPG,%eax
224	loop	1b
2252:	shrl	$12,%eax
226	movl	%eax,_Maxmem-SYSTEM
227
228	movl	$0x100000,%eax		# next, talley remaining memory
229	#movl	$((0xFFF000-0x100000)/NBPG),%ecx
230	movl	$(0xFFF-0x100),%ecx
2311:	movl	(%eax),%ebx		# save location to check
232	movl	$0xa55a5aa5,(%eax)	# write test pattern
233	cmpl	$0xa55a5aa5,(%eax)	# does not check yet for rollover
234	jne	2f
235	movl	%ebx,(%eax)		# restore memory
236	addl	$ NBPG,%eax
237	loop	1b
2382:	shrl	$12,%eax
239	movl	%eax,_Maxmem-SYSTEM
240#endif
241
242/* find end of kernel image */
243	movl	$_end-SYSTEM,%ecx
244	addl	$ NBPG-1,%ecx
245	andl	$~(NBPG-1),%ecx
246	movl	%ecx,%esi
247
248/* clear bss and memory for bootstrap pagetables. */
249	movl	$_edata-SYSTEM,%edi
250	subl	%edi,%ecx
251	addl	$(UPAGES+5)*NBPG,%ecx
252/*
253 * Virtual address space of kernel:
254 *
255 *	text | data | bss | page dir | proc0 kernel stack | usr stk map | Sysmap
256 *			     0               1       2       3             4
257 */
258	xorl	%eax,%eax	# pattern
259	cld
260	rep
261	stosb
262
263	movl	%esi,_IdlePTD-SYSTEM /*physical address of Idle Address space */
264
265#define	fillkpt		\
2661:	movl	%eax,(%ebx)	; \
267	addl	$ NBPG,%eax	; /* increment physical address */ \
268	addl	$4,%ebx		; /* next pte */ \
269	loop	1b		;
270
271/*
272 * Map Kernel
273 * N.B. don't bother with making kernel text RO, as 386
274 * ignores R/W AND U/S bits on kernel access (only v works) !
275 *
276 * First step - build page tables
277 */
278	movl	%esi,%ecx		# this much memory,
279	shrl	$ PGSHIFT,%ecx		# for this many pte s
280	addl	$ UPAGES+4,%ecx		# including our early context
281	movl	$0xa0,%ecx		# XXX - cover debugger pages
282	movl	$PG_V|PG_KW,%eax	#  having these bits set,
283	lea	(4*NBPG)(%esi),%ebx	#   physical address of KPT in proc 0,
284	movl	%ebx,_KPTphys-SYSTEM	#    in the kernel page table,
285	fillkpt
286
287/* map I/O memory map */
288
289	movl	$0x100-0xa0,%ecx	# for this many pte s,
290	movl	$(0xa0000|PG_V|PG_UW),%eax # having these bits set,(perhaps URW?) XXX 06 Aug 92
291	movl	%ebx,_atdevphys-SYSTEM	#   remember phys addr of ptes
292	fillkpt
293
294 /* map proc 0's kernel stack into user page table page */
295
296	movl	$ UPAGES,%ecx		# for this many pte s,
297	lea	(1*NBPG)(%esi),%eax	# physical address in proc 0
298	lea	(SYSTEM)(%eax),%edx
299	movl	%edx,_proc0paddr-SYSTEM  # remember VA for 0th process init
300	orl	$PG_V|PG_KW,%eax	#  having these bits set,
301	lea	(3*NBPG)(%esi),%ebx	# physical address of stack pt in proc 0
302	addl	$(PPTEOFF*4),%ebx
303	fillkpt
304
305/*
306 * Construct a page table directory
307 * (of page directory elements - pde's)
308 */
309	/* install a pde for temporary double map of bottom of VA */
310	lea	(4*NBPG)(%esi),%eax	# physical address of kernel page table
311	orl     $ PG_V|PG_UW,%eax	# pde entry is valid XXX 06 Aug 92
312	movl	%eax,(%esi)		# which is where temp maps!
313
314	/* kernel pde's */
315	movl	$ 3,%ecx		# for this many pde s,
316	lea	(SYSPDROFF*4)(%esi), %ebx	# offset of pde for kernel
317	fillkpt
318
319	/* install a pde recursively mapping page directory as a page table! */
320	movl	%esi,%eax		# phys address of ptd in proc 0
321	orl	$ PG_V|PG_UW,%eax	# pde entry is valid XXX 06 Aug 92
322	movl	%eax, PDRPDROFF*4(%esi)	# which is where PTmap maps!
323
324	/* install a pde to map kernel stack for proc 0 */
325	lea	(3*NBPG)(%esi),%eax	# physical address of pt in proc 0
326	orl	$PG_V|PG_KW,%eax	# pde entry is valid
327	movl	%eax,PPDROFF*4(%esi)	# which is where kernel stack maps!
328
329	/* copy and convert stuff from old gdt and idt for debugger */
330
331	cmpl	$0x0375c339,0x96104	# XXX - debugger signature
332	jne	1f
333	movb	$1,_bdb_exists-SYSTEM
3341:
335	pushal
336	subl	$2*6,%esp
337
338	sgdt	(%esp)
339	movl	2(%esp),%esi		# base address of current gdt
340	movl	$_gdt-SYSTEM,%edi
341	movl	%edi,2(%esp)
342	movl	$8*18/4,%ecx
343	rep				# copy gdt
344	movsl
345	movl	$_gdt-SYSTEM,-8+2(%edi)	# adjust gdt self-ptr
346	movb	$0x92,-8+5(%edi)
347
348	sidt	6(%esp)
349	movl	6+2(%esp),%esi		# base address of current idt
350	movl	8+4(%esi),%eax		# convert dbg descriptor to ...
351	movw	8(%esi),%ax
352	movl	%eax,bdb_dbg_ljmp+1-SYSTEM	# ... immediate offset ...
353	movl	8+2(%esi),%eax
354	movw	%ax,bdb_dbg_ljmp+5-SYSTEM	# ... and selector for ljmp
355	movl	24+4(%esi),%eax		# same for bpt descriptor
356	movw	24(%esi),%ax
357	movl	%eax,bdb_bpt_ljmp+1-SYSTEM
358	movl	24+2(%esi),%eax
359	movw	%ax,bdb_bpt_ljmp+5-SYSTEM
360
361	movl	$_idt-SYSTEM,%edi
362	movl	%edi,6+2(%esp)
363	movl	$8*4/4,%ecx
364	rep				# copy idt
365	movsl
366
367	lgdt	(%esp)
368	lidt	6(%esp)
369
370	addl	$2*6,%esp
371	popal
372
373	/* load base of page directory, and enable mapping */
374	movl	%esi,%eax		# phys address of ptd in proc 0
375 	orl	$ I386_CR3PAT,%eax
376	movl	%eax,%cr3		# load ptd addr into mmu
377	movl	%cr0,%eax		# get control word
378#ifdef USE_486_WRITE_PROTECT
379	orl	$CR0_PE|CR0_PG|CR0_WP,%eax	# and let s page!
380#else
381	orl	$CR0_PE|CR0_PG,%eax	# and let s page!
382#endif
383	movl	%eax,%cr0		# NOW!
384
385	pushl	$begin				# jump to high mem!
386	ret
387
388begin: /* now running relocated at SYSTEM where the system is linked to run */
389
390	.globl _Crtat			# XXX - locore should not know about
391	movl	_Crtat,%eax		# variables of device drivers (pccons)!
392	subl	$0xfe0a0000,%eax
393	movl	_atdevphys,%edx	# get pte PA
394	subl	_KPTphys,%edx	# remove base of ptes, now have phys offset
395	shll	$ PGSHIFT-2,%edx  # corresponding to virt offset
396	addl	$ SYSTEM,%edx	# add virtual base
397	movl	%edx, _atdevbase
398	addl	%eax,%edx
399	movl	%edx,_Crtat
400
401	/* set up bootstrap stack */
402	movl	$ _kstack+UPAGES*NBPG-4*12,%esp	# bootstrap stack end location
403	xorl	%eax,%eax		# mark end of frames
404	movl	%eax,%ebp
405	movl	_proc0paddr, %eax
406	movl	%esi, PCB_CR3(%eax)
407
408	lea	7*NBPG(%esi),%esi	# skip past stack.
409	pushl	%esi
410
411	/* relocate debugger gdt entries */
412
413	movl	$_gdt+8*9,%eax		# adjust slots 9-17
414	movl	$9,%ecx
415reloc_gdt:
416	movb	$0xfe,7(%eax)		# top byte of base addresses, was 0,
417	addl	$8,%eax			# now SYSTEM>>24
418	loop	reloc_gdt
419
420	cmpl	$0,_bdb_exists
421	je	1f
422	int	$3
4231:
424
425	call	_init386		# wire 386 chip for unix operation
426
427	movl	$0,_PTD
428	call 	_main			# autoconfiguration, mountroot etc
429	popl	%esi
430
431	/*
432	 * on return from main(), we are process 1
433	 * set up address space and stack so that we can 'return' to user mode
434	 */
435
436	movl	__ucodesel,%eax
437	movl	__udatasel,%ecx
438	# build outer stack frame
439	pushl	%ecx		# user ss
440	pushl	$ USRSTACK	# user esp
441	pushl	%eax		# user cs
442	pushl	$0		# user ip
443	movl	%cx,%ds
444	movl	%cx,%es
445	movl	%ax,%fs		# double map cs to fs
446	movl	%cx,%gs		# and ds to gs
447	lret	# goto user!
448
449	pushl	$lretmsg1	/* "should never get here!" */
450	call	_panic
451lretmsg1:
452	.asciz	"lret: toinit\n"
453
454
455	.set	exec,59
456	.set	exit,1
457
458#define	LCALL(x,y)	.byte 0x9a ; .long y; .word x
459/*
460 * Icode is copied out to process 1 and executed in user mode:
461 *	execve("/sbin/init", argv, envp); exit(0);
462 * If the exec fails, process 1 exits and the system panics.
463 */
464ENTRY(icode)
465	# pushl	$argv-_icode	# gas fucks up again
466	movl	$argv,%eax
467	subl	$_icode,%eax
468	pushl	%eax
469
470	# pushl	$init-_icode
471	movl	$init,%eax
472	subl	$_icode,%eax
473	pushl	%eax
474	pushl	%eax	# dummy out rta
475
476	movl	%esp,%ebp
477	movl	$exec,%eax
478	LCALL(0x7,0x0)
479	pushl	%eax
480	movl	$exit,%eax
481	pushl	%eax	# dummy out rta
482	LCALL(0x7,0x0)
483
484init:
485	.asciz	"/sbin/init"
486	ALIGN_DATA
487argv:
488	.long	init+6-_icode		# argv[0] = "init" ("/sbin/init" + 6)
489	.long	eicode-_icode		# argv[1] follows icode after copyout
490	.long	0
491eicode:
492
493	.globl	_szicode
494_szicode:
495	.long	_szicode-_icode
496
497ENTRY(sigcode)
498	call	12(%esp)
499	lea	28(%esp),%eax	# scp (the call may have clobbered the
500				# copy at 8(%esp))
501				# XXX - use genassym
502	pushl	%eax
503	pushl	%eax		# junk to fake return address
504	movl	$103,%eax	# sigreturn()
505	LCALL(0x7,0)		# enter kernel with args on stack
506	hlt			# never gets here
507
508	.globl	_szsigcode
509_szsigcode:
510	.long	_szsigcode-_sigcode
511
512
513/*****************************************************************************/
514/* support routines for GCC, general C-callable functions                    */
515/*****************************************************************************/
516
517ENTRY(__udivsi3)
518	movl 4(%esp),%eax
519	xorl %edx,%edx
520	divl 8(%esp)
521	ret
522
523ENTRY(__divsi3)
524	movl 4(%esp),%eax
525	cltd
526	idivl 8(%esp)
527	ret
528
529
530	/*
531	 * I/O bus instructions via C
532	 */
533ENTRY(outb)				# outb (port, val)
534	movl	4(%esp),%edx
535	NOP
536	movl	8(%esp),%eax
537	outb	%al,%dx
538	NOP
539	ret
540
541
542ENTRY(outw)				# outw (port, val)
543	movl	4(%esp),%edx
544	NOP
545	movl	8(%esp),%eax
546	outw	%ax,%dx
547	NOP
548	ret
549
550
551ENTRY(outsb)			# outsb(port,addr,cnt)
552	pushl	%esi
553	movw	8(%esp),%dx
554	movl	12(%esp),%esi
555	movl	16(%esp),%ecx
556	cld
557	NOP
558	rep
559	outsb
560	NOP
561	movl	%esi,%eax
562	popl	%esi
563	ret
564
565
566ENTRY(outsw)			# outsw(port,addr,cnt)
567	pushl	%esi
568	movw	8(%esp),%dx
569	movl	12(%esp),%esi
570	movl	16(%esp),%ecx
571	cld
572	NOP
573	rep
574	outsw
575	NOP
576	movl	%esi,%eax
577	popl	%esi
578	ret
579
580
581ENTRY(inb)			# val = inb (port)
582	movl	4(%esp),%edx
583	subl	%eax,%eax	# clr eax
584	NOP
585	inb	%dx,%al
586	ret
587
588
589ENTRY(inw)			# val = inw (port)
590	movl	4(%esp),%edx
591	subl	%eax,%eax	# clr eax
592	NOP
593	inw	%dx,%ax
594	ret
595
596
597ENTRY(insb)			# insb(port,addr,cnt)
598	pushl	%edi
599	movw	8(%esp),%dx
600	movl	12(%esp),%edi
601	movl	16(%esp),%ecx
602	cld
603	NOP
604	rep
605	insb
606	NOP
607	movl	%edi,%eax
608	popl	%edi
609	ret
610
611
612ENTRY(insw)			# insw(port,addr,cnt)
613	pushl	%edi
614	movw	8(%esp),%dx
615	movl	12(%esp),%edi
616	movl	16(%esp),%ecx
617	cld
618	NOP
619	rep
620	insw
621	NOP
622	movl	%edi,%eax
623	popl	%edi
624	ret
625
626
627ENTRY(rtcin)
628	movl	4(%esp),%eax
629	outb	%al,$0x70
630	subl	%eax,%eax	# clr eax
631	inb	$0x71,%al
632	ret
633
634
635	/*
636	 * bcopy family
637	 */
638ENTRY(bzero)			# void bzero(void *base, u_int cnt)
639	pushl	%edi
640	movl	8(%esp),%edi
641	movl	12(%esp),%ecx
642	xorl	%eax,%eax
643	shrl	$2,%ecx
644	cld
645	rep
646	stosl
647	movl	12(%esp),%ecx
648	andl	$3,%ecx
649	rep
650	stosb
651	popl	%edi
652	ret
653
654
655ENTRY(fillw)			# fillw (pat,base,cnt)
656	pushl	%edi
657	movl	8(%esp),%eax
658	movl	12(%esp),%edi
659	movl	16(%esp),%ecx
660	cld
661	rep
662	stosw
663	popl	%edi
664	ret
665
666ENTRY(bcopyb)
667	pushl	%esi
668	pushl	%edi
669	movl	12(%esp),%esi
670	movl	16(%esp),%edi
671	movl	20(%esp),%ecx
672	cmpl	%esi,%edi	/* potentially overlapping? */
673	jnb	1f
674	cld			/* nope, copy forwards */
675	rep
676	movsb
677	popl	%edi
678	popl	%esi
679	ret
680
681	ALIGN_TEXT
6821:
683	addl	%ecx,%edi	/* copy backwards. */
684	addl	%ecx,%esi
685	std
686	decl	%edi
687	decl	%esi
688	rep
689	movsb
690	popl	%edi
691	popl	%esi
692	cld
693	ret
694
695ENTRY(bcopyw)
696	pushl	%esi
697	pushl	%edi
698	movl	12(%esp),%esi
699	movl	16(%esp),%edi
700	movl	20(%esp),%ecx
701	cmpl	%esi,%edi	/* potentially overlapping? */
702	jnb	1f
703	cld			/* nope, copy forwards */
704	shrl	$1,%ecx		/* copy by 16-bit words */
705	rep
706	movsw
707	adc	%ecx,%ecx	/* any bytes left? */
708	rep
709	movsb
710	popl	%edi
711	popl	%esi
712	ret
713
714	ALIGN_TEXT
7151:
716	addl	%ecx,%edi	/* copy backwards */
717	addl	%ecx,%esi
718	std
719	andl	$1,%ecx		/* any fractional bytes? */
720	decl	%edi
721	decl	%esi
722	rep
723	movsb
724	movl	20(%esp),%ecx	/* copy remainder by 16-bit words */
725	shrl	$1,%ecx
726	decl	%esi
727	decl	%edi
728	rep
729	movsw
730	popl	%edi
731	popl	%esi
732	cld
733	ret
734
735ENTRY(bcopyx)
736	movl	16(%esp),%eax
737	cmpl	$2,%eax
738	je	_bcopyw
739	cmpl	$4,%eax
740	jne	_bcopyb
741	/*
742	 * Fall through to bcopy.  ENTRY() provides harmless fill bytes.
743	 */
744
745
746	/*
747	 * (ov)bcopy (src,dst,cnt)
748	 *  ws@tools.de     (Wolfgang Solfrank, TooLs GmbH) +49-228-985800
749	 */
750ENTRY(bcopy)
751ALTENTRY(ovbcopy)
752	pushl	%esi
753	pushl	%edi
754	movl	12(%esp),%esi
755	movl	16(%esp),%edi
756	movl	20(%esp),%ecx
757	cmpl	%esi,%edi	/* potentially overlapping? */
758	jnb	1f
759	cld			/* nope, copy forwards */
760	shrl	$2,%ecx		/* copy by 32-bit words */
761	rep
762	movsl
763	movl	20(%esp),%ecx
764	andl	$3,%ecx		/* any bytes left? */
765	rep
766	movsb
767	popl	%edi
768	popl	%esi
769	ret
770
771	ALIGN_TEXT
7721:
773	addl	%ecx,%edi	/* copy backwards */
774	addl	%ecx,%esi
775	std
776	andl	$3,%ecx		/* any fractional bytes? */
777	decl	%edi
778	decl	%esi
779	rep
780	movsb
781	movl	20(%esp),%ecx	/* copy remainder by 32-bit words */
782	shrl	$2,%ecx
783	subl	$3,%esi
784	subl	$3,%edi
785	rep
786	movsl
787	popl	%edi
788	popl	%esi
789	cld
790	ret
791
792ENTRY(ntohl)
793ALTENTRY(htonl)
794	movl	4(%esp),%eax
795#ifdef i486
796	/* XXX */
797	/* Since Gas 1.38 does not grok bswap this has been coded as the
798	 * equivalent bytes.  This can be changed back to bswap when we
799	 * upgrade to a newer version of Gas */
800	/* bswap	%eax */
801	.byte 	0x0f
802	.byte	0xc8
803#else
804	xchgb	%al,%ah
805	roll	$16,%eax
806	xchgb	%al,%ah
807#endif
808	ret
809
810ENTRY(ntohs)
811ALTENTRY(htons)
812	movzwl	4(%esp),%eax
813	xchgb	%al,%ah
814	ret
815
816
817#ifdef SHOW_A_LOT
818/*
819 * 'show_bits' was too big when defined as a macro.  The line length for some
820 * enclosing macro was too big for gas.  Perhaps the code would have blown
821 * the cache anyway.
822 */
823	ALIGN_TEXT
824show_bits:
825	pushl	%eax
826	SHOW_BIT(0)
827	SHOW_BIT(1)
828	SHOW_BIT(2)
829	SHOW_BIT(3)
830	SHOW_BIT(4)
831	SHOW_BIT(5)
832	SHOW_BIT(6)
833	SHOW_BIT(7)
834	SHOW_BIT(8)
835	SHOW_BIT(9)
836	SHOW_BIT(10)
837	SHOW_BIT(11)
838	SHOW_BIT(12)
839	SHOW_BIT(13)
840	SHOW_BIT(14)
841	SHOW_BIT(15)
842	popl	%eax
843	ret
844#endif /* SHOW_A_LOT */
845
846
847/*****************************************************************************/
848/* copyout and fubyte family                                                 */
849/*****************************************************************************/
850/*
851 * Access user memory from inside the kernel. These routines and possibly
852 * the math- and DOS emulators should be the only places that do this.
853 *
854 * We have to access the memory with user's permissions, so use a segment
855 * selector with RPL 3. For writes to user space we have to additionally
856 * check the PTE for write permission, because the 386 does not check
857 * write permissions when we are executing with EPL 0. The 486 does check
858 * this if the WP bit is set in CR0, so we can use a simpler version here.
859 *
860 * These routines set curpcb->onfault for the time they execute. When a
861 * protection violation occurs inside the functions, the trap handler
862 * returns to *curpcb->onfault instead of the function.
863 */
864/*
865 * XXX These routines load a segment register every time they execute.
866 * it would be nicer (faster) if they could depend on %gs.
867 */
868
869
870ENTRY(copyout)			# copyout (from_kernel, to_user, len)
871	movl	_curpcb, %eax
872	movl	$copyout_fault, PCB_ONFAULT(%eax)
873	pushl	%esi
874	pushl	%edi
875	pushl	%ebx
876	movl	16(%esp), %esi
877	movl	20(%esp), %edi
878	movl	24(%esp), %ebx
879	orl	%ebx, %ebx	# nothing to do?
880	jz	done_copyout
881
882#ifdef USE_486_WRITE_PROTECT
883	/* if WP bit in CR0 is set (n/a on 386), the hardware does the */
884	/* write check. We just have to load the right segment selector */
885	pushl	%es
886	movl	__udatasel, %eax
887	movl	%ax, %es
888#else /* USE_486_WRITE_PROTECT */
889	/* we have to check each PTE for (write) permission */
890
891			/* compute number of pages */
892	movl	%edi, %ecx
893	andl	$0x0fff, %ecx
894	addl	%ebx, %ecx
895	decl	%ecx
896	shrl	$IDXSHIFT+2, %ecx
897	incl	%ecx
898
899			/* compute PTE offset for start address */
900	movl	%edi, %edx
901	shrl	$IDXSHIFT, %edx
902	andb	$0xfc, %dl
903
9041:			/* check PTE for each page */
905	movb	_PTmap(%edx), %al
906	andb	$0x07, %al	/* Pages must be VALID + USERACC + WRITABLE */
907	cmpb	$0x07, %al
908	je	2f
909
910				/* simulate a trap */
911	pushl	%edx
912	pushl	%ecx
913	shll	$IDXSHIFT, %edx
914	pushl	%edx
915	call	_trapwrite	/* XXX trapwrite(addr) */
916	popl	%edx
917	popl	%ecx
918	popl	%edx
919
920	orl	%eax, %eax	/* if not ok, return EFAULT */
921	jnz	copyout_fault
922
9232:
924	addl	$4, %edx
925	decl	%ecx
926	jnz	1b		/* check next page */
927
928#endif /* USE_486_WRITE_PROTECT */
929
930			/* now copy it over */
931			/* bcopy (%esi, %edi, %ebx) */
932	cld
933	movl	%ebx, %ecx
934	shrl	$2, %ecx
935	rep
936	movsl
937	movb	%bl, %cl
938	andb	$3, %cl
939	rep
940	movsb
941#ifdef USE_486_WRITE_PROTECT
942	popl	%es
943#endif
944
945done_copyout:
946	popl	%ebx
947	popl	%edi
948	popl	%esi
949	xorl	%eax,%eax
950	movl	_curpcb,%edx
951	movl	%eax,PCB_ONFAULT(%edx)
952	ret
953
954copyout_fault:
955#ifdef	USE_486_WRITE_PROTECT
956	popl	%es
957#endif
958	popl	%ebx
959	popl	%edi
960	popl	%esi
961	movl	_curpcb, %edx
962	movl	$0, PCB_ONFAULT(%edx)
963	movl	$EFAULT, %eax
964	ret
965
966
967ENTRY(copyin)			# copyin (from_user, to_kernel, len)
968	movl	_curpcb,%eax
969	movl	$copyin_fault, PCB_ONFAULT(%eax)
970	pushl	%esi
971	pushl	%edi
972	movl	12(%esp),%esi		# caddr_t from
973	movl	16(%esp),%edi		# caddr_t to
974	movl	20(%esp),%ecx		# size_t  len
975	movl	%ecx,%edx
976	pushl	%ds
977	movl	__udatasel,%ax		# access 'from' via user data segment
978	movl	%ax,%ds
979
980	movb	%cl,%al
981	shrl	$2,%ecx			# copy longword-wise
982	cld
983	rep
984	movsl
985	movb	%al,%cl
986	andb	$3,%cl			# copy remaining bytes
987	rep
988	movsb
989
990	popl	%ds
991	popl	%edi
992	popl	%esi
993	xorl	%eax, %eax
994	movl	_curpcb, %edx
995	movl	%eax, PCB_ONFAULT(%edx)
996	ret
997
998copyin_fault:
999	popl	%ds
1000	popl	%edi
1001	popl	%esi
1002	movl	_curpcb, %edx
1003	movl	$0, PCB_ONFAULT(%edx)
1004	movl	$EFAULT, %eax
1005	ret
1006
1007	/*
1008	 * fu{byte,sword,word} : fetch a byte (sword, word) from user memory
1009	 */
1010ENTRY(fuword)
1011ALTENTRY(fuiword)
1012	movl	__udatasel,%eax
1013	movl	%ax,%gs
1014	movl	_curpcb,%ecx
1015	movl	$fusufault,PCB_ONFAULT(%ecx)
1016	movl	4(%esp),%edx
1017	gs
1018	movl	(%edx),%eax
1019	movl	$0,PCB_ONFAULT(%ecx)
1020	ret
1021
1022ENTRY(fusword)
1023	movl	__udatasel,%eax
1024	movl	%ax,%gs
1025	movl	_curpcb,%ecx
1026	movl	$fusufault,PCB_ONFAULT(%ecx)
1027	movl	4(%esp),%edx
1028	gs
1029	movzwl	(%edx),%eax
1030	movl	$0,PCB_ONFAULT(%ecx)
1031	ret
1032
1033ENTRY(fubyte)
1034ALTENTRY(fuibyte)
1035	movl	__udatasel,%eax
1036	movl	%ax,%gs
1037	movl	_curpcb,%ecx
1038	movl	$fusufault,PCB_ONFAULT(%ecx)
1039	movl	4(%esp),%edx
1040	gs
1041	movzbl	(%edx),%eax
1042	movl	$0,PCB_ONFAULT(%ecx)
1043	ret
1044
1045fusufault:
1046	movl	_curpcb,%ecx
1047	xorl	%eax,%eax
1048	movl	%eax,PCB_ONFAULT(%ecx)
1049	decl	%eax
1050	ret
1051
1052	/*
1053	 * su{byte,sword,word}: write a byte (word, longword) to user memory
1054	 */
1055#ifdef USE_486_WRITE_PROTECT
1056	/*
1057	 * we only have to set the right segment selector.
1058	 */
1059ENTRY(suword)
1060ALTENTRY(suiword)
1061	movl	__udatasel,%eax
1062	movl	%ax,%gs
1063	movl	_curpcb,%ecx
1064	movl	$fusufault,PCB_ONFAULT(%ecx)
1065	movl	4(%esp),%edx
1066	movl	8(%esp),%eax
1067	gs
1068	movl	%eax,(%edx)
1069	movl	$0,PCB_ONFAULT(%ecx)
1070	ret
1071
1072ENTRY(susword)
1073	movl	__udatasel,%eax
1074	movl	%ax,%gs
1075	movl	_curpcb,%ecx
1076	movl	$fusufault,PCB_ONFAULT(%ecx)
1077	movl	4(%esp),%edx
1078	movw	8(%esp),%ax
1079	gs
1080	movw	%ax,(%edx)
1081	movl	$0,PCB_ONFAULT(%ecx)
1082	ret
1083
1084ENTRY(subyte)
1085ALTENTRY(suibyte)
1086	movl	__udatasel,%eax
1087	movl	%ax,%gs
1088	movl	_curpcb,%ecx
1089	movl	$fusufault,PCB_ONFAULT(%ecx)
1090	movl	4(%esp),%edx
1091	movb	8(%esp),%al
1092	gs
1093	movb	%al,(%edx)
1094	movl	$0,PCB_ONFAULT(%ecx)
1095	ret
1096
1097
1098#else /* USE_486_WRITE_PROTECT */
1099	/*
1100	 * here starts the trouble again: check PTE, twice if word crosses
1101	 * a page boundary.
1102	 */
1103	# XXX - page boundary crossing is not handled yet
1104
1105ENTRY(subyte)
1106ENTRY(suibyte)
1107	movl	_curpcb, %ecx
1108	movl	$fusufault, PCB_ONFAULT(%ecx)
1109	movl	4(%esp), %edx
1110	movl	%edx, %eax
1111	shrl	$IDXSHIFT, %edx
1112	andb	$0xfc, %dl
1113	movb	_PTmap(%edx), %dl
1114	andb	$0x7, %dl		/* must be VALID + USERACC + WRITE */
1115	cmpb	$0x7, %dl
1116	je	1f
1117					/* simulate a trap */
1118	pushl	%eax
1119	call	_trapwrite
1120	popl	%edx
1121	orl	%eax, %eax
1122	jnz	fusufault
11231:
1124	movl	4(%esp), %edx
1125	movl	8(%esp), %eax
1126	movb	%al, (%edx)
1127	xorl	%eax, %eax
1128	movl	_curpcb, %ecx
1129	movl	%eax, PCB_ONFAULT(%ecx)
1130	ret
1131
1132ENTRY(susword)
1133	movl	_curpcb, %ecx
1134	movl	$fusufault, PCB_ONFAULT(%ecx)
1135	movl	4(%esp), %edx
1136	movl	%edx, %eax
1137	shrl	$IDXSHIFT, %edx
1138	andb	$0xfc, %dl
1139	movb	_PTmap(%edx), %dl
1140	andb	$0x7, %dl		/* must be VALID + USERACC + WRITE */
1141	cmpb	$0x7, %dl
1142	je	1f
1143					/* simulate a trap */
1144	pushl	%eax
1145	call	_trapwrite
1146	popl	%edx
1147	orl	%eax, %eax
1148	jnz	fusufault
11491:
1150	movl	4(%esp), %edx
1151	movl	8(%esp), %eax
1152	movw	%ax, (%edx)
1153	xorl	%eax, %eax
1154	movl	_curpcb, %ecx
1155	movl	%eax, PCB_ONFAULT(%ecx)
1156	ret
1157
1158ENTRY(suword)
1159ENTRY(suiword)
1160	movl	_curpcb, %ecx
1161	movl	$fusufault, PCB_ONFAULT(%ecx)
1162	movl	4(%esp), %edx
1163	movl	%edx, %eax
1164	shrl	$IDXSHIFT, %edx
1165	andb	$0xfc, %dl
1166	movb	_PTmap(%edx), %dl
1167	andb	$0x7, %dl		/* must be VALID + USERACC + WRITE */
1168	cmpb	$0x7, %dl
1169	je	1f
1170					/* simulate a trap */
1171	pushl	%eax
1172	call	_trapwrite
1173	popl	%edx
1174	orl	%eax, %eax
1175	jnz	fusufault
11761:
1177	movl	4(%esp), %edx
1178	movl	8(%esp), %eax
1179	movl	%eax, 0(%edx)
1180	xorl	%eax, %eax
1181	movl	_curpcb, %ecx
1182	movl	%eax, PCB_ONFAULT(%ecx)
1183	ret
1184
1185#endif /* USE_486_WRITE_PROTECT */
1186/*
1187 * copyoutstr(from, to, maxlen, int *lencopied)
1188 *	copy a string from from to to, stop when a 0 character is reached.
1189 *	return ENAMETOOLONG if string is longer than maxlen, and
1190 *	EFAULT on protection violations. If lencopied is non-zero,
1191 *	return the actual length in *lencopied.
1192 */
1193#ifdef USE_486_WRITE_PROTECT
1194
1195ENTRY(copyoutstr)
1196	pushl	%esi
1197	pushl	%edi
1198	movl	_curpcb, %ecx
1199	movl	$cpystrflt, PCB_ONFAULT(%ecx)
1200
1201	movl	12(%esp), %esi			# %esi = from
1202	movl	16(%esp), %edi			# %edi = to
1203	movl	20(%esp), %edx			# %edx = maxlen
1204	movl	__udatasel,%eax
1205	movl	%ax,%gs
1206	incl	%edx
1207
12081:
1209	decl	%edx
1210	jz	4f
1211	lodsb
1212	gs
1213	stosb
1214	orb	%al,%al
1215	jnz	1b
1216			/* Success -- 0 byte reached */
1217	decl	%edx
1218	xorl	%eax, %eax
1219	jmp	6f
12204:
1221			/* edx is zero -- return ENAMETOOLONG */
1222	movl	$ENAMETOOLONG, %eax
1223	jmp	6f
1224
1225#else	/* USE_486_WRITE_PROTECT */
1226
1227ENTRY(copyoutstr)
1228	pushl	%esi
1229	pushl	%edi
1230	movl	_curpcb, %ecx
1231	movl	$cpystrflt, PCB_ONFAULT(%ecx)
1232
1233	movl	12(%esp), %esi			# %esi = from
1234	movl	16(%esp), %edi			# %edi = to
1235	movl	20(%esp), %edx			# %edx = maxlen
12361:
1237	movl	%edi, %eax
1238	shrl	$IDXSHIFT, %eax
1239	andb	$0xfc, %al
1240	movb	_PTmap(%eax), %al
1241	andb	$7, %al
1242	cmpb	$7, %al
1243	je	2f
1244
1245			/* simulate trap */
1246	pushl	%edx
1247	pushl	%edi
1248	call	_trapwrite
1249	popl	%edi
1250	popl	%edx
1251	orl	%eax, %eax
1252	jnz	cpystrflt
1253
12542:			/* copy up to end of this page */
1255	movl	%edi, %eax
1256	andl	$0x0fff, %eax
1257	movl	$NBPG, %ecx
1258	subl	%eax, %ecx	/* ecx = NBPG - (src % NBPG) */
1259	cmpl	%ecx, %edx
1260	jge	3f
1261	movl	%edx, %ecx	/* ecx = min (ecx, edx) */
12623:
1263	orl	%ecx, %ecx
1264	jz	4f
1265	decl	%ecx
1266	decl	%edx
1267	lodsb
1268	stosb
1269	orb	%al, %al
1270	jnz	3b
1271
1272			/* Success -- 0 byte reached */
1273	decl	%edx
1274	xorl	%eax, %eax
1275	jmp	6f
1276
12774:			/* next page */
1278	orl	%edx, %edx
1279	jnz	1b
1280			/* edx is zero -- return ENAMETOOLONG */
1281	movl	$ENAMETOOLONG, %eax
1282	jmp	6f
1283#endif /* USE_486_WRITE_PROTECT */
1284
1285/*
1286 * copyinstr(from, to, maxlen, int *lencopied)
1287 *	copy a string from from to to, stop when a 0 character is reached.
1288 *	return ENAMETOOLONG if string is longer than maxlen, and
1289 *	EFAULT on protection violations. If lencopied is non-zero,
1290 *	return the actual length in *lencopied.
1291 */
1292ENTRY(copyinstr)
1293	pushl	%esi
1294	pushl	%edi
1295	movl	_curpcb, %ecx
1296	movl	$cpystrflt, PCB_ONFAULT(%ecx)
1297
1298	movl	12(%esp), %esi			# %esi = from
1299	movl	16(%esp), %edi			# %edi = to
1300	movl	20(%esp), %edx			# %edx = maxlen
1301	movl	__udatasel,%eax
1302	movl	%ax,%gs
1303	incl	%edx
1304
13051:
1306	decl	%edx
1307	jz	4f
1308	gs
1309	lodsb
1310	stosb
1311	orb	%al,%al
1312	jnz	1b
1313			/* Success -- 0 byte reached */
1314	decl	%edx
1315	xorl	%eax, %eax
1316	jmp	6f
13174:
1318			/* edx is zero -- return ENAMETOOLONG */
1319	movl	$ENAMETOOLONG, %eax
1320	jmp	6f
1321
1322cpystrflt:
1323	movl	$EFAULT, %eax
13246:			/* set *lencopied and return %eax */
1325	movl	_curpcb, %ecx
1326	movl	$0, PCB_ONFAULT(%ecx)
1327	movl	20(%esp), %ecx
1328	subl	%edx, %ecx
1329	movl	24(%esp), %edx
1330	orl	%edx, %edx
1331	jz	7f
1332	movl	%ecx, (%edx)
13337:
1334	popl	%edi
1335	popl	%esi
1336	ret
1337
1338
1339/*
1340 * copystr(from, to, maxlen, int *lencopied)
1341 */
1342ENTRY(copystr)
1343	pushl	%esi
1344	pushl	%edi
1345
1346	movl	12(%esp), %esi			# %esi = from
1347	movl	16(%esp), %edi			# %edi = to
1348	movl	20(%esp), %edx			# %edx = maxlen
1349	incl	%edx
1350
13511:
1352	decl	%edx
1353	jz	4f
1354	lodsb
1355	stosb
1356	orb	%al,%al
1357	jnz	1b
1358			/* Success -- 0 byte reached */
1359	decl	%edx
1360	xorl	%eax, %eax
1361	jmp	6f
13624:
1363			/* edx is zero -- return ENAMETOOLONG */
1364	movl	$ENAMETOOLONG, %eax
1365
13666:			/* set *lencopied and return %eax */
1367	movl	20(%esp), %ecx
1368	subl	%edx, %ecx
1369	movl	24(%esp), %edx
1370	orl	%edx, %edx
1371	jz	7f
1372	movl	%ecx, (%edx)
13737:
1374	popl	%edi
1375	popl	%esi
1376	ret
1377
1378/*****************************************************************************/
1379/* Handling of special 386 registers and descriptor tables etc               */
1380/*****************************************************************************/
1381	/*
1382	 * void lgdt(struct region_descriptor *rdp);
1383	 */
1384ENTRY(lgdt)
1385	/* reload the descriptor table */
1386	movl	4(%esp),%eax
1387	lgdt	(%eax)
1388	/* flush the prefetch q */
1389	jmp	1f
1390	nop
13911:
1392	/* reload "stale" selectors */
1393	movl	$KDSEL,%eax
1394	movl	%ax,%ds
1395	movl	%ax,%es
1396	movl	%ax,%ss
1397
1398	/* reload code selector by turning return into intersegmental return */
1399	movl	(%esp),%eax
1400	pushl	%eax
1401	# movl	$KCSEL,4(%esp)
1402	movl	$8,4(%esp)
1403	lret
1404
1405	/*
1406	 * void lidt(struct region_descriptor *rdp);
1407	 */
1408ENTRY(lidt)
1409	movl	4(%esp),%eax
1410	lidt	(%eax)
1411	ret
1412
1413	/*
1414	 * void lldt(u_short sel)
1415	 */
1416ENTRY(lldt)
1417	lldt	4(%esp)
1418	ret
1419
1420	/*
1421	 * void ltr(u_short sel)
1422	 */
1423ENTRY(ltr)
1424	ltr	4(%esp)
1425	ret
1426
1427ENTRY(ssdtosd)				# ssdtosd(*ssdp,*sdp)
1428	pushl	%ebx
1429	movl	8(%esp),%ecx
1430	movl	8(%ecx),%ebx
1431	shll	$16,%ebx
1432	movl	(%ecx),%edx
1433	roll	$16,%edx
1434	movb	%dh,%bl
1435	movb	%dl,%bh
1436	rorl	$8,%ebx
1437	movl	4(%ecx),%eax
1438	movw	%ax,%dx
1439	andl	$0xf0000,%eax
1440	orl	%eax,%ebx
1441	movl	12(%esp),%ecx
1442	movl	%edx,(%ecx)
1443	movl	%ebx,4(%ecx)
1444	popl	%ebx
1445	ret
1446
1447
1448ENTRY(tlbflush)				# tlbflush()
1449	movl	%cr3,%eax
1450 	orl	$ I386_CR3PAT,%eax
1451	movl	%eax,%cr3
1452	ret
1453
1454
1455ENTRY(lcr0)				# lcr0(cr0)
1456ALTENTRY(load_cr0)
1457	movl	4(%esp),%eax
1458	movl	%eax,%cr0
1459	ret
1460
1461
1462ENTRY(rcr0)				# rcr0()
1463	movl	%cr0,%eax
1464	ret
1465
1466
1467ENTRY(rcr2)				# rcr2()
1468	movl	%cr2,%eax
1469	ret
1470
1471
1472ENTRY(rcr3)				# rcr3()
1473ALTENTRY(_cr3)
1474	movl	%cr3,%eax
1475	ret
1476
1477
1478	/*
1479	 * void lcr3(caddr_t cr3)
1480	 */
1481ENTRY(lcr3)
1482ALTENTRY(load_cr3)
1483	movl	4(%esp),%eax
1484 	orl	$ I386_CR3PAT,%eax
1485	movl	%eax,%cr3
1486	ret
1487
1488
1489/*****************************************************************************/
1490/* setjump, longjump                                                         */
1491/*****************************************************************************/
1492
1493ENTRY(setjmp)
1494	movl	4(%esp),%eax
1495	movl	%ebx,  (%eax)		# save ebx
1496	movl	%esp, 4(%eax)		# save esp
1497	movl	%ebp, 8(%eax)		# save ebp
1498	movl	%esi,12(%eax)		# save esi
1499	movl	%edi,16(%eax)		# save edi
1500	movl	(%esp),%edx		# get rta
1501	movl	%edx,20(%eax)		# save eip
1502	xorl	%eax,%eax		# return (0);
1503	ret
1504
1505ENTRY(longjmp)
1506	movl	4(%esp),%eax
1507	movl	  (%eax),%ebx		# restore ebx
1508	movl	 4(%eax),%esp		# restore esp
1509	movl	 8(%eax),%ebp		# restore ebp
1510	movl	12(%eax),%esi		# restore esi
1511	movl	16(%eax),%edi		# restore edi
1512	movl	20(%eax),%edx		# get rta
1513	movl	%edx,(%esp)		# put in return frame
1514	xorl	%eax,%eax		# return (1);
1515	incl	%eax
1516	ret
1517
1518
1519/*****************************************************************************/
1520/* Scheduling                                                                */
1521/*****************************************************************************/
1522
1523/*
1524 * The following primitives manipulate the run queues.
1525 * _whichqs tells which of the 32 queues _qs
1526 * have processes in them.  Setrq puts processes into queues, Remrq
1527 * removes them from queues.  The running process is on no queue,
1528 * other processes are on a queue related to p->p_pri, divided by 4
1529 * actually to shrink the 0-127 range of priorities into the 32 available
1530 * queues.
1531 */
1532
1533	.globl	_whichqs,_qs,_cnt,_panic
1534	.comm	_noproc,4
1535	.comm	_runrun,4
1536
1537/*
1538 * Setrq(p)
1539 *
1540 * Call should be made at spl6(), and p->p_stat should be SRUN
1541 */
1542ENTRY(setrq)
1543	movl	4(%esp),%eax
1544	cmpl	$0,P_RLINK(%eax)	# should not be on q already
1545	je	set1
1546	pushl	$set2
1547	call	_panic
1548set1:
1549	movzbl	P_PRI(%eax),%edx
1550	shrl	$2,%edx
1551	btsl	%edx,_whichqs		# set q full bit
1552	shll	$3,%edx
1553	addl	$_qs,%edx		# locate q hdr
1554	movl	%edx,P_LINK(%eax)	# link process on tail of q
1555	movl	P_RLINK(%edx),%ecx
1556	movl	%ecx,P_RLINK(%eax)
1557	movl	%eax,P_RLINK(%edx)
1558	movl	%eax,P_LINK(%ecx)
1559	ret
1560
1561set2:	.asciz	"setrq"
1562
1563/*
1564 * Remrq(p)
1565 *
1566 * Call should be made at spl6().
1567 */
1568ENTRY(remrq)
1569	movl	4(%esp),%eax
1570	movzbl	P_PRI(%eax),%edx
1571	shrl	$2,%edx
1572	btrl	%edx,_whichqs		# clear full bit, panic if clear already
1573	jb	rem1
1574	pushl	$rem3
1575	call	_panic
1576rem1:
1577	pushl	%edx
1578	movl	P_LINK(%eax),%ecx	# unlink process
1579	movl	P_RLINK(%eax),%edx
1580	movl	%edx,P_RLINK(%ecx)
1581	movl	P_RLINK(%eax),%ecx
1582	movl	P_LINK(%eax),%edx
1583	movl	%edx,P_LINK(%ecx)
1584	popl	%edx
1585	movl	$_qs,%ecx
1586	shll	$3,%edx
1587	addl	%edx,%ecx
1588	cmpl	P_LINK(%ecx),%ecx	# q still has something?
1589	je	rem2
1590	shrl	$3,%edx			# yes, set bit as still full
1591	btsl	%edx,_whichqs
1592rem2:
1593	movl	$0,P_RLINK(%eax)	# zap reverse link to indicate off list
1594	ret
1595
1596rem3:	.asciz	"remrq"
1597sw0:	.asciz	"swtch"
1598
1599/*
1600 * When no processes are on the runq, Swtch branches to idle
1601 * to wait for something to come ready.
1602 */
1603LENTRY(Idle)
1604	sti
1605	SHOW_STI
1606idle_loop:
1607	call	_spl0
1608	cmpl	$0,_whichqs
1609	jne	sw1
1610	hlt		# wait for interrupt
1611	jmp	idle_loop
1612
1613	SUPERALIGN_TEXT	/* so profiling doesn't lump Idle with swtch().. */
1614badsw:
1615	pushl	$sw0
1616	call	_panic
1617	/*NOTREACHED*/
1618
1619/*
1620 * Swtch()
1621 */
1622ENTRY(swtch)
1623
1624	incl	_cnt+V_SWTCH
1625
1626	/* switch to new process. first, save context as needed */
1627
1628	movl	_curproc,%ecx
1629
1630	/* if no process to save, don't bother */
1631	testl	%ecx,%ecx
1632	je	sw1
1633
1634	movl	P_ADDR(%ecx),%ecx
1635
1636	movl	(%esp),%eax		# Hardware registers
1637	movl	%eax, PCB_EIP(%ecx)
1638	movl	%ebx, PCB_EBX(%ecx)
1639	movl	%esp, PCB_ESP(%ecx)
1640	movl	%ebp, PCB_EBP(%ecx)
1641	movl	%esi, PCB_ESI(%ecx)
1642	movl	%edi, PCB_EDI(%ecx)
1643
1644#ifdef NPX
1645	/* have we used fp, and need a save? */
1646	mov	_curproc,%eax
1647	cmp	%eax,_npxproc
1648	jne	1f
1649	pushl	%ecx			/* h/w bugs make saving complicated */
1650	leal	PCB_SAVEFPU(%ecx),%eax
1651	pushl	%eax
1652	call	_npxsave		/* do it in a big C function */
1653	popl	%eax
1654	popl	%ecx
16551:
1656#endif
1657
1658	movl	_CMAP2,%eax		# save temporary map PTE
1659	movl	%eax,PCB_CMAP2(%ecx)	# in our context
1660	movl	$0,_curproc		#  out of process
1661
1662	# movw	_cpl, %ax
1663	# movw	%ax, PCB_IML(%ecx)	# save ipl
1664
1665	/* save is done, now choose a new process or idle */
1666sw1:
1667	cli
1668	SHOW_CLI
1669	movl	_whichqs,%edi
16702:
1671	# XXX - bsf is sloow
1672	bsfl	%edi,%eax		# find a full q
1673	je	Idle			# if none, idle
1674	# XX update whichqs?
1675swfnd:
1676	btrl	%eax,%edi		# clear q full status
1677	jnb	2b		# if it was clear, look for another
1678	movl	%eax,%ebx		# save which one we are using
1679
1680	shll	$3,%eax
1681	addl	$_qs,%eax		# select q
1682	movl	%eax,%esi
1683
1684#ifdef	DIAGNOSTIC
1685	cmpl	P_LINK(%eax),%eax # linked to self? (e.g. not on list)
1686	je	badsw			# not possible
1687#endif
1688
1689	movl	P_LINK(%eax),%ecx	# unlink from front of process q
1690	movl	P_LINK(%ecx),%edx
1691	movl	%edx,P_LINK(%eax)
1692	movl	P_RLINK(%ecx),%eax
1693	movl	%eax,P_RLINK(%edx)
1694
1695	cmpl	P_LINK(%ecx),%esi	# q empty
1696	je	3f
1697	btsl	%ebx,%edi		# nope, set to indicate full
16983:
1699	movl	%edi,_whichqs		# update q status
1700
1701	movl	$0,%eax
1702	movl	%eax,_want_resched
1703
1704#ifdef	DIAGNOSTIC
1705	cmpl	%eax,P_WCHAN(%ecx)
1706	jne	badsw
1707	cmpb	$ SRUN,P_STAT(%ecx)
1708	jne	badsw
1709#endif
1710
1711	movl	%eax,P_RLINK(%ecx) /* isolate process to run */
1712	movl	P_ADDR(%ecx),%edx
1713	movl	PCB_CR3(%edx),%ebx
1714
1715	/* switch address space */
1716	movl	%ebx,%cr3
1717
1718	/* restore context */
1719	movl	PCB_EBX(%edx), %ebx
1720	movl	PCB_ESP(%edx), %esp
1721	movl	PCB_EBP(%edx), %ebp
1722	movl	PCB_ESI(%edx), %esi
1723	movl	PCB_EDI(%edx), %edi
1724	movl	PCB_EIP(%edx), %eax
1725	movl	%eax, (%esp)
1726
1727	movl	PCB_CMAP2(%edx),%eax	# get temporary map
1728	movl	%eax,_CMAP2		# reload temporary map PTE
1729
1730	movl	%ecx,_curproc		# into next process
1731	movl	%edx,_curpcb
1732
1733	pushl	%edx			# save p to return
1734/*
1735 * XXX - 0.0 forgot to save it - is that why this was commented out in 0.1?
1736 * I think restoring the cpl is unnecessary, but we must turn off the cli
1737 * now that spl*() don't do it as a side affect.
1738 */
1739	pushl	PCB_IML(%edx)
1740	sti
1741	SHOW_STI
1742#if 0
1743	call	_splx
1744#endif
1745	addl	$4,%esp
1746/*
1747 * XXX - 0.0 gets here via swtch_to_inactive().  I think 0.1 gets here in the
1748 * same way.  Better return a value.
1749 */
1750	popl	%eax			# return (p);
1751	ret
1752
1753ENTRY(mvesp)
1754	movl	%esp,%eax
1755	ret
1756/*
1757 * struct proc *swtch_to_inactive(p) ; struct proc *p;
1758 *
1759 * At exit of a process, move off the address space of the
1760 * process and onto a "safe" one. Then, on a temporary stack
1761 * return and run code that disposes of the old state.
1762 * Since this code requires a parameter from the "old" stack,
1763 * pass it back as a return value.
1764 */
1765ENTRY(swtch_to_inactive)
1766	popl	%edx			# old pc
1767	popl	%eax			# arg, our return value
1768	movl	_IdlePTD,%ecx
1769	movl	%ecx,%cr3		# good bye address space
1770 #write buffer?
1771	movl	$tmpstk-4,%esp		# temporary stack, compensated for call
1772	jmp	%edx			# return, execute remainder of cleanup
1773
1774/*
1775 * savectx(pcb, altreturn)
1776 * Update pcb, saving current processor state and arranging
1777 * for alternate return ala longjmp in swtch if altreturn is true.
1778 */
1779ENTRY(savectx)
1780	movl	4(%esp), %ecx
1781	movw	_cpl, %ax
1782	movw	%ax,  PCB_IML(%ecx)
1783	movl	(%esp), %eax
1784	movl	%eax, PCB_EIP(%ecx)
1785	movl	%ebx, PCB_EBX(%ecx)
1786	movl	%esp, PCB_ESP(%ecx)
1787	movl	%ebp, PCB_EBP(%ecx)
1788	movl	%esi, PCB_ESI(%ecx)
1789	movl	%edi, PCB_EDI(%ecx)
1790
1791#ifdef NPX
1792	/*
1793	 * If npxproc == NULL, then the npx h/w state is irrelevant and the
1794	 * state had better already be in the pcb.  This is true for forks
1795	 * but not for dumps (the old book-keeping with FP flags in the pcb
1796	 * always lost for dumps because the dump pcb has 0 flags).
1797	 *
1798	 * If npxproc != NULL, then we have to save the npx h/w state to
1799	 * npxproc's pcb and copy it to the requested pcb, or save to the
1800	 * requested pcb and reload.  Copying is easier because we would
1801	 * have to handle h/w bugs for reloading.  We used to lose the
1802	 * parent's npx state for forks by forgetting to reload.
1803	 */
1804	mov	_npxproc,%eax
1805	testl	%eax,%eax
1806	je	1f
1807
1808	pushl	%ecx
1809	movl	P_ADDR(%eax),%eax
1810	leal	PCB_SAVEFPU(%eax),%eax
1811	pushl	%eax
1812	pushl	%eax
1813	call	_npxsave
1814	popl	%eax
1815	popl	%eax
1816	popl	%ecx
1817
1818	pushl	%ecx
1819	pushl	$108+8*2	/* XXX h/w state size + padding */
1820	leal	PCB_SAVEFPU(%ecx),%ecx
1821	pushl	%ecx
1822	pushl	%eax
1823	call	_bcopy
1824	addl	$12,%esp
1825	popl	%ecx
18261:
1827#endif
1828
1829	movl	_CMAP2, %edx		# save temporary map PTE
1830	movl	%edx, PCB_CMAP2(%ecx)	# in our context
1831
1832	cmpl	$0, 8(%esp)
1833	je	1f
1834	movl	%esp, %edx		# relocate current sp relative to pcb
1835	subl	$_kstack, %edx		#   (sp is relative to kstack):
1836	addl	%edx, %ecx		#   pcb += sp - kstack;
1837	movl	%eax, (%ecx)		# write return pc at (relocated) sp@
1838	# this mess deals with replicating register state gcc hides
1839	movl	12(%esp),%eax
1840	movl	%eax,12(%ecx)
1841	movl	16(%esp),%eax
1842	movl	%eax,16(%ecx)
1843	movl	20(%esp),%eax
1844	movl	%eax,20(%ecx)
1845	movl	24(%esp),%eax
1846	movl	%eax,24(%ecx)
18471:
1848	xorl	%eax, %eax		# return 0
1849	ret
1850
1851/*
1852 * addupc(int pc, struct uprof *up, int ticks):
1853 * update profiling information for the user process.
1854 */
1855ENTRY(addupc)
1856	pushl %ebp
1857	movl %esp,%ebp
1858	movl 12(%ebp),%edx		/* up */
1859	movl 8(%ebp),%eax		/* pc */
1860
1861	subl PR_OFF(%edx),%eax		/* pc -= up->pr_off */
1862	jl L1				/* if (pc < 0) return */
1863
1864	shrl $1,%eax			/* praddr = pc >> 1 */
1865	imull PR_SCALE(%edx),%eax	/* praddr *= up->pr_scale */
1866	shrl $15,%eax			/* praddr = praddr << 15 */
1867	andl $-2,%eax			/* praddr &= ~1 */
1868
1869	cmpl PR_SIZE(%edx),%eax		/* if (praddr > up->pr_size) return */
1870	ja L1
1871
1872/*	addl %eax,%eax			/* praddr -> word offset */
1873	addl PR_BASE(%edx),%eax		/* praddr += up-> pr_base */
1874	movl 16(%ebp),%ecx		/* ticks */
1875
1876	movl _curpcb,%edx
1877	movl $proffault,PCB_ONFAULT(%edx)
1878	addl %ecx,(%eax)		/* storage location += ticks */
1879	movl $0,PCB_ONFAULT(%edx)
1880L1:
1881	leave
1882	ret
1883
1884	ALIGN_TEXT
1885proffault:
1886	/* if we get a fault, then kill profiling all together */
1887	movl $0,PCB_ONFAULT(%edx)	/* squish the fault handler */
1888 	movl 12(%ebp),%ecx
1889	movl $0,PR_SCALE(%ecx)		/* up->pr_scale = 0 */
1890	leave
1891	ret
1892
1893# To be done:
1894ENTRY(astoff)
1895	ret
1896
1897
1898/*****************************************************************************/
1899/* Trap handling                                                             */
1900/*****************************************************************************/
1901/*
1902 * Trap and fault vector routines
1903 *
1904 * XXX - debugger traps are now interrupt gates so at least bdb doesn't lose
1905 * control.  The sti's give the standard losing behaviour for ddb and kgdb.
1906 */
1907#define	IDTVEC(name)	ALIGN_TEXT; .globl _X/**/name; _X/**/name:
1908#define	TRAP(a)		pushl $(a) ; jmp alltraps
1909#ifdef KGDB
1910#  define BPTTRAP(a)	sti; pushl $(a) ; jmp bpttraps
1911#else
1912#  define BPTTRAP(a)	sti; TRAP(a)
1913#endif
1914
1915IDTVEC(div)
1916	pushl $0; TRAP(T_DIVIDE)
1917IDTVEC(dbg)
1918#ifdef BDBTRAP
1919	BDBTRAP(dbg)
1920#endif
1921	pushl $0; BPTTRAP(T_TRCTRAP)
1922IDTVEC(nmi)
1923	pushl $0; TRAP(T_NMI)
1924IDTVEC(bpt)
1925#ifdef BDBTRAP
1926	BDBTRAP(bpt)
1927#endif
1928	pushl $0; BPTTRAP(T_BPTFLT)
1929IDTVEC(ofl)
1930	pushl $0; TRAP(T_OFLOW)
1931IDTVEC(bnd)
1932	pushl $0; TRAP(T_BOUND)
1933IDTVEC(ill)
1934	pushl $0; TRAP(T_PRIVINFLT)
1935IDTVEC(dna)
1936	pushl $0; TRAP(T_DNA)
1937IDTVEC(dble)
1938	TRAP(T_DOUBLEFLT)
1939	/*PANIC("Double Fault");*/
1940IDTVEC(fpusegm)
1941	pushl $0; TRAP(T_FPOPFLT)
1942IDTVEC(tss)
1943	TRAP(T_TSSFLT)
1944	/*PANIC("TSS not valid");*/
1945IDTVEC(missing)
1946	TRAP(T_SEGNPFLT)
1947IDTVEC(stk)
1948	TRAP(T_STKFLT)
1949IDTVEC(prot)
1950	TRAP(T_PROTFLT)
1951IDTVEC(page)
1952	TRAP(T_PAGEFLT)
1953IDTVEC(rsvd)
1954	pushl $0; TRAP(T_RESERVED)
1955IDTVEC(fpu)
1956#ifdef NPX
1957	/*
1958	 * Handle like an interrupt so that we can call npxintr to clear the
1959	 * error.  It would be better to handle npx interrupts as traps but
1960	 * this is difficult for nested interrupts.
1961	 */
1962	pushl	$0		/* dummy error code */
1963	pushl	$T_ASTFLT
1964	pushal
1965	nop			/* silly, the bug is for popal and it only
1966				 * bites when the next instruction has a
1967				 * complicated address mode */
1968	pushl	%ds
1969	pushl	%es		/* now the stack frame is a trap frame */
1970	movl	$KDSEL,%eax
1971	movl	%ax,%ds
1972	movl	%ax,%es
1973	pushl	_cpl
1974	pushl	$0		/* dummy unit to finish building intr frame */
1975	incl	_cnt+V_TRAP
1976	call	_npxintr
1977	jmp	doreti
1978#else
1979	pushl $0; TRAP(T_ARITHTRAP)
1980#endif
1981	/* 17 - 31 reserved for future exp */
1982IDTVEC(rsvd0)
1983	pushl $0; TRAP(17)
1984IDTVEC(rsvd1)
1985	pushl $0; TRAP(18)
1986IDTVEC(rsvd2)
1987	pushl $0; TRAP(19)
1988IDTVEC(rsvd3)
1989	pushl $0; TRAP(20)
1990IDTVEC(rsvd4)
1991	pushl $0; TRAP(21)
1992IDTVEC(rsvd5)
1993	pushl $0; TRAP(22)
1994IDTVEC(rsvd6)
1995	pushl $0; TRAP(23)
1996IDTVEC(rsvd7)
1997	pushl $0; TRAP(24)
1998IDTVEC(rsvd8)
1999	pushl $0; TRAP(25)
2000IDTVEC(rsvd9)
2001	pushl $0; TRAP(26)
2002IDTVEC(rsvd10)
2003	pushl $0; TRAP(27)
2004IDTVEC(rsvd11)
2005	pushl $0; TRAP(28)
2006IDTVEC(rsvd12)
2007	pushl $0; TRAP(29)
2008IDTVEC(rsvd13)
2009	pushl $0; TRAP(30)
2010IDTVEC(rsvd14)
2011	pushl $0; TRAP(31)
2012
2013	SUPERALIGN_TEXT
2014alltraps:
2015	pushal
2016	nop
2017	pushl	%ds
2018	pushl	%es
2019	movl	$KDSEL,%eax
2020	movl	%ax,%ds
2021	movl	%ax,%es
2022calltrap:
2023	incl	_cnt+V_TRAP
2024	call	_trap
2025	/*
2026	 * Return through doreti to handle ASTs.  Have to change trap frame
2027	 * to interrupt frame.
2028	 */
2029	movl	$T_ASTFLT,4+4+32(%esp)	/* new trap type (err code not used) */
2030	pushl	_cpl
2031	pushl	$0			/* dummy unit */
2032	jmp	doreti
2033
2034#ifdef KGDB
2035/*
2036 * This code checks for a kgdb trap, then falls through
2037 * to the regular trap code.
2038 */
2039	SUPERALIGN_TEXT
2040bpttraps:
2041	pushal
2042	nop
2043	pushl	%es
2044	pushl	%ds
2045	movl	$KDSEL,%eax
2046	movl	%ax,%ds
2047	movl	%ax,%es
2048	testb	$SEL_RPL_MASK,TRAPF_CS_OFF(%esp)
2049					# non-kernel mode?
2050	jne	calltrap		# yes
2051	call	_kgdb_trap_glue
2052	jmp	calltrap
2053#endif
2054
2055/*
2056 * Call gate entry for syscall
2057 */
2058 	SUPERALIGN_TEXT
2059IDTVEC(syscall)
2060	pushfl	# only for stupid carry bit and more stupid wait3 cc kludge
2061		# XXX - also for direction flag (bzero, etc. clear it)
2062	pushal	# only need eax,ecx,edx - trap resaves others
2063	nop
2064	movl	$KDSEL,%eax		# switch to kernel segments
2065	movl	%ax,%ds
2066	movl	%ax,%es
2067	incl	_cnt+V_SYSCALL	# kml 3/25/93
2068	call	_syscall
2069	/*
2070	 * Return through doreti to handle ASTs.  Have to change syscall frame
2071	 * to interrupt frame.
2072	 *
2073	 * XXX - we should have set up the frame earlier to avoid the
2074	 * following popal/pushal (not much can be done to avoid shuffling
2075	 * the flags).  Consistent frames would simplify things all over.
2076	 */
2077	movl	32+0(%esp),%eax	/* old flags, shuffle to above cs:eip */
2078	movl	32+4(%esp),%ebx	/* `int' frame should have been ef, eip, cs */
2079	movl	32+8(%esp),%ecx
2080	movl	%ebx,32+0(%esp)
2081	movl	%ecx,32+4(%esp)
2082	movl	%eax,32+8(%esp)
2083	popal
2084	nop
2085	pushl	$0		/* dummy error code */
2086	pushl	$T_ASTFLT
2087	pushal
2088	nop
2089	movl	__udatasel,%eax	/* switch back to user segments */
2090	pushl	%eax		/* XXX - better to preserve originals? */
2091	pushl	%eax
2092	pushl	_cpl
2093	pushl	$0
2094	jmp	doreti
2095
2096
2097/*****************************************************************************/
2098/* include generated interrupt vectors and ISA intr code                     */
2099/*****************************************************************************/
2100
2101#include "i386/isa/vector.s"
2102#include "i386/isa/icu.s"
2103