btx.S revision 52827
1#
2# Copyright (c) 1998 Robert Nordier
3# All rights reserved.
4#
5# Redistribution and use in source and binary forms are freely
6# permitted provided that the above copyright notice and this
7# paragraph and the following disclaimer are duplicated in all
8# such forms.
9#
10# This software is provided "AS IS" and without any express or
11# implied warranties, including, without limitation, the implied
12# warranties of merchantability and fitness for a particular
13# purpose.
14#
15
16# $FreeBSD: head/sys/boot/pc98/btx/btx/btx.S 52827 1999-11-03 08:32:03Z nyan $
17
18#
19# Memory layout.
20#
21		.set MEM_BTX,0x1000		# Start of BTX memory
22		.set MEM_ESP0,0x1800		# Supervisor stack
23		.set MEM_BUF,0x1800		# Scratch buffer
24		.set MEM_ESP1,0x1e00		# Link stack
25		.set MEM_IDT,0x1e00		# IDT
26		.set MEM_TSS,0x1f98		# TSS
27		.set MEM_MAP,0x2000		# I/O bit map
28		.set MEM_DIR,0x4000		# Page directory
29		.set MEM_TBL,0x5000		# Page tables
30		.set MEM_ORG,0x9000		# BTX code
31		.set MEM_USR,0xa000		# Start of user memory
32#
33# Paging control.
34#
35		.set PAG_SIZ,0x1000		# Page size
36		.set PAG_CNT,0x1000		# Pages to map
37#
38# Segment selectors.
39#
40		.set SEL_SCODE,0x8		# Supervisor code
41		.set SEL_SDATA,0x10		# Supervisor data
42		.set SEL_RCODE,0x18		# Real mode code
43		.set SEL_RDATA,0x20		# Real mode data
44		.set SEL_UCODE,0x28|3		# User code
45		.set SEL_UDATA,0x30|3		# User data
46		.set SEL_TSS,0x38		# TSS
47#
48# Task state segment fields.
49#
50		.set TSS_ESP0,0x4		# PL 0 ESP
51		.set TSS_SS0,0x8		# PL 0 SS
52		.set TSS_ESP1,0xc		# PL 1 ESP
53		.set TSS_MAP,0x66		# I/O bit map base
54#
55# System calls.
56#
57		.set SYS_EXIT,0x0		# Exit
58		.set SYS_EXEC,0x1		# Exec
59#
60# V86 constants.
61#
62		.set V86_FLG,0x208eff		# V86 flag mask
63		.set V86_STK,0x400		# V86 stack allowance
64#
65# Dump format control bytes.
66#
67		.set DMP_X16,0x1		# Word
68		.set DMP_X32,0x2		# Long
69		.set DMP_MEM,0x4		# Memory
70		.set DMP_EOL,0x8		# End of line
71#
72# Screen defaults and assumptions.
73#
74.`ifdef' PC98
75		.set SCR_MAT,0xe1		# Mode/attribute
76.else
77		.set SCR_MAT,0x7		# Mode/attribute
78.endif
79		.set SCR_COL,0x50		# Columns per row
80		.set SCR_ROW,0x19		# Rows per screen
81#
82# BIOS Data Area locations.
83#
84.`ifdef' PC98
85		.set BDA_MEM,0xa1501		# Free memory
86		.set BDA_POS,0xa153e		# Cursor position
87.else
88		.set BDA_MEM,0x413		# Free memory
89		.set BDA_SCR,0x449		# Video mode
90		.set BDA_POS,0x450		# Cursor position
91.endif
92#
93# Derivations, for brevity.
94#
95		.set _ESP0H,MEM_ESP0>>0x8	# Byte 1 of ESP0
96		.set _ESP1H,MEM_ESP1>>0x8	# Byte 1 of ESP1
97		.set _TSSIO,MEM_MAP-MEM_TSS	# TSS I/O base
98		.set _TSSLM,MEM_DIR-MEM_TSS-1	# TSS limit
99		.set _IDTLM,MEM_TSS-MEM_IDT-1	# IDT limit
100#
101# Code segment.
102#
103		.globl start
104start:						# Start of code
105#
106# BTX header.
107#
108btx_hdr:	.byte 0xeb			# Machine ID
109		.byte 0xe			# Header size
110		.ascii "BTX"			# Magic
111		.byte 0x1			# Major version
112		.byte 0x1			# Minor version
113		.byte 0x0			# Flags
114		.word PAG_CNT-MEM_ORG>>0xc	# Paging control
115		.word break-start		# Text size
116		.long 0x0			# Entry address
117#
118# Initialization routine.
119#
120init:		cli				# Disable interrupts
121		xorl %eax,%eax			# Zero/segment
122		movl %ax,%ss			# Set up
123		movwir(MEM_ESP0,_sp)		#  stack
124		movl %ax,%es			# Address
125		movl %ax,%ds			#  data
126		pushw $0x2			# Clear
127		popfw				#  flags
128#
129# Initialize memory.
130#
131		movwir(MEM_IDT,_di)		# Memory to initialize
132		movwir((MEM_ORG-MEM_IDT)/2,_cx) # Words to zero
133		pushl %edi			# Save
134		rep				# Zero-fill
135		stosl				#  memory
136		popl %edi			# Restore
137#
138# Create IDT.
139#
140		movwir(idtctl,_si)		# Control string
141init.1: 	lodsb				# Get entry
142		cwde				#  count
143		xchgl %eax,%ecx 		#  as word
144		jecxz init.4			# If done
145		lodsb				# Get segment
146		xchgl %eax,%edx 		#  P:DPL:type
147		lodsl				# Get control
148		xchgl %eax,%ebx 		#  set
149		lodsl				# Get handler offset
150		movb $SEL_SCODE,%dh		# Segment selector
151init.2: 	shrl %ebx			# Handle this int?
152		jnc init.3			# No
153		movwr0(_ax,_di_)		# Set handler offset
154		movbr1(_dh,0x2,_di_)		#  and selector
155		movbr1(_dl,0x5,_di_)		# Set P:DPL:type
156		addwia(0x4)			# Next handler
157init.3: 	leaw1r(0x8,_di_,_di)		# Next entry
158		loop init.2			# Till set done
159		jmp init.1			# Continue
160#
161# Initialize TSS.
162#
163init.4: 	movbi1(_ESP0H,TSS_ESP0+1,_di_)	# Set ESP0
164		movbi1(SEL_SDATA,TSS_SS0,_di_)	# Set SS0
165		movbi1(_ESP1H,TSS_ESP1+1,_di_)	# Set ESP1
166		movbi1(_TSSIO,TSS_MAP,_di_)	# Set I/O bit map base
167ifdef(`PAGING',`
168#
169# Create page directory.
170#
171		xorw %dx,%dx			# Page
172		movb $PAG_SIZ>>0x8,%dh		#  size
173		xorw %ax,%ax			# Zero
174		movwir(MEM_DIR,_di)		# Page directory
175		movb $PAG_CNT>>0xa,%cl		# Entries
176		movwir(MEM_TBL|0x7,_ax) 	# First entry
177init.5: 	stosw				# Write entry
178		addl %edx,%eax			# To next
179		loop init.5			# Till done
180#
181# Create page tables.
182#
183		movwir(MEM_TBL,_di)		# Page table
184		movb $PAG_CNT>>0x8,%ch		# Entries
185		xorl %eax,%eax			# Start address
186init.6: 	movb $0x7,%al			# Set U:W:P flags
187		cmpwmr(btx_hdr+0x8,_cx) 	# Standard user page?
188		jb init.7			# Yes
189		cmpwir(PAG_CNT-MEM_BTX>>0xc,_cx)# BTX memory?
190		jae init.7			# No or first page
191		andb $~0x2,%al			# Clear W flag
192		cmpwir(PAG_CNT-MEM_USR>>0xc,_cx)# User page zero?
193		jne init.7			# No
194		tstbim(0x80,btx_hdr+0x7)	# Unmap it?
195		jz init.7			# No
196		andb $~0x1,%al			# Clear P flag
197init.7: 	stosw				# Set entry
198		addw %dx,%ax			# Next address
199		loop init.6			# Till done
200')
201#
202# Bring up the system.
203#
204		movwir(0x2820,_bx)		# Set protected mode
205		callwi(setpic)			#  IRQ offsets
206		lidtwm(idtdesc) 		# Set IDT
207ifdef(`PAGING',`
208		xorw %ax,%ax			# Set base
209		movb $MEM_DIR>>0x8,%ah		#  of page
210		movl %eax,%cr3			#  directory
211')
212		lgdtwm(gdtdesc) 		# Set GDT
213		movl %cr0,%eax			# Switch to
214ifdef(`PAGING',`
215		o16				#  protected mode
216		orl $0x80000001,%eax            #  and enable paging
217',`
218		o16				#  protected mode
219		orl $0x01,%eax			#
220')
221		movl %eax,%cr0			#
222		jmpfwi(SEL_SCODE,init.8)	# To 32-bit code
223init.8: 	xorl %ecx,%ecx			# Zero
224		movb $SEL_SDATA,%cl		# To 32-bit
225		movl %cx,%ss			#  stack
226#
227# Launch user task.
228#
229		movb $SEL_TSS,%cl		# Set task
230		ltrl %ecx			#  register
231		movl $MEM_USR,%edx		# User base address
232		movzwl %ss:BDA_MEM,%eax 	# Get free memory
233.`ifdef' PC98
234		andl $0x7,%eax
235		incl %eax
236		shll $0x11,%eax			# To bytes
237.else
238		shll $0xa,%eax			# To bytes
239.endif
240		subl $0x1000,%eax		# Less arg space
241		subl %edx,%eax			# Less base
242		movb $SEL_UDATA,%cl		# User data selector
243		pushl %ecx			# Set SS
244		pushl %eax			# Set ESP
245		pushl $0x202			# Set flags (IF set)
246		pushl $SEL_UCODE		# Set CS
247		pushl btx_hdr+0xc		# Set EIP
248		pushl %ecx			# Set GS
249		pushl %ecx			# Set FS
250		pushl %ecx			# Set DS
251		pushl %ecx			# Set ES
252		pushl %edx			# Set EAX
253		movb $0x7,%cl			# Set remaining
254init.9:		pushb $0x0			#  general
255		loop init.9			#  registers
256		popa				#  and initialize
257		popl %es			# Initialize
258		popl %ds			#  user
259		popl %fs			#  segment
260		popl %gs			#  registers
261		iret				# To user mode
262#
263# Exit routine.
264#
265exit:		cli				# Disable interrupts
266		movl $MEM_ESP0,%esp		# Clear stack
267ifdef(`PAGING',`
268#
269# Turn off paging.
270#
271		movl %cr0,%eax			# Get CR0
272		andl $~0x80000000,%eax		# Disable
273		movl %eax,%cr0			#  paging
274')
275		xorl %ecx,%ecx			# Zero
276ifdef(`PAGING',`
277		movl %ecx,%cr3			# Flush TLB
278')
279#
280# To 16 bits.
281#
282		o16				# Reload
283		jmpfwi(SEL_RCODE,exit.1)	#  CS
284exit.1: 	movb $SEL_RDATA,%cl		# 16-bit selector
285		movl %cx,%ss			# Reload SS
286		movl %cx,%ds			# Load
287		movl %cx,%es			#  remaining
288		movl %cx,%fs			#  segment
289		movl %cx,%gs			#  registers
290#
291# To real-address mode.
292#
293		decl %eax			# Switch to
294		movl %eax,%cr0			#  real mode
295		jmpfwi(0x0,exit.2)		# Reload CS
296exit.2: 	xorl %eax,%eax			# Real mode segment
297		movl %ax,%ss			# Reload SS
298		movl %ax,%ds			# Address data
299.`ifdef' PC98
300		movwir(0x1008,_bx)		# Set real mode
301.else
302		movwir(0x7008,_bx)		# Set real mode
303.endif
304		callwi(setpic)			#  IRQ offsets
305		lidtwm(ivtdesc) 		# Set IVT
306#
307# Reboot or await reset.
308#
309		sti				# Enable interrupts
310		tstbim(0x1,btx_hdr+0x7)		# Reboot?
311exit.3:		jz exit.3			# No
312.`ifdef' PC98
313		movb $0xa0,%al
314		outb %al,$0x35
315		movb 0,%al
316		outb %al,$0xf0
317exit.4:		jmp exit.4
318.else
319		int $0x19			# BIOS: Reboot
320.endif
321#
322# Set IRQ offsets by reprogramming 8259A PICs.
323#
324.`ifdef' PC98
325setpic: 	inb $0x02,%al			# Save master
326		pushl %eax			#  IMR
327		inb $0x0a,%al			# Save slave
328		pushl %eax			#  IMR
329		movb $0x11,%al			# ICW1 to
330		outb %al,$0x00			#  master,
331		outb %al,$0x08			#  slave
332		movb %bl,%al			# ICW2 to
333		outb %al,$0x02			#  master
334		movb %bh,%al			# ICW2 to
335		outb %al,$0x0a			#  slave
336		movb $0x80,%al			# ICW3 to
337		outb %al,$0x02			#  master
338		movb $0x7,%al			# ICW3 to
339		outb %al,$0x0a			#  slave
340		movb $0x1d,%al			# ICW4 to
341		outb %al,$0x02			#  master,
342		movb $0x9,%al			# ICW4 to
343		outb %al,$0x0a			#  slave
344		popl %eax			# Restore slave
345		outb %al,$0x0a			#  IMR
346		popl %eax			# Restore master
347		outb %al,$0x02			#  IMR
348.else
349setpic: 	inb $0x21,%al			# Save master
350		pushl %eax			#  IMR
351		inb $0xa1,%al			# Save slave
352		pushl %eax			#  IMR
353		movb $0x11,%al			# ICW1 to
354		outb %al,$0x20			#  master,
355		outb %al,$0xa0			#  slave
356		movb %bl,%al			# ICW2 to
357		outb %al,$0x21			#  master
358		movb %bh,%al			# ICW2 to
359		outb %al,$0xa1			#  slave
360		movb $0x4,%al			# ICW3 to
361		outb %al,$0x21			#  master
362		movb $0x2,%al			# ICW3 to
363		outb %al,$0xa1			#  slave
364		movb $0x1,%al			# ICW4 to
365		outb %al,$0x21			#  master,
366		outb %al,$0xa1			#  slave
367		popl %eax			# Restore slave
368		outb %al,$0xa1			#  IMR
369		popl %eax			# Restore master
370		outb %al,$0x21			#  IMR
371.endif
372		ret				# To caller
373#
374# Initiate return from V86 mode to user mode.
375#
376inthlt: 	hlt				# To supervisor mode
377#
378# Exception jump table.
379#
380intx00: 	pushb $0x0			# Int 0x0: #DE
381		jmp ex_noc			# Divide error
382		pushb $0x1			# Int 0x1: #DB
383		jmp ex_noc			# Debug
384		pushb $0x3			# Int 0x3: #BP
385		jmp ex_noc			# Breakpoint
386		pushb $0x4			# Int 0x4: #OF
387		jmp ex_noc			# Overflow
388		pushb $0x5			# Int 0x5: #BR
389		jmp ex_noc			# BOUND range exceeded
390		pushb $0x6			# Int 0x6: #UD
391		jmp ex_noc			# Invalid opcode
392		pushb $0x7			# Int 0x7: #NM
393		jmp ex_noc			# Device not available
394		pushb $0x8			# Int 0x8: #DF
395		jmp except			# Double fault
396		pushb $0xa			# Int 0xa: #TS
397		jmp except			# Invalid TSS
398		pushb $0xb			# Int 0xb: #NP
399		jmp except			# Segment not present
400		pushb $0xc			# Int 0xc: #SS
401		jmp except			# Stack segment fault
402		pushb $0xd			# Int 0xd: #GP
403		jmp ex_v86			# General protection
404		pushb $0xe			# Int 0xe: #PF
405		jmp except			# Page fault
406intx10: 	pushb $0x10			# Int 0x10: #MF
407		jmp ex_noc			# Floating-point error
408#
409# Handle #GP exception.
410#
411ex_v86: 	testb $0x2,0x12(%esp,1) 	# V86 mode?
412		jz except			# No
413		jmp v86mon			# To monitor
414#
415# Save a zero error code.
416#
417ex_noc: 	pushl (%esp,1)			# Duplicate int no
418		movb $0x0,0x4(%esp,1)		# Fake error code
419#
420# Handle exception.
421#
422except: 	cld				# String ops inc
423		pushl %ds			# Save
424		pushl %es			#  most
425		pusha				#  registers
426		movb $0x6,%al			# Push loop count
427		testb $0x2,0x3a(%esp,1) 	# V86 mode?
428		jnz except.1			# Yes
429		pushl %gs			# Set GS
430		pushl %fs			# Set FS
431		pushl %ds			# Set DS
432		pushl %es			# Set ES
433		movb $0x2,%al			# Push loop count
434		cmpw $SEL_SCODE,0x44(%esp,1)	# Supervisor mode?
435		jne except.1			# No
436		pushl %ss			# Set SS
437		leal 0x50(%esp,1),%eax		# Set
438		pushl %eax			#  ESP
439		jmp except.2			# Join common code
440except.1:	pushl 0x50(%esp,1)		# Set GS, FS, DS, ES
441		decb %al			#  (if V86 mode), and
442		jne except.1			#  SS, ESP
443except.2:	pushl $SEL_SDATA		# Set up
444		popl %ds			#  to
445		pushl %ds			#  address
446		popl %es			#  data
447		movl %esp,%ebx			# Stack frame
448		movl $dmpfmt,%esi		# Dump format string
449		movl $MEM_BUF,%edi		# Buffer
450.`ifdef' PC98
451		pushl %eax
452		pushl %edx
453wait.1:
454		inb  $0x60,%al
455		testb $0x04,%al
456		jz   wait.1
457		movb $0xe0,%al
458		outb %al,$0x62
459wait.2:
460		inb  $0x60,%al
461		testb $0x01,%al
462		jz   wait.2
463		xorl %edx,%edx
464		inb  $0x62,%al
465		movb %al,%dl
466		inb  $0x62,%al
467		movb %al,%dh
468		inb  $0x62,%al
469		inb  $0x62,%al
470		inb  $0x62,%al
471		movl %edx,%eax
472		shlw $1,%ax
473		movl $BDA_POS,%edx
474		movw %ax,(%edx)
475		popl  %edx
476		popl  %eax
477.endif
478		pushl %edi			# Dump to
479		call dump			#  buffer
480		popl %esi			#  and
481		call putstr			#  display
482		leal 0x18(%esp,1),%esp		# Discard frame
483		popa				# Restore
484		popl %es			#  registers
485		popl %ds			#  saved
486		cmpb $0x3,(%esp,1)		# Breakpoint?
487		je except.3			# Yes
488		jmp exit			# Exit
489except.3:	leal 0x8(%esp,1),%esp		# Discard err, int no
490		iret				# From interrupt
491#
492# Return to user mode from V86 mode.
493#
494intrtn: 	cld				# String ops inc
495		pushl %ds			# Address
496		popl %es			#  data
497		leal 0x3c(%ebp),%edx		# V86 Segment registers
498		movl MEM_TSS+TSS_ESP1,%esi	# Link stack pointer
499		lodsl				# INT_V86 args pointer
500		movl %esi,%ebx			# Saved exception frame
501		testl %eax,%eax 		# INT_V86 args?
502		jz intrtn.2			# No
503		movl $MEM_USR,%edi		# User base
504		movl 0x1c(%esi),%ebx		# User ESP
505		movl %eax,(%edi,%ebx,1) 	# Restore to user stack
506		leal 0x8(%edi,%eax,1),%edi	# Arg segment registers
507		testb $0x4,-0x6(%edi)		# Return flags?
508		jz intrtn.1			# No
509		movl 0x30(%ebp),%eax		# Get V86 flags
510		movw %ax,0x18(%esi)		# Set user flags
511intrtn.1:	leal 0x10(%esi),%ebx		# Saved exception frame
512		xchgl %edx,%esi 		# Segment registers
513		movb $0x4,%cl			# Update seg regs
514		rep				#  in INT_V86
515		movsl				#  args
516intrtn.2:	movl %edx,%esi			# Segment registers
517		leal 0x28(%ebp),%edi		# Set up seg
518		movb $0x4,%cl			#  regs for
519		rep				#  later
520		movsl				#  pop
521		movl %ebx,%esi			# Restore exception
522		movb $0x5,%cl			#  frame to
523		rep				#  supervisor
524		movsl				#  stack
525		movl %esi,MEM_TSS+TSS_ESP1	# Link stack pointer
526		popa				# Restore
527		leal 0x8(%esp,1),%esp		# Discard err, int no
528		popl %es			# Restore
529		popl %ds			#  user
530		popl %fs			#  segment
531		popl %gs			#  registers
532		iret				# To user mode
533#
534# V86 monitor.
535#
536v86mon: 	cld				# String ops inc
537		pushl $SEL_SDATA		# Set up for
538		popl %ds			#  flat addressing
539		pusha				# Save registers
540		movl %esp,%ebp			# Address stack frame
541		movzwl 0x2c(%ebp),%edi		# Load V86 CS
542		shll $0x4,%edi			# To linear
543		movl 0x28(%ebp),%esi		# Load V86 IP
544		addl %edi,%esi			# Code pointer
545		xorl %ecx,%ecx			# Zero
546		movb $0x2,%cl			# 16-bit operands
547		xorl %eax,%eax			# Zero
548v86mon.1:	lodsb				# Get opcode
549		cmpb $0x66,%al			# Operand size prefix?
550		jne v86mon.2			# No
551		movb $0x4,%cl			# 32-bit operands
552		jmp v86mon.1			# Continue
553v86mon.2:	cmpb $0xf4,%al			# HLT?
554		jne v86mon.3			# No
555		cmpl $inthlt+0x1,%esi		# Is inthlt?
556		jne v86mon.7			# No (ignore)
557		jmp intrtn			# Return to user mode
558v86mon.3:	cmpb $0xf,%al			# Is
559		jne v86mon.4			#  this
560		cmpb $0x20,(%esi)		#  a
561		jne v86mon.4			#  MOV EAX,CR0
562		cmpb $0xc0,0x1(%esi)		#  instruction?
563		je v86mov			# Yes
564v86mon.4:	cmpb $0xfa,%al			# CLI?
565		je v86cli			# Yes
566		cmpb $0xfb,%al			# STI?
567		je v86sti			# Yes
568		movzwl 0x38(%ebp),%ebx		# Load V86 SS
569		shll $0x4,%ebx			# To offset
570		pushl %ebx			# Save
571		addl 0x34(%ebp),%ebx		# Add V86 SP
572		movl 0x30(%ebp),%edx		# Load V86 flags
573		cmpb $0x9c,%al			# PUSHF/PUSHFD?
574		je v86pushf			# Yes
575		cmpb $0x9d,%al			# POPF/POPFD?
576		je v86popf			# Yes
577		cmpb $0xcd,%al			# INT imm8?
578		je v86intn			# Yes
579		cmpb $0xcf,%al			# IRET/IRETD?
580		je v86iret			# Yes
581		popl %ebx			# Restore
582		popa				# Restore
583		jmp except			# Handle exception
584v86mon.5:	movl %edx,0x30(%ebp)		# Save V86 flags
585v86mon.6:	popl %edx			# V86 SS adjustment
586		subl %edx,%ebx			# Save V86
587		movl %ebx,0x34(%ebp)		#  SP
588v86mon.7:	subl %edi,%esi			# From linear
589		movl %esi,0x28(%ebp)		# Save V86 IP
590		popa				# Restore
591		leal 0x8(%esp,1),%esp		# Discard int no, error
592		iret				# To V86 mode
593#
594# Emulate MOV EAX,CR0.
595#
596v86mov: 	movl %cr0,%eax			# CR0 to
597		movl %eax,0x1c(%ebp)		#  saved EAX
598		incl %esi			# Adjust
599		incl %esi			#  IP
600		jmp v86mon.7			# Finish up
601#
602# Emulate CLI.
603#
604v86cli: 	andb $~0x2,0x31(%ebp)		# Clear IF
605		jmp v86mon.7			# Finish up
606#
607# Emulate STI.
608#
609v86sti: 	orb $0x2,0x31(%ebp)		# Set IF
610		jmp v86mon.7			# Finish up
611#
612# Emulate PUSHF/PUSHFD.
613#
614v86pushf:	subl %ecx,%ebx			# Adjust SP
615		cmpb $0x4,%cl			# 32-bit
616		je v86pushf.1			# Yes
617		o16				# 16-bit
618v86pushf.1:	movl %edx,(%ebx)		# Save flags
619		jmp v86mon.6			# Finish up
620#
621# Emulate IRET/IRETD.
622#
623v86iret:	movzwl (%ebx),%esi		# Load V86 IP
624		movzwl 0x2(%ebx),%edi		# Load V86 CS
625		leal 0x4(%ebx),%ebx		# Adjust SP
626		movl %edi,0x2c(%ebp)		# Save V86 CS
627		xorl %edi,%edi			# No ESI adjustment
628#
629# Emulate POPF/POPFD (and remainder of IRET/IRETD).
630#
631v86popf:	cmpb $0x4,%cl			# 32-bit?
632		je v86popf.1			# Yes
633		movl %edx,%eax			# Initialize
634		o16				# 16-bit
635v86popf.1:	movl (%ebx),%eax		# Load flags
636		addl %ecx,%ebx			# Adjust SP
637		andl $V86_FLG,%eax		# Merge
638		andl $~V86_FLG,%edx		#  the
639		orl %eax,%edx			#  flags
640		jmp v86mon.5			# Finish up
641#
642# trap int 15, function 87
643# reads %es:%si from saved registers on stack to find a GDT containing
644# source and destination locations
645# reads count of words from saved %cx
646# returns success by setting %ah to 0
647#
648int15_87:	pushl %eax			# Save
649		pushl %ebx			#  some information
650		pushl %esi			#  onto the stack.
651		pushl %edi
652		xorl %eax,%eax			# clean EAX
653		xorl %ebx,%ebx			# clean EBX
654		movl 0x4(%ebp),%esi		# Get user's ESI
655		movl 0x3C(%ebp),%ebx		# store ES
656		movw %si,%ax			# store SI
657		shll $0x4,%ebx			# Make it a seg.
658		addl %eax,%ebx			# ebx=(es<<4)+si
659		movb 0x14(%ebx),%al		# Grab the
660		movb 0x17(%ebx),%ah		#  necessary
661		shll $0x10,%eax			#  information
662		movw 0x12(%ebx),%ax		#  from
663		movl %eax,%esi			#  the
664		movb 0x1c(%ebx),%al		#  GDT in order to
665		movb 0x1f(%ebx),%ah		#  have %esi offset
666		shll $0x10,%eax			#  of source and %edi
667		movw 0x1a(%ebx),%ax		#  of destination.
668		movl %eax,%edi
669		pushl %ds			# Make:
670		popl %es			# es = ds
671		pushl %ecx			# stash ECX
672		xorl %ecx,%ecx			# highw of ECX is clear
673		movw 0x18(%ebp),%cx		# Get user's ECX
674		rep				# repeat...
675		movsb				#  perform copy.
676		popl %ecx			# Restore
677		popl %edi
678		popl %esi			#  previous
679		popl %ebx			#  register
680		popl %eax			#  values.
681		movb $0x0,0x1d(%ebp)		# set ah = 0 to indicate
682						#  success
683		andb $0xfe,%dl			# clear CF
684		jmp v86mon.5			# Finish up
685
686#
687# Emulate INT imm8... also make sure to check if it's int 15/87
688#
689v86intn:	lodsb				# Get int no
690		cmpb $0x15,%al			# is it int 15?
691		jne v86intn.2			#  no, skip parse
692		pushl %eax                      # stash EAX
693		movl 0x1c(%ebp),%eax		# user's saved EAX
694		cmpb $0x87,%ah			# is it our sub function?
695		jne v86intn.1			#  no, don't handle it
696		popl %eax			# get the stack straight
697		jmp int15_87			# it's our cue
698v86intn.1:	popl %eax			# restore EAX
699v86intn.2:	subl %edi,%esi			# From
700		shrl $0x4,%edi			#  linear
701		movw %dx,-0x2(%ebx)		# Save flags
702		movw %di,-0x4(%ebx)		# Save CS
703		leal -0x6(%ebx),%ebx		# Adjust SP
704		movw %si,(%ebx) 		# Save IP
705		shll $0x2,%eax			# Scale
706		movzwl (%eax),%esi		# Load IP
707		movzwl 0x2(%eax),%edi		# Load CS
708		movl %edi,0x2c(%ebp)		# Save CS
709		xorl %edi,%edi			# No ESI adjustment
710		andb $~0x3,%dh			# Clear IF and TF
711		jmp v86mon.5			# Finish up
712#
713# Hardware interrupt jump table.
714#
715intx20: 	pushb $0x8			# Int 0x20: IRQ0
716		jmp int_hw			# V86 int 0x8
717		pushb $0x9			# Int 0x21: IRQ1
718		jmp int_hw			# V86 int 0x9
719		pushb $0xa			# Int 0x22: IRQ2
720		jmp int_hw			# V86 int 0xa
721		pushb $0xb			# Int 0x23: IRQ3
722		jmp int_hw			# V86 int 0xb
723		pushb $0xc			# Int 0x24: IRQ4
724		jmp int_hw			# V86 int 0xc
725		pushb $0xd			# Int 0x25: IRQ5
726		jmp int_hw			# V86 int 0xd
727		pushb $0xe			# Int 0x26: IRQ6
728		jmp int_hw			# V86 int 0xe
729		pushb $0xf			# Int 0x27: IRQ7
730		jmp int_hw			# V86 int 0xf
731.`ifdef' PC98
732		pushb $0x10			# Int 0x28: IRQ8
733		jmp int_hw			# V86 int 0x10
734		pushb $0x11			# Int 0x29: IRQ9
735		jmp int_hw			# V86 int 0x11
736		pushb $0x12			# Int 0x2a: IRQ10
737		jmp int_hw			# V86 int 0x12
738		pushb $0x13			# Int 0x2b: IRQ11
739		jmp int_hw			# V86 int 0x13
740		pushb $0x14			# Int 0x2c: IRQ12
741		jmp int_hw			# V86 int 0x14
742		pushb $0x15			# Int 0x2d: IRQ13
743		jmp int_hw			# V86 int 0x15
744		pushb $0x16			# Int 0x2e: IRQ14
745		jmp int_hw			# V86 int 0x16
746		pushb $0x17			# Int 0x2f: IRQ15
747		jmp int_hw			# V86 int 0x17
748.else
749		pushb $0x70			# Int 0x28: IRQ8
750		jmp int_hw			# V86 int 0x70
751		pushb $0x71			# Int 0x29: IRQ9
752		jmp int_hw			# V86 int 0x71
753		pushb $0x72			# Int 0x2a: IRQ10
754		jmp int_hw			# V86 int 0x72
755		pushb $0x73			# Int 0x2b: IRQ11
756		jmp int_hw			# V86 int 0x73
757		pushb $0x74			# Int 0x2c: IRQ12
758		jmp int_hw			# V86 int 0x74
759		pushb $0x75			# Int 0x2d: IRQ13
760		jmp int_hw			# V86 int 0x75
761		pushb $0x76			# Int 0x2e: IRQ14
762		jmp int_hw			# V86 int 0x76
763		pushb $0x77			# Int 0x2f: IRQ15
764		jmp int_hw			# V86 int 0x77
765.endif
766#
767# Reflect hardware interrupts.
768#
769int_hw: 	testb $0x2,0xe(%esp,1)		# V86 mode?
770		jz intusr			# No
771		pushl $SEL_SDATA		# Address
772		popl %ds			#  data
773		xchgl %eax,(%esp,1)		# Swap EAX, int no
774		pushl %ebp			# Address
775		movl %esp,%ebp			#  stack frame
776		pushl %ebx			# Save
777		shll $0x2,%eax			# Get int
778		movl (%eax),%eax		#  vector
779		subl $0x6,0x14(%ebp)		# Adjust V86 ESP
780		movzwl 0x18(%ebp),%ebx		# V86 SS
781		shll $0x4,%ebx			#  * 0x10
782		addl 0x14(%ebp),%ebx		#  + V86 ESP
783		xchgw %ax,0x8(%ebp)		# Swap V86 IP
784		rorl $0x10,%eax 		# Swap words
785		xchgw %ax,0xc(%ebp)		# Swap V86 CS
786		roll $0x10,%eax 		# Swap words
787		movl %eax,(%ebx)		# CS:IP for IRET
788		movl 0x10(%ebp),%eax		# V86 flags
789		movw %ax,0x4(%ebx)		# Flags for IRET
790		andb $~0x3,0x11(%ebp)		# Clear IF, TF
791		popl %ebx			# Restore
792		popl %ebp			#  saved
793		popl %eax			#  registers
794		iret				# To V86 mode
795#
796# Invoke V86 interrupt from user mode, with arguments.
797#
798intx31: 	stc				# Have btx_v86
799		pushl %eax			# Missing int no
800#
801# Invoke V86 interrupt from user mode.
802#
803intusr: 	std				# String ops dec
804		pushl %eax			# Expand
805		pushl %eax			#  stack
806		pushl %eax			#  frame
807		pusha				# Save
808		pushl %gs			# Save
809		movl %esp,%eax			#  seg regs
810		pushl %fs			#  and
811		pushl %ds			#  point
812		pushl %es			#  to them
813		pushb $SEL_SDATA		# Set up
814		popl %ds			#  to
815		pushl %ds			#  address
816		popl %es			#  data
817		movl $MEM_USR,%ebx		# User base
818		movl %ebx,%edx			#  address
819		jc intusr.1			# If btx_v86
820		xorl %edx,%edx			# Control flags
821		xorl %ebp,%ebp			# btx_v86 pointer
822intusr.1:	leal 0x50(%esp,1),%esi		# Base of frame
823		pushl %esi			# Save
824		addl -0x4(%esi),%ebx		# User ESP
825		movl MEM_TSS+TSS_ESP1,%edi	# Link stack pointer
826		leal -0x4(%edi),%edi		# Adjust for push
827		xorl %ecx,%ecx			# Zero
828		movb $0x5,%cl			# Push exception
829		rep				#  frame on
830		movsl				#  link stack
831		xchgl %eax,%esi 		# Saved seg regs
832		movl 0x40(%esp,1),%eax		# Get int no
833		testl %edx,%edx 		# Have btx_v86?
834		jz intusr.2			# No
835		movl (%ebx),%ebp		# btx_v86 pointer
836		movb $0x4,%cl			# Count
837		addl %ecx,%ebx			# Adjust for pop
838		rep				# Push saved seg regs
839		movsl				#  on link stack
840		addl %ebp,%edx			# Flatten btx_v86 ptr
841		leal 0x14(%edx),%esi		# Seg regs pointer
842		movl 0x4(%edx),%eax		# Get int no/address
843		movzwl 0x2(%edx),%edx		# Get control flags
844intusr.2:	movl %ebp,(%edi)		# Push btx_v86 and
845		movl %edi,MEM_TSS+TSS_ESP1	#  save link stack ptr
846		popl %edi			# Base of frame
847		xchgl %eax,%ebp 		# Save intno/address
848		movl 0x48(%esp,1),%eax		# Get flags
849		testb $0x2,%dl			# Simulate CALLF?
850		jnz intusr.3			# Yes
851		decl %ebx			# Push flags
852		decl %ebx			#  on V86
853		movw %ax,(%ebx) 		#  stack
854intusr.3:	movb $0x4,%cl			# Count
855		subl %ecx,%ebx			# Push return address
856		movl $inthlt,(%ebx)		#  on V86 stack
857		rep				# Copy seg regs to
858		movsl				#  exception frame
859		xchgl %eax,%ecx 		# Save flags
860		movl %ebx,%eax			# User ESP
861		subl $V86_STK,%eax		# Less bytes
862		ja intusr.4			#  to
863		xorl %eax,%eax			#  keep
864intusr.4:	shrl $0x4,%eax			# Gives segment
865		stosl				# Set SS
866		shll $0x4,%eax			# To bytes
867		xchgl %eax,%ebx 		# Swap
868		subl %ebx,%eax			# Gives offset
869		stosl				# Set ESP
870		xchgl %eax,%ecx 		# Get flags
871		btsl $0x11,%eax 		# Set VM
872		andb $~0x3,%ah			# Clear IF and TF
873		stosl				# Set EFL
874		xchgl %eax,%ebp 		# Get int no/address
875		testb $0x1,%dl			# Address?
876		jnz intusr.5			# Yes
877		shll $0x2,%eax			# Scale
878		movl (%eax),%eax		# Load int vector
879intusr.5:	movl %eax,%ecx			# Save
880		shrl $0x10,%eax 		# Gives segment
881		stosl				# Set CS
882		movw %cx,%ax			# Restore
883		stosl				# Set EIP
884		leal 0x10(%esp,1),%esp		# Discard seg regs
885		popa				# Restore
886		iret				# To V86 mode
887#
888# System Call.
889#
890intx30: 	cmpl $SYS_EXEC,%eax		# Exec system call?
891		jne intx30.1			# No
892		pushl %ss			# Set up
893		popl %es			#  all
894		pushl %es			#  segment
895		popl %ds			#  registers
896		pushl %ds			#  for the
897		popl %fs			#  program
898		pushl %fs			#  we're
899		popl %gs			#  invoking
900		movl $MEM_USR,%eax		# User base address
901		addl 0xc(%esp,1),%eax		# Change to user
902		leal 0x4(%eax),%esp		#  stack
903		movl %cr0,%eax			# Turn
904		andl $~0x80000000,%eax		#  off
905		movl %eax,%cr0			#  paging
906		xorl %eax,%eax			# Flush
907		movl %eax,%cr3			#  TLB
908		popl %eax			# Call
909		call *%eax			#  program
910intx30.1:	incb %ss:btx_hdr+0x7		# Flag reboot
911		jmp exit			# Exit
912#
913# Dump structure [EBX] to [EDI], using format string [ESI].
914#
915dump.0: 	stosb				# Save char
916dump:		lodsb				# Load char
917		testb %al,%al			# End of string?
918		jz dump.10			# Yes
919		testb $0x80,%al 		# Control?
920		jz dump.0			# No
921		movb %al,%ch			# Save control
922		movb $'=',%al			# Append
923		stosb				#  '='
924		lodsb				# Get offset
925		pushl %esi			# Save
926		movsbl %al,%esi 		# To
927		addl %ebx,%esi			#  pointer
928		testb $DMP_X16,%ch		# Dump word?
929		jz dump.1			# No
930		lodsw				# Get and
931		call hex16			#  dump it
932dump.1: 	testb $DMP_X32,%ch		# Dump long?
933		jz dump.2			# No
934		lodsl				# Get and
935		call hex32			#  dump it
936dump.2: 	testb $DMP_MEM,%ch		# Dump memory?
937		jz dump.8			# No
938		pushl %ds			# Save
939		testb $0x2,0x52(%ebx)		# V86 mode?
940		jnz dump.3			# Yes
941		verrl 0x4(%esi) 		# Readable selector?
942		jnz dump.3			# No
943		ldsl (%esi),%esi		# Load pointer
944		jmp dump.4			# Join common code
945dump.3: 	lodsl				# Set offset
946		xchgl %eax,%edx 		# Save
947		lodsl				# Get segment
948		shll $0x4,%eax			#  * 0x10
949		addl %edx,%eax			#  + offset
950		xchgl %eax,%esi 		# Set pointer
951dump.4: 	movb $0x10,%cl			# Bytes to dump
952dump.5: 	lodsb				# Get byte and
953		call hex8			#  dump it
954		decb %cl			# Keep count
955		jz dump.7			# If done
956		movb $'-',%al			# Separator
957		cmpb $0x8,%cl			# Half way?
958		je dump.6			# Yes
959		movb $' ',%al			# Use space
960dump.6: 	stosb				# Save separator
961		jmp dump.5			# Continue
962dump.7: 	popl %ds			# Restore
963dump.8: 	popl %esi			# Restore
964		movb $0xa,%al			# Line feed
965		testb $DMP_EOL,%ch		# End of line?
966		jnz dump.9			# Yes
967		movb $' ',%al			# Use spaces
968		stosb				# Save one
969dump.9: 	jmp dump.0			# Continue
970dump.10:	stosb				# Terminate string
971		ret				# To caller
972#
973# Convert EAX, AX, or AL to hex, saving the result to [EDI].
974#
975hex32:		pushl %eax			# Save
976		shrl $0x10,%eax 		# Do upper
977		call hex16			#  16
978		popl %eax			# Restore
979hex16:		call hex16.1			# Do upper 8
980hex16.1:	xchgb %ah,%al			# Save/restore
981hex8:		pushl %eax			# Save
982		shrb $0x4,%al			# Do upper
983		call hex8.1			#  4
984		popl %eax			# Restore
985hex8.1: 	andb $0xf,%al			# Get lower 4
986		cmpb $0xa,%al			# Convert
987		sbbb $0x69,%al			#  to hex
988		das				#  digit
989		orb $0x20,%al			# To lower case
990		stosb				# Save char
991		ret				# (Recursive)
992#
993# Output zero-terminated string [ESI] to the console.
994#
995putstr.0:	call putchr			# Output char
996putstr: 	lodsb				# Load char
997		testb %al,%al			# End of string?
998		jnz putstr.0			# No
999		ret				# To caller
1000#
1001# Output character AL to the console.
1002#
1003putchr: 	pusha				# Save
1004		xorl %ecx,%ecx			# Zero for loops
1005		movb $SCR_MAT,%ah		# Mode/attribute
1006		movl $BDA_POS,%ebx		# BDA pointer
1007		movw (%ebx),%dx 		# Cursor position
1008.`ifdef' PC98
1009		movl $0xa0000,%edi
1010.else
1011		movl $0xb8000,%edi		# Regen buffer (color)
1012		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
1013		jne putchr.1			# No
1014		xorw %di,%di			# Regen buffer (mono)
1015.endif
1016putchr.1:	cmpb $0xa,%al			# New line?
1017		je putchr.2			# Yes
1018.`ifdef' PC98
1019		movw %dx,%cx
1020		movb %al,(%edi,%ecx,1)		# Write char
1021		addl $0x2000,%ecx
1022		movb %ah,(%edi,%ecx,1)		# Write attr
1023		addw $0x02,%dx
1024		jmp putchr.3
1025putchr.2:	movw %dx,%ax
1026		movb $SCR_COL*2,%dl
1027		div %dl
1028		incb %al
1029		mul %dl
1030		movw %ax,%dx
1031putchr.3:	cmpw $SCR_ROW*SCR_COL*2,%dx
1032.else
1033		xchgl %eax,%ecx 		# Save char
1034		movb $SCR_COL,%al		# Columns per row
1035		mulb %dh			#  * row position
1036		addb %dl,%al			#  + column
1037		adcb $0x0,%ah			#  position
1038		shll %eax			#  * 2
1039		xchgl %eax,%ecx 		# Swap char, offset
1040		movw %ax,(%edi,%ecx,1)		# Write attr:char
1041		incl %edx			# Bump cursor
1042		cmpb $SCR_COL,%dl		# Beyond row?
1043		jb putchr.3			# No
1044putchr.2:	xorb %dl,%dl			# Zero column
1045		incb %dh			# Bump row
1046putchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
1047.endif
1048		jb putchr.4			# No
1049		leal 2*SCR_COL(%edi),%esi	# New top line
1050		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
1051		rep				# Scroll
1052		movsl				#  screen
1053		movb $' ',%al			# Space
1054.`ifdef' PC98
1055		xorb %ah,%ah
1056.endif
1057		movb $SCR_COL,%cl		# Columns to clear
1058		rep				# Clear
1059		stosw				#  line
1060.`ifdef' PC98
1061		movw $(SCR_ROW-1)*SCR_COL*2,%dx
1062.else
1063		movb $SCR_ROW-1,%dh		# Bottom line
1064.endif
1065putchr.4:	movw %dx,(%ebx) 		# Update position
1066		popa				# Restore
1067		ret				# To caller
1068
1069		.p2align 4
1070#
1071# Global descriptor table.
1072#
1073gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
1074		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
1075		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
1076		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
1077		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
1078		.word 0xffff,MEM_USR,0xfa00,0xcf# SEL_UCODE
1079		.word 0xffff,MEM_USR,0xf200,0xcf# SEL_UDATA
1080		.word _TSSLM,MEM_TSS,0x8900,0x0 # SEL_TSS
1081gdt.1:
1082#
1083# Pseudo-descriptors.
1084#
1085gdtdesc:	.word gdt.1-gdt-1,gdt,0x0	# GDT
1086idtdesc:	.word _IDTLM,MEM_IDT,0x0	# IDT
1087ivtdesc:	.word 0x400-0x0-1,0x0,0x0	# IVT
1088#
1089# IDT construction control string.
1090#
1091idtctl: 	.byte 0x10,  0x8e		# Int 0x0-0xf
1092		.word 0x7dfb,intx00		#  (exceptions)
1093		.byte 0x10,  0x8e		# Int 0x10
1094		.word 0x1,   intx10		#  (exception)
1095		.byte 0x10,  0x8e		# Int 0x20-0x2f
1096		.word 0xffff,intx20		#  (hardware)
1097		.byte 0x1,   0xee		# int 0x30
1098		.word 0x1,   intx30		#  (system call)
1099		.byte 0x2,   0xee		# Int 0x31-0x32
1100		.word 0x1,   intx31		#  (V86, null)
1101		.byte 0x0			# End of string
1102#
1103# Dump format string.
1104#
1105dmpfmt: 	.byte '\n'			# "\n"
1106		.ascii "int"			# "int="
1107		.byte 0x80|DMP_X32,	   0x40 # "00000000  "
1108		.ascii "err"			# "err="
1109		.byte 0x80|DMP_X32,	   0x44 # "00000000  "
1110		.ascii "efl"			# "efl="
1111		.byte 0x80|DMP_X32,	   0x50 # "00000000  "
1112		.ascii "eip"			# "eip="
1113		.byte 0x80|DMP_X32|DMP_EOL,0x48 # "00000000\n"
1114		.ascii "eax"			# "eax="
1115		.byte 0x80|DMP_X32,	   0x34 # "00000000  "
1116		.ascii "ebx"			# "ebx="
1117		.byte 0x80|DMP_X32,	   0x28 # "00000000  "
1118		.ascii "ecx"			# "ecx="
1119		.byte 0x80|DMP_X32,	   0x30 # "00000000  "
1120		.ascii "edx"			# "edx="
1121		.byte 0x80|DMP_X32|DMP_EOL,0x2c # "00000000\n"
1122		.ascii "esi"			# "esi="
1123		.byte 0x80|DMP_X32,	   0x1c # "00000000  "
1124		.ascii "edi"			# "edi="
1125		.byte 0x80|DMP_X32,	   0x18 # "00000000  "
1126		.ascii "ebp"			# "ebp="
1127		.byte 0x80|DMP_X32,	   0x20 # "00000000  "
1128		.ascii "esp"			# "esp="
1129		.byte 0x80|DMP_X32|DMP_EOL,0x0	# "00000000\n"
1130		.ascii "cs"			# "cs="
1131		.byte 0x80|DMP_X16,	   0x4c # "0000  "
1132		.ascii "ds"			# "ds="
1133		.byte 0x80|DMP_X16,	   0xc	# "0000  "
1134		.ascii "es"			# "es="
1135		.byte 0x80|DMP_X16,	   0x8	# "0000  "
1136		.ascii "  "			# "  "
1137		.ascii "fs"			# "fs="
1138		.byte 0x80|DMP_X16,	   0x10 # "0000  "
1139		.ascii "gs"			# "gs="
1140		.byte 0x80|DMP_X16,	   0x14 # "0000  "
1141		.ascii "ss"			# "ss="
1142		.byte 0x80|DMP_X16|DMP_EOL,0x4	# "0000\n"
1143		.ascii "cs:eip" 		# "cs:eip="
1144		.byte 0x80|DMP_MEM|DMP_EOL,0x48 # "00 00 ... 00 00\n"
1145		.ascii "ss:esp" 		# "ss:esp="
1146		.byte 0x80|DMP_MEM|DMP_EOL,0x0	# "00 00 ... 00 00\n"
1147		.asciz "System halted"		# End
1148#
1149# End of BTX memory.
1150#
1151		.p2align 4
1152break:
1153