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