locore.s revision 5
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#define	ALIGN_DATA	.align	2
85#define	ALIGN_TEXT	.align	2,0x90	/* 4-byte boundaries, NOP-filled */
86#define	SUPERALIGN_TEXT	.align	4,0x90	/* 16-byte boundaries better for 486 */
87
88/* NB: NOP now preserves registers so NOPs can be inserted anywhere */
89/* XXX: NOP and FASTER_NOP are misleadingly named */
90#ifdef BROKEN_HARDWARE_AND_OR_SOFTWARE /* XXX - rarely necessary */
91#define	FASTER_NOP	pushl %eax ; inb $0x84,%al ; popl %eax
92#define	NOP	pushl %eax ; inb $0x84,%al ; inb $0x84,%al ; popl %eax
93#else
94#define	FASTER_NOP
95#define	NOP
96#endif
97
98/*
99 * PTmap is recursive pagemap at top of virtual address space.
100 * Within PTmap, the page directory can be found (third indirection).
101 */
102	.set	PDRPDROFF,0x3F7		# Page dir index of Page dir
103	.globl	_PTmap, _PTD, _PTDpde, _Sysmap
104	.set	_PTmap,0xFDC00000
105	.set	_PTD,0xFDFF7000
106	.set	_Sysmap,0xFDFF8000
107	.set	_PTDpde,0xFDFF7000+4*PDRPDROFF
108
109/*
110 * APTmap, APTD is the alternate recursive pagemap.
111 * It's used when modifying another process's page tables.
112 */
113	.set	APDRPDROFF,0x3FE		# Page dir index of Page dir
114	.globl	_APTmap, _APTD, _APTDpde
115	.set	_APTmap,0xFF800000
116	.set	_APTD,0xFFBFE000
117	.set	_APTDpde,0xFDFF7000+4*APDRPDROFF
118
119/*
120 * Access to each processes kernel stack is via a region of
121 * per-process address space (at the beginning), immediatly above
122 * the user process stack.
123 */
124	.set	_kstack, USRSTACK
125	.globl	_kstack
126	.set	PPDROFF,0x3F6
127	.set	PPTEOFF,0x400-UPAGES	# 0x3FE
128
129#define	ENTRY(name) \
130	.globl _/**/name; ALIGN_TEXT; _/**/name:
131#define	ALTENTRY(name)	ENTRY(name)
132
133/*
134 * Initialization
135 */
136	.data
137	.globl	_cpu,_cold,_boothowto,_bootdev,_cyloffset,_atdevbase,_atdevphys
138_cpu:	.long	0		# are we 386, 386sx, or 486
139_cold:	.long	1		# cold till we are not
140_atdevbase:	.long	0	# location of start of iomem in virtual
141_atdevphys:	.long	0	# location of device mapping ptes (phys)
142
143	.globl	_IdlePTD, _KPTphys
144_IdlePTD:	.long	0
145_KPTphys:	.long	0
146
147	.space 512
148tmpstk:
149	.text
150	.globl	start
151start:	movw	$0x1234,%ax
152	movw	%ax,0x472	# warm boot
153	jmp	1f
154	.space	0x500		# skip over warm boot shit
155
156	/*
157	 * pass parameters on stack (howto, bootdev, unit, cyloffset)
158	 * note: (%esp) is return address of boot
159	 * ( if we want to hold onto /boot, it's physical %esp up to _end)
160	 */
161
162 1:	movl	4(%esp),%eax
163	movl	%eax,_boothowto-SYSTEM
164	movl	8(%esp),%eax
165	movl	%eax,_bootdev-SYSTEM
166	movl	12(%esp),%eax
167	movl	%eax, _cyloffset-SYSTEM
168
169	/*
170	 * Finished with old stack; load new %esp now instead of later so
171	 * we can trace this code without having to worry about the trace
172	 * trap clobbering the memory test or the zeroing of the bss+bootstrap
173	 * page tables.
174	 *
175	 * XXX - wdboot clears the bss after testing that this is safe.
176	 * This is too wasteful - memory below 640K is scarce.  The boot
177	 * program should check:
178	 *	text+data <= &stack_variable - more_space_for_stack
179	 *	text+data+bss+pad+space_for_page_tables <= end_of_memory
180	 * Oops, the gdt is in the carcass of the boot program so clearing
181	 * the rest of memory is still not possible.
182	 */
183	movl	$ tmpstk-SYSTEM,%esp	# bootstrap stack end location
184
185#ifdef garbage
186	/* count up memory */
187
188	xorl	%eax,%eax		# start with base memory at 0x0
189	#movl	$ 0xA0000/NBPG,%ecx	# look every 4K up to 640K
190	movl	$ 0xA0,%ecx		# look every 4K up to 640K
1911:	movl	(%eax),%ebx		# save location to check
192	movl	$0xa55a5aa5,(%eax)	# write test pattern
193	/* flush stupid cache here! (with bcopy (0,0,512*1024) ) */
194	cmpl	$0xa55a5aa5,(%eax)	# does not check yet for rollover
195	jne	2f
196	movl	%ebx,(%eax)		# restore memory
197	addl	$ NBPG,%eax
198	loop	1b
1992:	shrl	$12,%eax
200	movl	%eax,_Maxmem-SYSTEM
201
202	movl	$0x100000,%eax		# next, talley remaining memory
203	#movl	$((0xFFF000-0x100000)/NBPG),%ecx
204	movl	$(0xFFF-0x100),%ecx
2051:	movl	(%eax),%ebx		# save location to check
206	movl	$0xa55a5aa5,(%eax)	# write test pattern
207	cmpl	$0xa55a5aa5,(%eax)	# does not check yet for rollover
208	jne	2f
209	movl	%ebx,(%eax)		# restore memory
210	addl	$ NBPG,%eax
211	loop	1b
2122:	shrl	$12,%eax
213	movl	%eax,_Maxmem-SYSTEM
214#endif
215
216/* find end of kernel image */
217	movl	$_end-SYSTEM,%ecx
218	addl	$ NBPG-1,%ecx
219	andl	$~(NBPG-1),%ecx
220	movl	%ecx,%esi
221
222/* clear bss and memory for bootstrap pagetables. */
223	movl	$_edata-SYSTEM,%edi
224	subl	%edi,%ecx
225	addl	$(UPAGES+5)*NBPG,%ecx
226/*
227 * Virtual address space of kernel:
228 *
229 *	text | data | bss | page dir | proc0 kernel stack | usr stk map | Sysmap
230 *			     0               1       2       3             4
231 */
232	xorl	%eax,%eax	# pattern
233	cld
234	rep
235	stosb
236
237	movl	%esi,_IdlePTD-SYSTEM /*physical address of Idle Address space */
238
239#define	fillkpt		\
2401:	movl	%eax,(%ebx)	; \
241	addl	$ NBPG,%eax	; /* increment physical address */ \
242	addl	$4,%ebx		; /* next pte */ \
243	loop	1b		;
244
245/*
246 * Map Kernel
247 * N.B. don't bother with making kernel text RO, as 386
248 * ignores R/W AND U/S bits on kernel access (only v works) !
249 *
250 * First step - build page tables
251 */
252	movl	%esi,%ecx		# this much memory,
253	shrl	$ PGSHIFT,%ecx		# for this many pte s
254	addl	$ UPAGES+4,%ecx		# including our early context
255	movl	$0xa0,%ecx		# XXX - cover debugger pages
256	movl	$PG_V|PG_KW,%eax	#  having these bits set,
257	lea	(4*NBPG)(%esi),%ebx	#   physical address of KPT in proc 0,
258	movl	%ebx,_KPTphys-SYSTEM	#    in the kernel page table,
259	fillkpt
260
261/* map I/O memory map */
262
263	movl	$0x100-0xa0,%ecx	# for this many pte s,
264	movl	$(0xa0000|PG_V|PG_UW),%eax # having these bits set,(perhaps URW?) XXX 06 Aug 92
265	movl	%ebx,_atdevphys-SYSTEM	#   remember phys addr of ptes
266	fillkpt
267
268 /* map proc 0's kernel stack into user page table page */
269
270	movl	$ UPAGES,%ecx		# for this many pte s,
271	lea	(1*NBPG)(%esi),%eax	# physical address in proc 0
272	lea	(SYSTEM)(%eax),%edx
273	movl	%edx,_proc0paddr-SYSTEM  # remember VA for 0th process init
274	orl	$PG_V|PG_KW,%eax	#  having these bits set,
275	lea	(3*NBPG)(%esi),%ebx	# physical address of stack pt in proc 0
276	addl	$(PPTEOFF*4),%ebx
277	fillkpt
278
279/*
280 * Construct a page table directory
281 * (of page directory elements - pde's)
282 */
283	/* install a pde for temporary double map of bottom of VA */
284	lea	(4*NBPG)(%esi),%eax	# physical address of kernel page table
285	orl     $ PG_V|PG_UW,%eax	# pde entry is valid XXX 06 Aug 92
286	movl	%eax,(%esi)		# which is where temp maps!
287
288	/* kernel pde's */
289	movl	$ 3,%ecx		# for this many pde s,
290	lea	(SYSPDROFF*4)(%esi), %ebx	# offset of pde for kernel
291	fillkpt
292
293	/* install a pde recursively mapping page directory as a page table! */
294	movl	%esi,%eax		# phys address of ptd in proc 0
295	orl	$ PG_V|PG_UW,%eax	# pde entry is valid XXX 06 Aug 92
296	movl	%eax, PDRPDROFF*4(%esi)	# which is where PTmap maps!
297
298	/* install a pde to map kernel stack for proc 0 */
299	lea	(3*NBPG)(%esi),%eax	# physical address of pt in proc 0
300	orl	$PG_V|PG_KW,%eax	# pde entry is valid
301	movl	%eax,PPDROFF*4(%esi)	# which is where kernel stack maps!
302
303	/* copy and convert stuff from old gdt and idt for debugger */
304
305	cmpl	$0x0375c339,0x96104	# XXX - debugger signature
306	jne	1f
307	movb	$1,_bdb_exists-SYSTEM
3081:
309	pushal
310	subl	$2*6,%esp
311
312	sgdt	(%esp)
313	movl	2(%esp),%esi		# base address of current gdt
314	movl	$_gdt-SYSTEM,%edi
315	movl	%edi,2(%esp)
316	movl	$8*18/4,%ecx
317	rep				# copy gdt
318	movsl
319	movl	$_gdt-SYSTEM,-8+2(%edi)	# adjust gdt self-ptr
320	movb	$0x92,-8+5(%edi)
321
322	sidt	6(%esp)
323	movl	6+2(%esp),%esi		# base address of current idt
324	movl	8+4(%esi),%eax		# convert dbg descriptor to ...
325	movw	8(%esi),%ax
326	movl	%eax,bdb_dbg_ljmp+1-SYSTEM	# ... immediate offset ...
327	movl	8+2(%esi),%eax
328	movw	%ax,bdb_dbg_ljmp+5-SYSTEM	# ... and selector for ljmp
329	movl	24+4(%esi),%eax		# same for bpt descriptor
330	movw	24(%esi),%ax
331	movl	%eax,bdb_bpt_ljmp+1-SYSTEM
332	movl	24+2(%esi),%eax
333	movw	%ax,bdb_bpt_ljmp+5-SYSTEM
334
335	movl	$_idt-SYSTEM,%edi
336	movl	%edi,6+2(%esp)
337	movl	$8*4/4,%ecx
338	rep				# copy idt
339	movsl
340
341	lgdt	(%esp)
342	lidt	6(%esp)
343
344	addl	$2*6,%esp
345	popal
346
347	/* load base of page directory, and enable mapping */
348	movl	%esi,%eax		# phys address of ptd in proc 0
349 	orl	$ I386_CR3PAT,%eax
350	movl	%eax,%cr3		# load ptd addr into mmu
351	movl	%cr0,%eax		# get control word
352#ifdef USE_486_WRITE_PROTECT
353	orl	$CR0_PE|CR0_PG|CR0_WP,%eax	# and let s page!
354#else
355	orl	$CR0_PE|CR0_PG,%eax	# and let s page!
356#endif
357	movl	%eax,%cr0		# NOW!
358
359	pushl	$begin				# jump to high mem!
360	ret
361
362begin: /* now running relocated at SYSTEM where the system is linked to run */
363
364	.globl _Crtat
365	movl	_Crtat,%eax
366	subl	$0xfe0a0000,%eax
367	movl	_atdevphys,%edx	# get pte PA
368	subl	_KPTphys,%edx	# remove base of ptes, now have phys offset
369	shll	$ PGSHIFT-2,%edx  # corresponding to virt offset
370	addl	$ SYSTEM,%edx	# add virtual base
371	movl	%edx, _atdevbase
372	addl	%eax,%edx
373	movl	%edx,_Crtat
374
375	/* set up bootstrap stack */
376	movl	$ _kstack+UPAGES*NBPG-4*12,%esp	# bootstrap stack end location
377	xorl	%eax,%eax		# mark end of frames
378	movl	%eax,%ebp
379	movl	_proc0paddr, %eax
380	movl	%esi, PCB_CR3(%eax)
381
382	lea	7*NBPG(%esi),%esi	# skip past stack.
383	pushl	%esi
384
385	/* relocate debugger gdt entries */
386
387	movl	$_gdt+8*9,%eax		# adjust slots 9-17
388	movl	$9,%ecx
389reloc_gdt:
390	movb	$0xfe,7(%eax)		# top byte of base addresses, was 0,
391	addl	$8,%eax			# now SYSTEM>>24
392	loop	reloc_gdt
393
394	cmpl	$0,_bdb_exists
395	je	1f
396	int	$3
3971:
398
399	call	_init386		# wire 386 chip for unix operation
400
401	movl	$0,_PTD
402	call 	_main
403	popl	%esi
404
405	.globl	__ucodesel,__udatasel
406	movl	__ucodesel,%eax
407	movl	__udatasel,%ecx
408	# build outer stack frame
409	pushl	%ecx		# user ss
410	pushl	$ USRSTACK	# user esp
411	pushl	%eax		# user cs
412	pushl	$0		# user ip
413	movl	%cx,%ds
414	movl	%cx,%es
415	movl	%ax,%fs		# double map cs to fs
416	movl	%cx,%gs		# and ds to gs
417	lret	# goto user!
418
419	pushl	$lretmsg1	/* "should never get here!" */
420	call	_panic
421lretmsg1:
422	.asciz	"lret: toinit\n"
423
424
425	.set	exec,59
426	.set	exit,1
427
428#define	LCALL(x,y)	.byte 0x9a ; .long y; .word x
429/*
430 * Icode is copied out to process 1 to exec /etc/init.
431 * If the exec fails, process 1 exits.
432 */
433ENTRY(icode)
434	# pushl	$argv-_icode	# gas fucks up again
435	movl	$argv,%eax
436	subl	$_icode,%eax
437	pushl	%eax
438
439	# pushl	$init-_icode
440	movl	$init,%eax
441	subl	$_icode,%eax
442	pushl	%eax
443	pushl	%eax	# dummy out rta
444
445	movl	%esp,%ebp
446	movl	$exec,%eax
447	LCALL(0x7,0x0)
448	pushl	%eax
449	movl	$exit,%eax
450	pushl	%eax	# dummy out rta
451	LCALL(0x7,0x0)
452
453init:
454	.asciz	"/sbin/init"
455	ALIGN_DATA
456argv:
457	.long	init+6-_icode		# argv[0] = "init" ("/sbin/init" + 6)
458	.long	eicode-_icode		# argv[1] follows icode after copyout
459	.long	0
460eicode:
461
462	.globl	_szicode
463_szicode:
464	.long	_szicode-_icode
465
466ENTRY(sigcode)
467	call	12(%esp)
468	lea	28(%esp),%eax	# scp (the call may have clobbered the
469				# copy at 8(%esp))
470				# XXX - use genassym
471	pushl	%eax
472	pushl	%eax		# junk to fake return address
473	movl	$103,%eax	# sigreturn()
474	LCALL(0x7,0)		# enter kernel with args on stack
475	hlt			# never gets here
476
477	.globl	_szsigcode
478_szsigcode:
479	.long	_szsigcode-_sigcode
480
481	/*
482	 * Support routines for GCC
483	 */
484ENTRY(__udivsi3)
485	movl 4(%esp),%eax
486	xorl %edx,%edx
487	divl 8(%esp)
488	ret
489
490ENTRY(__divsi3)
491	movl 4(%esp),%eax
492	cltd
493	idivl 8(%esp)
494	ret
495
496	/*
497	 * I/O bus instructions via C
498	 */
499ENTRY(inb)
500	movl	4(%esp),%edx
501	subl	%eax,%eax	# clr eax
502	NOP
503	inb	%dx,%al
504	ret
505
506
507ENTRY(inw)
508	movl	4(%esp),%edx
509	subl	%eax,%eax	# clr eax
510	NOP
511	inw	%dx,%ax
512	ret
513
514
515ENTRY(rtcin)
516	movl	4(%esp),%eax
517	outb	%al,$0x70
518	subl	%eax,%eax	# clr eax
519	inb	$0x71,%al
520	ret
521
522ENTRY(outb)
523	movl	4(%esp),%edx
524	NOP
525	movl	8(%esp),%eax
526	outb	%al,%dx
527	NOP
528	ret
529
530ENTRY(outw)
531	movl	4(%esp),%edx
532	NOP
533	movl	8(%esp),%eax
534	outw	%ax,%dx
535	NOP
536	ret
537
538	/*
539	 * void bzero(void *base, u_int cnt)
540	 */
541
542ENTRY(bzero)
543	pushl	%edi
544	movl	8(%esp),%edi
545	movl	12(%esp),%ecx
546	xorl	%eax,%eax
547	shrl	$2,%ecx
548	cld
549	rep
550	stosl
551	movl	12(%esp),%ecx
552	andl	$3,%ecx
553	rep
554	stosb
555	popl	%edi
556	ret
557
558	/*
559	 * fillw (pat,base,cnt)
560	 */
561
562ENTRY(fillw)
563	pushl	%edi
564	movl	8(%esp),%eax
565	movl	12(%esp),%edi
566	movl	16(%esp),%ecx
567	cld
568	rep
569	stosw
570	popl	%edi
571	ret
572
573ENTRY(bcopyb)
574	pushl	%esi
575	pushl	%edi
576	movl	12(%esp),%esi
577	movl	16(%esp),%edi
578	movl	20(%esp),%ecx
579	cmpl	%esi,%edi	/* potentially overlapping? */
580	jnb	1f
581	cld			/* nope, copy forwards */
582	rep
583	movsb
584	popl	%edi
585	popl	%esi
586	ret
587
588	ALIGN_TEXT
5891:
590	addl	%ecx,%edi	/* copy backwards. */
591	addl	%ecx,%esi
592	std
593	decl	%edi
594	decl	%esi
595	rep
596	movsb
597	popl	%edi
598	popl	%esi
599	cld
600	ret
601
602ENTRY(bcopyw)
603	pushl	%esi
604	pushl	%edi
605	movl	12(%esp),%esi
606	movl	16(%esp),%edi
607	movl	20(%esp),%ecx
608	cmpl	%esi,%edi	/* potentially overlapping? */
609	jnb	1f
610	cld			/* nope, copy forwards */
611	shrl	$1,%ecx		/* copy by 16-bit words */
612	rep
613	movsw
614	adc	%ecx,%ecx	/* any bytes left? */
615	rep
616	movsb
617	popl	%edi
618	popl	%esi
619	ret
620
621	ALIGN_TEXT
6221:
623	addl	%ecx,%edi	/* copy backwards */
624	addl	%ecx,%esi
625	std
626	andl	$1,%ecx		/* any fractional bytes? */
627	decl	%edi
628	decl	%esi
629	rep
630	movsb
631	movl	20(%esp),%ecx	/* copy remainder by 16-bit words */
632	shrl	$1,%ecx
633	decl	%esi
634	decl	%edi
635	rep
636	movsw
637	popl	%edi
638	popl	%esi
639	cld
640	ret
641
642ENTRY(bcopyx)
643	movl	16(%esp),%eax
644	cmpl	$2,%eax
645	je	_bcopyw
646	cmpl	$4,%eax
647	jne	_bcopyb
648	/*
649	 * Fall through to bcopy.  ENTRY() provides harmless fill bytes.
650	 */
651
652	/*
653	 * (ov)bcopy (src,dst,cnt)
654	 *  ws@tools.de     (Wolfgang Solfrank, TooLs GmbH) +49-228-985800
655	 *  Changed by bde to not bother returning %eax = 0.
656	 */
657
658ENTRY(ovbcopy)
659ENTRY(bcopy)
660	pushl	%esi
661	pushl	%edi
662	movl	12(%esp),%esi
663	movl	16(%esp),%edi
664	movl	20(%esp),%ecx
665	cmpl	%esi,%edi	/* potentially overlapping? */
666	jnb	1f
667	cld			/* nope, copy forwards */
668	shrl	$2,%ecx		/* copy by 32-bit words */
669	rep
670	movsl
671	movl	20(%esp),%ecx
672	andl	$3,%ecx		/* any bytes left? */
673	rep
674	movsb
675	popl	%edi
676	popl	%esi
677	ret
678
679	ALIGN_TEXT
6801:
681	addl	%ecx,%edi	/* copy backwards */
682	addl	%ecx,%esi
683	std
684	andl	$3,%ecx		/* any fractional bytes? */
685	decl	%edi
686	decl	%esi
687	rep
688	movsb
689	movl	20(%esp),%ecx	/* copy remainder by 32-bit words */
690	shrl	$2,%ecx
691	subl	$3,%esi
692	subl	$3,%edi
693	rep
694	movsl
695	popl	%edi
696	popl	%esi
697	cld
698	ret
699
700#ifdef notdef
701ENTRY(copyout)
702	movl	_curpcb, %eax
703	movl	$cpyflt, PCB_ONFAULT(%eax) # in case we page/protection violate
704	pushl	%esi
705	pushl	%edi
706	pushl	%ebx
707	movl	16(%esp), %esi
708	movl	20(%esp), %edi
709	movl	24(%esp), %ebx
710
711 				/* first, check to see if "write fault" */
7121:	movl	%edi, %eax
713#ifdef notyet
714	shrl	$IDXSHIFT, %eax	/* fetch pte associated with address */
715	andb	$0xfc, %al
716	movl	_PTmap(%eax), %eax
717
718	andb	$7, %al		/* if we are the one case that won't trap... */
719	cmpb	$5, %al
720	jne	2f
721				/* ... then simulate the trap! */
722	pushl	%edi
723	call	_trapwrite	/* trapwrite(addr) */
724	popl	%edx
725
726	cmpl	$0, %eax	/* if not ok, return */
727	jne	cpyflt
728				/* otherwise, continue with reference */
7292:
730	movl	%edi, %eax	/* calculate remainder this pass */
731	andl	$0xfffff000, %eax
732	movl	$NBPG, %ecx
733	subl	%eax, %ecx
734	cmpl	%ecx, %ebx
735	jle	3f
736	movl	%ebx, %ecx
7373:	subl	%ecx, %ebx
738	movl	%ecx, %edx
739#else
740	movl	%ebx, %ecx
741	movl	%ebx, %edx
742#endif
743
744	shrl	$2,%ecx			/* movem */
745	cld
746	rep
747	movsl
748	movl	%edx, %ecx		/* don't depend on ecx here! */
749	andl	$3, %ecx
750	rep
751	movsb
752
753#ifdef notyet
754	cmpl	$0, %ebx
755	jl	1b
756#endif
757
758	popl	%ebx
759	popl	%edi
760	popl	%esi
761	xorl	%eax,%eax
762	movl	_curpcb,%edx
763	movl	%eax,PCB_ONFAULT(%edx)
764	ret
765
766ENTRY(copyin)
767	movl	_curpcb,%eax
768	movl	$cpyflt,PCB_ONFAULT(%eax) # in case we page/protection violate
769	pushl	%esi
770	pushl	%edi
771	pushl	%ebx		# XXX - not used, but affects stack offsets
772	movl	12(%esp),%esi
773	movl	16(%esp),%edi
774	movl	20(%esp),%ecx
775	shrl	$2,%ecx
776	cld
777	rep
778	movsl
779	movl	20(%esp),%ecx
780	andl	$3,%ecx
781	rep
782	movsb
783	popl	%ebx
784	popl	%edi
785	popl	%esi
786	xorl	%eax,%eax
787	movl	_curpcb,%edx
788	movl	%eax,PCB_ONFAULT(%edx)
789	ret
790
791	ALIGN_TEXT
792cpyflt:
793	popl	%ebx
794	popl	%edi
795	popl	%esi
796	movl	_curpcb,%edx
797	movl	$0,PCB_ONFAULT(%edx)
798	movl	$ EFAULT,%eax
799	ret
800#else
801ENTRY(copyout)
802	movl	_curpcb,%eax
803	movl	$cpyflt,PCB_ONFAULT(%eax) # in case we page/protection violate
804	pushl	%esi
805	pushl	%edi
806	movl	12(%esp),%esi
807	movl	16(%esp),%edi
808	movl	20(%esp),%ecx
809	shrl	$2,%ecx
810	cld
811	rep
812	movsl
813	movl	20(%esp),%ecx
814	andl	$3,%ecx
815	rep
816	movsb
817	popl	%edi
818	popl	%esi
819	xorl	%eax,%eax
820	movl	_curpcb,%edx
821	movl	%eax,PCB_ONFAULT(%edx)
822	ret
823
824ENTRY(copyin)
825	movl	_curpcb,%eax
826	movl	$cpyflt,PCB_ONFAULT(%eax) # in case we page/protection violate
827	pushl	%esi
828	pushl	%edi
829	movl	12(%esp),%esi
830	movl	16(%esp),%edi
831	movl	20(%esp),%ecx
832	shrl	$2,%ecx
833	cld
834	rep
835	movsl
836	movl	20(%esp),%ecx
837	andl	$3,%ecx
838	rep
839	movsb
840	popl	%edi
841	popl	%esi
842	xorl	%eax,%eax
843	movl	_curpcb,%edx
844	movl	%eax,PCB_ONFAULT(%edx)
845	ret
846
847	ALIGN_TEXT
848cpyflt: popl	%edi
849	popl	%esi
850	movl	_curpcb,%edx
851	movl	$0,PCB_ONFAULT(%edx)
852	movl	$ EFAULT,%eax
853	ret
854
855#endif
856
857	# insb(port,addr,cnt)
858ENTRY(insb)
859	pushl	%edi
860	movw	8(%esp),%dx
861	movl	12(%esp),%edi
862	movl	16(%esp),%ecx
863	cld
864	NOP
865	rep
866	insb
867	NOP
868	movl	%edi,%eax
869	popl	%edi
870	ret
871
872	# insw(port,addr,cnt)
873ENTRY(insw)
874	pushl	%edi
875	movw	8(%esp),%dx
876	movl	12(%esp),%edi
877	movl	16(%esp),%ecx
878	cld
879	NOP
880	.byte 0x66,0xf2,0x6d	# rep insw
881	NOP
882	movl	%edi,%eax
883	popl	%edi
884	ret
885
886	# outsw(port,addr,cnt)
887ENTRY(outsw)
888	pushl	%esi
889	movw	8(%esp),%dx
890	movl	12(%esp),%esi
891	movl	16(%esp),%ecx
892	cld
893	NOP
894	.byte 0x66,0xf2,0x6f	# rep outsw
895	NOP
896	movl	%esi,%eax
897	popl	%esi
898	ret
899
900	# outsb(port,addr,cnt)
901ENTRY(outsb)
902	pushl	%esi
903	movw	8(%esp),%dx
904	movl	12(%esp),%esi
905	movl	16(%esp),%ecx
906	cld
907	NOP
908	rep
909	outsb
910	NOP
911	movl	%esi,%eax
912	popl	%esi
913	ret
914
915	/*
916	 * void lgdt(struct region_descriptor *rdp);
917	 */
918ENTRY(lgdt)
919	/* reload the descriptor table */
920	movl	4(%esp),%eax
921	lgdt	(%eax)
922	/* flush the prefetch q */
923	jmp	1f
924	nop
9251:
926	/* reload "stale" selectors */
927	movl	$KDSEL,%eax
928	movl	%ax,%ds
929	movl	%ax,%es
930	movl	%ax,%ss
931
932	/* reload code selector by turning return into intersegmental return */
933	movl	(%esp),%eax
934	pushl	%eax
935	# movl	$KCSEL,4(%esp)
936	movl	$8,4(%esp)
937	lret
938
939	/*
940	 * void lidt(struct region_descriptor *rdp);
941	 */
942ENTRY(lidt)
943	movl	4(%esp),%eax
944	lidt	(%eax)
945	ret
946
947	/*
948	 * void lldt(u_short sel)
949	 */
950ENTRY(lldt)
951	lldt	4(%esp)
952	ret
953
954	/*
955	 * void ltr(u_short sel)
956	 */
957ENTRY(ltr)
958	ltr	4(%esp)
959	ret
960
961	/*
962	 * void lcr3(caddr_t cr3)
963	 */
964	ALIGN_TEXT
965ENTRY(load_cr3)
966ALTENTRY(lcr3)
967	movl	4(%esp),%eax
968 	orl	$ I386_CR3PAT,%eax
969	movl	%eax,%cr3
970	ret
971
972	# tlbflush()
973ENTRY(tlbflush)
974	movl	%cr3,%eax
975 	orl	$ I386_CR3PAT,%eax
976	movl	%eax,%cr3
977	ret
978
979	# lcr0(cr0)
980ENTRY(lcr0)
981ALTENTRY(load_cr0)
982	movl	4(%esp),%eax
983	movl	%eax,%cr0
984	ret
985
986	# rcr0()
987ENTRY(rcr0)
988	movl	%cr0,%eax
989	ret
990
991	# rcr2()
992ENTRY(rcr2)
993	movl	%cr2,%eax
994	ret
995
996	# rcr3()
997ENTRY(_cr3)
998ALTENTRY(rcr3)
999	movl	%cr3,%eax
1000	ret
1001
1002	# ssdtosd(*ssdp,*sdp)
1003ENTRY(ssdtosd)
1004	pushl	%ebx
1005	movl	8(%esp),%ecx
1006	movl	8(%ecx),%ebx
1007	shll	$16,%ebx
1008	movl	(%ecx),%edx
1009	roll	$16,%edx
1010	movb	%dh,%bl
1011	movb	%dl,%bh
1012	rorl	$8,%ebx
1013	movl	4(%ecx),%eax
1014	movw	%ax,%dx
1015	andl	$0xf0000,%eax
1016	orl	%eax,%ebx
1017	movl	12(%esp),%ecx
1018	movl	%edx,(%ecx)
1019	movl	%ebx,4(%ecx)
1020	popl	%ebx
1021	ret
1022
1023/*
1024 * {fu,su},{byte,word}
1025 */
1026ALTENTRY(fuiword)
1027ENTRY(fuword)
1028	movl	_curpcb,%ecx
1029	movl	$fusufault,PCB_ONFAULT(%ecx)
1030	movl	4(%esp),%edx
1031	.byte	0x65		# use gs
1032	movl	(%edx),%eax
1033	movl	$0,PCB_ONFAULT(%ecx)
1034	ret
1035
1036ENTRY(fusword)
1037	movl	_curpcb,%ecx
1038	movl	$fusufault,PCB_ONFAULT(%ecx) #in case we page/protection violate
1039	movl	4(%esp),%edx
1040	.byte	0x65		# use gs
1041	movzwl	(%edx),%eax
1042	movl	$0,PCB_ONFAULT(%ecx)
1043	ret
1044
1045ALTENTRY(fuibyte)
1046ENTRY(fubyte)
1047	movl	_curpcb,%ecx
1048	movl	$fusufault,PCB_ONFAULT(%ecx) #in case we page/protection violate
1049	movl	4(%esp),%edx
1050	.byte	0x65		# use gs
1051	movzbl	(%edx),%eax
1052	movl	$0,PCB_ONFAULT(%ecx)
1053	ret
1054
1055	ALIGN_TEXT
1056fusufault:
1057	movl	_curpcb,%ecx
1058	xorl	%eax,%eax
1059	movl	%eax,PCB_ONFAULT(%ecx) #in case we page/protection violate
1060	decl	%eax
1061	ret
1062
1063ALTENTRY(suiword)
1064ENTRY(suword)
1065	movl	_curpcb,%ecx
1066	movl	$fusufault,PCB_ONFAULT(%ecx) #in case we page/protection violate
1067	movl	4(%esp),%edx
1068	movl	8(%esp),%eax
1069
1070#ifdef notdef
1071	shrl	$IDXSHIFT, %edx	/* fetch pte associated with address */
1072	andb	$0xfc, %dl
1073	movl	_PTmap(%edx), %edx
1074
1075	andb	$7, %dl		/* if we are the one case that won't trap... */
1076	cmpb	$5 , %edx
1077	jne	1f
1078				/* ... then simulate the trap! */
1079	pushl	%edi
1080	call	_trapwrite	/* trapwrite(addr) */
1081	popl	%edx
1082	cmpl	$0, %eax	/* if not ok, return */
1083	jne	fusufault
1084	movl	8(%esp),%eax	/* otherwise, continue with reference */
10851:
1086	movl	4(%esp),%edx
1087#endif
1088	.byte	0x65		# use gs
1089	movl	%eax,(%edx)
1090	xorl	%eax,%eax
1091	movl	%eax,PCB_ONFAULT(%ecx) #in case we page/protection violate
1092	ret
1093
1094ENTRY(susword)
1095	movl	_curpcb,%ecx
1096	movl	$fusufault,PCB_ONFAULT(%ecx) #in case we page/protection violate
1097	movl	4(%esp),%edx
1098	movl	8(%esp),%eax
1099#ifdef notdef
1100shrl	$IDXSHIFT, %edx	/* calculate pte address */
1101andb	$0xfc, %dl
1102movl	_PTmap(%edx), %edx
1103andb	$7, %edx	/* if we are the one case that won't trap... */
1104cmpb	$5 , %edx
1105jne	1f
1106/* ..., then simulate the trap! */
1107	pushl	%edi
1108	call	_trapwrite	/* trapwrite(addr) */
1109	popl	%edx
1110movl	_curpcb, %ecx	# restore trashed registers
1111cmpl	$0, %eax	/* if not ok, return */
1112jne	fusufault
1113movl	8(%esp),%eax
11141: movl	4(%esp),%edx
1115#endif
1116	.byte	0x65		# use gs
1117	movw	%ax,(%edx)
1118	xorl	%eax,%eax
1119	movl	%eax,PCB_ONFAULT(%ecx) #in case we page/protection violate
1120	ret
1121
1122ALTENTRY(suibyte)
1123ENTRY(subyte)
1124	movl	_curpcb,%ecx
1125	movl	$fusufault,PCB_ONFAULT(%ecx) #in case we page/protection violate
1126	movl	4(%esp),%edx
1127	movl	8(%esp),%eax
1128#ifdef notdef
1129shrl	$IDXSHIFT, %edx	/* calculate pte address */
1130andb	$0xfc, %dl
1131movl	_PTmap(%edx), %edx
1132andb	$7, %edx	/* if we are the one case that won't trap... */
1133cmpb	$5 , %edx
1134jne	1f
1135/* ..., then simulate the trap! */
1136	pushl	%edi
1137	call	_trapwrite	/* trapwrite(addr) */
1138	popl	%edx
1139movl	_curpcb, %ecx	# restore trashed registers
1140cmpl	$0, %eax	/* if not ok, return */
1141jne	fusufault
1142movl	8(%esp),%eax
11431: movl	4(%esp),%edx
1144#endif
1145	.byte	0x65		# use gs
1146	movb	%eax,(%edx)
1147	xorl	%eax,%eax
1148	movl	%eax,PCB_ONFAULT(%ecx) #in case we page/protection violate
1149	ret
1150
1151ENTRY(setjmp)
1152	movl	4(%esp),%eax
1153	movl	%ebx,  (%eax)		# save ebx
1154	movl	%esp, 4(%eax)		# save esp
1155	movl	%ebp, 8(%eax)		# save ebp
1156	movl	%esi,12(%eax)		# save esi
1157	movl	%edi,16(%eax)		# save edi
1158	movl	(%esp),%edx		# get rta
1159	movl	%edx,20(%eax)		# save eip
1160	xorl	%eax,%eax		# return (0);
1161	ret
1162
1163ENTRY(longjmp)
1164	movl	4(%esp),%eax
1165	movl	  (%eax),%ebx		# restore ebx
1166	movl	 4(%eax),%esp		# restore esp
1167	movl	 8(%eax),%ebp		# restore ebp
1168	movl	12(%eax),%esi		# restore esi
1169	movl	16(%eax),%edi		# restore edi
1170	movl	20(%eax),%edx		# get rta
1171	movl	%edx,(%esp)		# put in return frame
1172	xorl	%eax,%eax		# return (1);
1173	incl	%eax
1174	ret
1175/*
1176 * The following primitives manipulate the run queues.
1177 * _whichqs tells which of the 32 queues _qs
1178 * have processes in them.  Setrq puts processes into queues, Remrq
1179 * removes them from queues.  The running process is on no queue,
1180 * other processes are on a queue related to p->p_pri, divided by 4
1181 * actually to shrink the 0-127 range of priorities into the 32 available
1182 * queues.
1183 */
1184
1185	.globl	_whichqs,_qs,_cnt,_panic
1186	.comm	_noproc,4
1187	.comm	_runrun,4
1188
1189/*
1190 * Setrq(p)
1191 *
1192 * Call should be made at spl6(), and p->p_stat should be SRUN
1193 */
1194ENTRY(setrq)
1195	movl	4(%esp),%eax
1196	cmpl	$0,P_RLINK(%eax)	# should not be on q already
1197	je	set1
1198	pushl	$set2
1199	call	_panic
1200set1:
1201	movzbl	P_PRI(%eax),%edx
1202	shrl	$2,%edx
1203	btsl	%edx,_whichqs		# set q full bit
1204	shll	$3,%edx
1205	addl	$_qs,%edx		# locate q hdr
1206	movl	%edx,P_LINK(%eax)	# link process on tail of q
1207	movl	P_RLINK(%edx),%ecx
1208	movl	%ecx,P_RLINK(%eax)
1209	movl	%eax,P_RLINK(%edx)
1210	movl	%eax,P_LINK(%ecx)
1211	ret
1212
1213set2:	.asciz	"setrq"
1214
1215/*
1216 * Remrq(p)
1217 *
1218 * Call should be made at spl6().
1219 */
1220ENTRY(remrq)
1221	movl	4(%esp),%eax
1222	movzbl	P_PRI(%eax),%edx
1223	shrl	$2,%edx
1224	btrl	%edx,_whichqs		# clear full bit, panic if clear already
1225	jb	rem1
1226	pushl	$rem3
1227	call	_panic
1228rem1:
1229	pushl	%edx
1230	movl	P_LINK(%eax),%ecx	# unlink process
1231	movl	P_RLINK(%eax),%edx
1232	movl	%edx,P_RLINK(%ecx)
1233	movl	P_RLINK(%eax),%ecx
1234	movl	P_LINK(%eax),%edx
1235	movl	%edx,P_LINK(%ecx)
1236	popl	%edx
1237	movl	$_qs,%ecx
1238	shll	$3,%edx
1239	addl	%edx,%ecx
1240	cmpl	P_LINK(%ecx),%ecx	# q still has something?
1241	je	rem2
1242	shrl	$3,%edx			# yes, set bit as still full
1243	btsl	%edx,_whichqs
1244rem2:
1245	movl	$0,P_RLINK(%eax)	# zap reverse link to indicate off list
1246	ret
1247
1248rem3:	.asciz	"remrq"
1249sw0:	.asciz	"swtch"
1250
1251/*
1252 * When no processes are on the runq, Swtch branches to idle
1253 * to wait for something to come ready.
1254 */
1255	.globl	Idle
1256	ALIGN_TEXT
1257Idle:
1258sti_for_idle:
1259	sti
1260	SHOW_STI
1261	ALIGN_TEXT
1262idle:
1263	call	_spl0
1264	cmpl	$0,_whichqs
1265	jne	sw1
1266	hlt				# wait for interrupt
1267	jmp	idle
1268
1269	SUPERALIGN_TEXT	/* so profiling doesn't lump Idle with swtch().. */
1270badsw:
1271	pushl	$sw0
1272	call	_panic
1273	/*NOTREACHED*/
1274
1275/*
1276 * Swtch()
1277 */
1278ENTRY(swtch)
1279
1280	incl	_cnt+V_SWTCH
1281
1282	/* switch to new process. first, save context as needed */
1283
1284	movl	_curproc,%ecx
1285
1286	/* if no process to save, don't bother */
1287	testl	%ecx,%ecx
1288	je	sw1
1289
1290	movl	P_ADDR(%ecx),%ecx
1291
1292	movl	(%esp),%eax		# Hardware registers
1293	movl	%eax, PCB_EIP(%ecx)
1294	movl	%ebx, PCB_EBX(%ecx)
1295	movl	%esp, PCB_ESP(%ecx)
1296	movl	%ebp, PCB_EBP(%ecx)
1297	movl	%esi, PCB_ESI(%ecx)
1298	movl	%edi, PCB_EDI(%ecx)
1299
1300#ifdef NPX
1301	/* have we used fp, and need a save? */
1302	mov	_curproc,%eax
1303	cmp	%eax,_npxproc
1304	jne	1f
1305	pushl	%ecx			/* h/w bugs make saving complicated */
1306	leal	PCB_SAVEFPU(%ecx),%eax
1307	pushl	%eax
1308	call	_npxsave		/* do it in a big C function */
1309	popl	%eax
1310	popl	%ecx
13111:
1312#endif
1313
1314	movl	_CMAP2,%eax		# save temporary map PTE
1315	movl	%eax,PCB_CMAP2(%ecx)	# in our context
1316	movl	$0,_curproc		#  out of process
1317
1318	# movw	_cpl, %ax
1319	# movw	%ax, PCB_IML(%ecx)	# save ipl
1320
1321	/* save is done, now choose a new process or idle */
1322sw1:
1323	cli
1324	SHOW_CLI
1325	movl	_whichqs,%edi
13262:
1327	# XXX - bsf is sloow
1328	bsfl	%edi,%eax		# find a full q
1329	je	sti_for_idle		# if none, idle
1330	# XX update whichqs?
1331swfnd:
1332	btrl	%eax,%edi		# clear q full status
1333	jnb	2b		# if it was clear, look for another
1334	movl	%eax,%ebx		# save which one we are using
1335
1336	shll	$3,%eax
1337	addl	$_qs,%eax		# select q
1338	movl	%eax,%esi
1339
1340#ifdef	DIAGNOSTIC
1341	cmpl	P_LINK(%eax),%eax # linked to self? (e.g. not on list)
1342	je	badsw			# not possible
1343#endif
1344
1345	movl	P_LINK(%eax),%ecx	# unlink from front of process q
1346	movl	P_LINK(%ecx),%edx
1347	movl	%edx,P_LINK(%eax)
1348	movl	P_RLINK(%ecx),%eax
1349	movl	%eax,P_RLINK(%edx)
1350
1351	cmpl	P_LINK(%ecx),%esi	# q empty
1352	je	3f
1353	btsl	%ebx,%edi		# nope, set to indicate full
13543:
1355	movl	%edi,_whichqs		# update q status
1356
1357	movl	$0,%eax
1358	movl	%eax,_want_resched
1359
1360#ifdef	DIAGNOSTIC
1361	cmpl	%eax,P_WCHAN(%ecx)
1362	jne	badsw
1363	cmpb	$ SRUN,P_STAT(%ecx)
1364	jne	badsw
1365#endif
1366
1367	movl	%eax,P_RLINK(%ecx) /* isolate process to run */
1368	movl	P_ADDR(%ecx),%edx
1369	movl	PCB_CR3(%edx),%ebx
1370
1371	/* switch address space */
1372	movl	%ebx,%cr3
1373
1374	/* restore context */
1375	movl	PCB_EBX(%edx), %ebx
1376	movl	PCB_ESP(%edx), %esp
1377	movl	PCB_EBP(%edx), %ebp
1378	movl	PCB_ESI(%edx), %esi
1379	movl	PCB_EDI(%edx), %edi
1380	movl	PCB_EIP(%edx), %eax
1381	movl	%eax, (%esp)
1382
1383	movl	PCB_CMAP2(%edx),%eax	# get temporary map
1384	movl	%eax,_CMAP2		# reload temporary map PTE
1385
1386	movl	%ecx,_curproc		# into next process
1387	movl	%edx,_curpcb
1388
1389	pushl	%edx			# save p to return
1390/*
1391 * XXX - 0.0 forgot to save it - is that why this was commented out in 0.1?
1392 * I think restoring the cpl is unnecessary, but we must turn off the cli
1393 * now that spl*() don't do it as a side affect.
1394 */
1395	pushl	PCB_IML(%edx)
1396	sti
1397	SHOW_STI
1398#if 0
1399	call	_splx
1400#endif
1401	addl	$4,%esp
1402/*
1403 * XXX - 0.0 gets here via swtch_to_inactive().  I think 0.1 gets here in the
1404 * same way.  Better return a value.
1405 */
1406	popl	%eax			# return (p);
1407	ret
1408
1409ENTRY(mvesp)
1410	movl	%esp,%eax
1411	ret
1412/*
1413 * struct proc *swtch_to_inactive(p) ; struct proc *p;
1414 *
1415 * At exit of a process, move off the address space of the
1416 * process and onto a "safe" one. Then, on a temporary stack
1417 * return and run code that disposes of the old state.
1418 * Since this code requires a parameter from the "old" stack,
1419 * pass it back as a return value.
1420 */
1421ENTRY(swtch_to_inactive)
1422	popl	%edx			# old pc
1423	popl	%eax			# arg, our return value
1424	movl	_IdlePTD,%ecx
1425	movl	%ecx,%cr3		# good bye address space
1426 #write buffer?
1427	movl	$tmpstk-4,%esp		# temporary stack, compensated for call
1428	jmp	%edx			# return, execute remainder of cleanup
1429
1430/*
1431 * savectx(pcb, altreturn)
1432 * Update pcb, saving current processor state and arranging
1433 * for alternate return ala longjmp in swtch if altreturn is true.
1434 */
1435ENTRY(savectx)
1436	movl	4(%esp), %ecx
1437	movw	_cpl, %ax
1438	movw	%ax,  PCB_IML(%ecx)
1439	movl	(%esp), %eax
1440	movl	%eax, PCB_EIP(%ecx)
1441	movl	%ebx, PCB_EBX(%ecx)
1442	movl	%esp, PCB_ESP(%ecx)
1443	movl	%ebp, PCB_EBP(%ecx)
1444	movl	%esi, PCB_ESI(%ecx)
1445	movl	%edi, PCB_EDI(%ecx)
1446
1447#ifdef NPX
1448	/*
1449	 * If npxproc == NULL, then the npx h/w state is irrelevant and the
1450	 * state had better already be in the pcb.  This is true for forks
1451	 * but not for dumps (the old book-keeping with FP flags in the pcb
1452	 * always lost for dumps because the dump pcb has 0 flags).
1453	 *
1454	 * If npxproc != NULL, then we have to save the npx h/w state to
1455	 * npxproc's pcb and copy it to the requested pcb, or save to the
1456	 * requested pcb and reload.  Copying is easier because we would
1457	 * have to handle h/w bugs for reloading.  We used to lose the
1458	 * parent's npx state for forks by forgetting to reload.
1459	 */
1460	mov	_npxproc,%eax
1461	testl	%eax,%eax
1462	je	1f
1463
1464	pushl	%ecx
1465	movl	P_ADDR(%eax),%eax
1466	leal	PCB_SAVEFPU(%eax),%eax
1467	pushl	%eax
1468	pushl	%eax
1469	call	_npxsave
1470	popl	%eax
1471	popl	%eax
1472	popl	%ecx
1473
1474	pushl	%ecx
1475	pushl	$108+8*2	/* XXX h/w state size + padding */
1476	leal	PCB_SAVEFPU(%ecx),%ecx
1477	pushl	%ecx
1478	pushl	%eax
1479	call	_bcopy
1480	addl	$12,%esp
1481	popl	%ecx
14821:
1483#endif
1484
1485	movl	_CMAP2, %edx		# save temporary map PTE
1486	movl	%edx, PCB_CMAP2(%ecx)	# in our context
1487
1488	cmpl	$0, 8(%esp)
1489	je	1f
1490	movl	%esp, %edx		# relocate current sp relative to pcb
1491	subl	$_kstack, %edx		#   (sp is relative to kstack):
1492	addl	%edx, %ecx		#   pcb += sp - kstack;
1493	movl	%eax, (%ecx)		# write return pc at (relocated) sp@
1494	# this mess deals with replicating register state gcc hides
1495	movl	12(%esp),%eax
1496	movl	%eax,12(%ecx)
1497	movl	16(%esp),%eax
1498	movl	%eax,16(%ecx)
1499	movl	20(%esp),%eax
1500	movl	%eax,20(%ecx)
1501	movl	24(%esp),%eax
1502	movl	%eax,24(%ecx)
15031:
1504	xorl	%eax, %eax		# return 0
1505	ret
1506
1507/*
1508 * addupc(int pc, struct uprof *up, int ticks):
1509 * update profiling information for the user process.
1510 */
1511
1512ENTRY(addupc)
1513	pushl %ebp
1514	movl %esp,%ebp
1515	movl 12(%ebp),%edx		/* up */
1516	movl 8(%ebp),%eax		/* pc */
1517
1518	subl PR_OFF(%edx),%eax		/* pc -= up->pr_off */
1519	jl L1				/* if (pc < 0) return */
1520
1521	shrl $1,%eax			/* praddr = pc >> 1 */
1522	imull PR_SCALE(%edx),%eax	/* praddr *= up->pr_scale */
1523	shrl $15,%eax			/* praddr = praddr << 15 */
1524	andl $-2,%eax			/* praddr &= ~1 */
1525
1526	cmpl PR_SIZE(%edx),%eax		/* if (praddr > up->pr_size) return */
1527	ja L1
1528
1529/*	addl %eax,%eax			/* praddr -> word offset */
1530	addl PR_BASE(%edx),%eax		/* praddr += up-> pr_base */
1531	movl 16(%ebp),%ecx		/* ticks */
1532
1533	movl _curpcb,%edx
1534	movl $proffault,PCB_ONFAULT(%edx)
1535	addl %ecx,(%eax)		/* storage location += ticks */
1536	movl $0,PCB_ONFAULT(%edx)
1537L1:
1538	leave
1539	ret
1540
1541	ALIGN_TEXT
1542proffault:
1543	/* if we get a fault, then kill profiling all together */
1544	movl $0,PCB_ONFAULT(%edx)	/* squish the fault handler */
1545 	movl 12(%ebp),%ecx
1546	movl $0,PR_SCALE(%ecx)		/* up->pr_scale = 0 */
1547	leave
1548	ret
1549
1550 # To be done:
1551 ENTRY(astoff)
1552	ret
1553
1554	.data
1555	ALIGN_DATA
1556	.globl	_cyloffset, _curpcb
1557_cyloffset:	.long	0
1558	.globl	_proc0paddr
1559_proc0paddr:	.long	0
1560LF:	.asciz "swtch %x"
1561	ALIGN_DATA
1562
1563#if 0
1564#define	PANIC(msg)	xorl %eax,%eax; movl %eax,_waittime; pushl 1f; \
1565			call _panic; MSG(msg)
1566#define	PRINTF(n,msg)	pushal ; nop ; pushl 1f; call _printf; MSG(msg) ; \
1567			 popl %eax ; popal
1568#define	MSG(msg)	.data; 1: .asciz msg; ALIGN_DATA; .text
1569#endif /* 0 */
1570
1571/*
1572 * Trap and fault vector routines
1573 *
1574 * XXX - debugger traps are now interrupt gates so at least bdb doesn't lose
1575 * control.  The sti's give the standard losing behaviour for ddb and kgdb.
1576 */
1577#define	IDTVEC(name)	ALIGN_TEXT; .globl _X/**/name; _X/**/name:
1578#define	TRAP(a)		pushl $(a) ; jmp alltraps
1579#ifdef KGDB
1580#define	BPTTRAP(a)	sti; pushl $(a) ; jmp bpttraps
1581#else
1582#define	BPTTRAP(a)	sti; TRAP(a)
1583#endif
1584
1585	.text
1586IDTVEC(div)
1587	pushl $0; TRAP(T_DIVIDE)
1588IDTVEC(dbg)
1589#ifdef BDBTRAP
1590	BDBTRAP(dbg)
1591#endif
1592	pushl $0; BPTTRAP(T_TRCTRAP)
1593IDTVEC(nmi)
1594	pushl $0; TRAP(T_NMI)
1595IDTVEC(bpt)
1596#ifdef BDBTRAP
1597	BDBTRAP(bpt)
1598#endif
1599	pushl $0; BPTTRAP(T_BPTFLT)
1600IDTVEC(ofl)
1601	pushl $0; TRAP(T_OFLOW)
1602IDTVEC(bnd)
1603	pushl $0; TRAP(T_BOUND)
1604IDTVEC(ill)
1605	pushl $0; TRAP(T_PRIVINFLT)
1606IDTVEC(dna)
1607	pushl $0; TRAP(T_DNA)
1608IDTVEC(dble)
1609	TRAP(T_DOUBLEFLT)
1610	/*PANIC("Double Fault");*/
1611IDTVEC(fpusegm)
1612	pushl $0; TRAP(T_FPOPFLT)
1613IDTVEC(tss)
1614	TRAP(T_TSSFLT)
1615	/*PANIC("TSS not valid");*/
1616IDTVEC(missing)
1617	TRAP(T_SEGNPFLT)
1618IDTVEC(stk)
1619	TRAP(T_STKFLT)
1620IDTVEC(prot)
1621	TRAP(T_PROTFLT)
1622IDTVEC(page)
1623	TRAP(T_PAGEFLT)
1624IDTVEC(rsvd)
1625	pushl $0; TRAP(T_RESERVED)
1626IDTVEC(fpu)
1627#ifdef NPX
1628	/*
1629	 * Handle like an interrupt so that we can call npxintr to clear the
1630	 * error.  It would be better to handle npx interrupts as traps but
1631	 * this is difficult for nested interrupts.
1632	 */
1633	pushl	$0		/* dummy error code */
1634	pushl	$T_ASTFLT
1635	pushal
1636	nop			/* silly, the bug is for popal and it only
1637				 * bites when the next instruction has a
1638				 * complicated address mode */
1639	pushl	%ds
1640	pushl	%es		/* now the stack frame is a trap frame */
1641	movl	$KDSEL,%eax
1642	movl	%ax,%ds
1643	movl	%ax,%es
1644	pushl	_cpl
1645	pushl	$0		/* dummy unit to finish building intr frame */
1646	incl	_cnt+V_TRAP
1647	call	_npxintr
1648	jmp	doreti
1649#else
1650	pushl $0; TRAP(T_ARITHTRAP)
1651#endif
1652	/* 17 - 31 reserved for future exp */
1653IDTVEC(rsvd0)
1654	pushl $0; TRAP(17)
1655IDTVEC(rsvd1)
1656	pushl $0; TRAP(18)
1657IDTVEC(rsvd2)
1658	pushl $0; TRAP(19)
1659IDTVEC(rsvd3)
1660	pushl $0; TRAP(20)
1661IDTVEC(rsvd4)
1662	pushl $0; TRAP(21)
1663IDTVEC(rsvd5)
1664	pushl $0; TRAP(22)
1665IDTVEC(rsvd6)
1666	pushl $0; TRAP(23)
1667IDTVEC(rsvd7)
1668	pushl $0; TRAP(24)
1669IDTVEC(rsvd8)
1670	pushl $0; TRAP(25)
1671IDTVEC(rsvd9)
1672	pushl $0; TRAP(26)
1673IDTVEC(rsvd10)
1674	pushl $0; TRAP(27)
1675IDTVEC(rsvd11)
1676	pushl $0; TRAP(28)
1677IDTVEC(rsvd12)
1678	pushl $0; TRAP(29)
1679IDTVEC(rsvd13)
1680	pushl $0; TRAP(30)
1681IDTVEC(rsvd14)
1682	pushl $0; TRAP(31)
1683
1684	SUPERALIGN_TEXT
1685alltraps:
1686	pushal
1687	nop
1688	pushl	%ds
1689	pushl	%es
1690	movl	$KDSEL,%eax
1691	movl	%ax,%ds
1692	movl	%ax,%es
1693calltrap:
1694	incl	_cnt+V_TRAP
1695	call	_trap
1696	/*
1697	 * Return through doreti to handle ASTs.  Have to change trap frame
1698	 * to interrupt frame.
1699	 */
1700	movl	$T_ASTFLT,4+4+32(%esp)	/* new trap type (err code not used) */
1701	pushl	_cpl
1702	pushl	$0			/* dummy unit */
1703	jmp	doreti
1704
1705#ifdef KGDB
1706/*
1707 * This code checks for a kgdb trap, then falls through
1708 * to the regular trap code.
1709 */
1710	ALIGN_TEXT
1711bpttraps:
1712	pushal
1713	nop
1714	pushl	%es
1715	pushl	%ds
1716	movl	$KDSEL,%eax
1717	movl	%ax,%ds
1718	movl	%ax,%es
1719	testb	$SEL_RPL_MASK,TRAPF_CS_OFF(%esp)
1720					# non-kernel mode?
1721	jne	calltrap		# yes
1722	call	_kgdb_trap_glue
1723	jmp	calltrap
1724#endif
1725
1726/*
1727 * Call gate entry for syscall
1728 */
1729
1730	SUPERALIGN_TEXT
1731IDTVEC(syscall)
1732	pushfl	# only for stupid carry bit and more stupid wait3 cc kludge
1733		# XXX - also for direction flag (bzero, etc. clear it)
1734	pushal	# only need eax,ecx,edx - trap resaves others
1735	nop
1736	movl	$KDSEL,%eax		# switch to kernel segments
1737	movl	%ax,%ds
1738	movl	%ax,%es
1739	incl	_cnt+V_SYSCALL  # kml 3/25/93
1740	call	_syscall
1741	/*
1742	 * Return through doreti to handle ASTs.  Have to change syscall frame
1743	 * to interrupt frame.
1744	 *
1745	 * XXX - we should have set up the frame earlier to avoid the
1746	 * following popal/pushal (not much can be done to avoid shuffling
1747	 * the flags).  Consistent frames would simplify things all over.
1748	 */
1749	movl	32+0(%esp),%eax	/* old flags, shuffle to above cs:eip */
1750	movl	32+4(%esp),%ebx	/* `int' frame should have been ef, eip, cs */
1751	movl	32+8(%esp),%ecx
1752	movl	%ebx,32+0(%esp)
1753	movl	%ecx,32+4(%esp)
1754	movl	%eax,32+8(%esp)
1755	popal
1756	nop
1757	pushl	$0		/* dummy error code */
1758	pushl	$T_ASTFLT
1759	pushal
1760	nop
1761	movl	__udatasel,%eax	/* switch back to user segments */
1762	push	%eax		/* XXX - better to preserve originals? */
1763	push	%eax
1764	pushl	_cpl
1765	pushl	$0
1766	jmp	doreti
1767
1768ENTRY(htonl)
1769ENTRY(ntohl)
1770	movl	4(%esp),%eax
1771#ifdef i486
1772	/* XXX */
1773	/* Since Gas 1.38 does not grok bswap this has been coded as the
1774	 * equivalent bytes.  This can be changed back to bswap when we
1775	 * upgrade to a newer version of Gas */
1776	/* bswap	%eax */
1777	.byte 	0x0f
1778	.byte	0xc8
1779#else
1780	xchgb	%al,%ah
1781	roll	$16,%eax
1782	xchgb	%al,%ah
1783#endif
1784	ret
1785
1786ENTRY(htons)
1787ENTRY(ntohs)
1788	movzwl	4(%esp),%eax
1789	xchgb	%al,%ah
1790	ret
1791
1792#ifdef SHOW_A_LOT
1793
1794/*
1795 * 'show_bits' was too big when defined as a macro.  The line length for some
1796 * enclosing macro was too big for gas.  Perhaps the code would have blown
1797 * the cache anyway.
1798 */
1799
1800	ALIGN_TEXT
1801show_bits:
1802	pushl	%eax
1803	SHOW_BIT(0)
1804	SHOW_BIT(1)
1805	SHOW_BIT(2)
1806	SHOW_BIT(3)
1807	SHOW_BIT(4)
1808	SHOW_BIT(5)
1809	SHOW_BIT(6)
1810	SHOW_BIT(7)
1811	SHOW_BIT(8)
1812	SHOW_BIT(9)
1813	SHOW_BIT(10)
1814	SHOW_BIT(11)
1815	SHOW_BIT(12)
1816	SHOW_BIT(13)
1817	SHOW_BIT(14)
1818	SHOW_BIT(15)
1819	popl	%eax
1820	ret
1821
1822	.data
1823bit_colors:
1824	.byte	GREEN,RED,0,0
1825	.text
1826
1827#endif /* SHOW_A_LOT */
1828
1829#include "i386/isa/vector.s"
1830#include "i386/isa/icu.s"
1831