btx.S revision 43561
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#	$Id: btx.s,v 1.9 1999/01/22 13:07:17 rnordier Exp $
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 0x0			# 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
167#
168# Create page directory.
169#
170		xorw %dx,%dx			# Page
171		movb $PAG_SIZ>>0x8,%dh		#  size
172		xorw %ax,%ax			# Zero
173		movwir(MEM_DIR,_di)		# Page directory
174		movb $PAG_CNT>>0xa,%cl		# Entries
175		movwir(MEM_TBL|0x7,_ax) 	# First entry
176init.5: 	stosw				# Write entry
177		addl %edx,%eax			# To next
178		loop init.5			# Till done
179#
180# Create page tables.
181#
182		movwir(MEM_TBL,_di)		# Page table
183		movb $PAG_CNT>>0x8,%ch		# Entries
184		xorl %eax,%eax			# Start address
185init.6: 	movb $0x7,%al			# Set U:W:P flags
186		cmpwmr(btx_hdr+0x8,_cx) 	# Standard user page?
187		jb init.7			# Yes
188		cmpwir(PAG_CNT-MEM_BTX>>0xc,_cx)# BTX memory?
189		jae init.7			# No or first page
190		andb $~0x2,%al			# Clear W flag
191		cmpwir(PAG_CNT-MEM_USR>>0xc,_cx)# User page zero?
192		jne init.7			# No
193		tstbim(0x80,btx_hdr+0x7)	# Unmap it?
194		jz init.7			# No
195		andb $~0x1,%al			# Clear P flag
196init.7: 	stosw				# Set entry
197		addw %dx,%ax			# Next address
198		loop init.6			# Till done
199#
200# Bring up the system.
201#
202		movwir(0x2820,_bx)		# Set protected mode
203		callwi(setpic)			#  IRQ offsets
204		lidtwm(idtdesc) 		# Set IDT
205		xorw %ax,%ax			# Set base
206		movb $MEM_DIR>>0x8,%ah		#  of page
207		movl %eax,%cr3			#  directory
208		lgdtwm(gdtdesc) 		# Set GDT
209		movl %cr0,%eax			# Switch to
210		o16				#  protected mode
211		orl $0x80000001,%eax		#  and enable
212		movl %eax,%cr0			#  paging
213		jmpfwi(SEL_SCODE,init.8)	# To 32-bit code
214init.8: 	xorl %ecx,%ecx			# Zero
215		movb $SEL_SDATA,%cl		# To 32-bit
216		movl %cx,%ss			#  stack
217#
218# Launch user task.
219#
220		movb $SEL_TSS,%cl		# Set task
221		ltrl %ecx			#  register
222		movl $MEM_USR,%edx		# User base address
223		movzwl %ss:BDA_MEM,%eax 	# Get free memory
224.`ifdef' PC98
225		andl $0x7,%eax
226		incl %eax
227		shll $0x11,%eax			# To bytes
228.else
229		shll $0xa,%eax			# To bytes
230.endif
231		subl $0x1000,%eax		# Less arg space
232		subl %edx,%eax			# Less base
233		movb $SEL_UDATA,%cl		# User data selector
234		pushl %ecx			# Set SS
235		pushl %eax			# Set ESP
236		pushl $0x202			# Set flags (IF set)
237		pushl $SEL_UCODE		# Set CS
238		pushl btx_hdr+0xc		# Set EIP
239		pushl %ecx			# Set GS
240		pushl %ecx			# Set FS
241		pushl %ecx			# Set DS
242		pushl %ecx			# Set ES
243		pushl %edx			# Set EAX
244		movb $0x7,%cl			# Set remaining
245init.9:		pushb $0x0			#  general
246		loop init.9			#  registers
247		popa				#  and initialize
248		popl %es			# Initialize
249		popl %ds			#  user
250		popl %fs			#  segment
251		popl %gs			#  registers
252		iret				# To user mode
253#
254# Exit routine.
255#
256exit:		cli				# Disable interrupts
257		movl $MEM_ESP0,%esp		# Clear stack
258#
259# Turn off paging.
260#
261		movl %cr0,%eax			# Get CR0
262		andl $~0x80000000,%eax		# Disable
263		movl %eax,%cr0			#  paging
264		xorl %ecx,%ecx			# Zero
265		movl %ecx,%cr3			# Flush TLB
266#
267# To 16 bits.
268#
269		o16				# Reload
270		jmpfwi(SEL_RCODE,exit.1)	#  CS
271exit.1: 	movb $SEL_RDATA,%cl		# 16-bit selector
272		movl %cx,%ss			# Reload SS
273		movl %cx,%ds			# Load
274		movl %cx,%es			#  remaining
275		movl %cx,%fs			#  segment
276		movl %cx,%gs			#  registers
277#
278# To real-address mode.
279#
280		decl %eax			# Switch to
281		movl %eax,%cr0			#  real mode
282		jmpfwi(0x0,exit.2)		# Reload CS
283exit.2: 	xorl %eax,%eax			# Real mode segment
284		movl %ax,%ss			# Reload SS
285		movl %ax,%ds			# Address data
286.`ifdef' PC98
287		movwir(0x1008,_bx)		# Set real mode
288.else
289		movwir(0x7008,_bx)		# Set real mode
290.endif
291		callwi(setpic)			#  IRQ offsets
292		lidtwm(ivtdesc) 		# Set IVT
293#
294# Reboot or await reset.
295#
296		sti				# Enable interrupts
297		tstbim(0x1,btx_hdr+0x7)		# Reboot?
298exit.3:		jz exit.3			# No
299.`ifdef' PC98
300		movb $0xa0,%al
301		outb %al,$0x35
302		movb 0,%al
303		outb %al,$0xf0
304exit.4:		jmp exit.4
305.else
306		int $0x19			# BIOS: Reboot
307.endif
308#
309# Set IRQ offsets by reprogramming 8259A PICs.
310#
311.`ifdef' PC98
312setpic: 	inb $0x02,%al			# Save master
313		pushl %eax			#  IMR
314		inb $0x0a,%al			# Save slave
315		pushl %eax			#  IMR
316		movb $0x11,%al			# ICW1 to
317		outb %al,$0x00			#  master,
318		outb %al,$0x08			#  slave
319		movb %bl,%al			# ICW2 to
320		outb %al,$0x02			#  master
321		movb %bh,%al			# ICW2 to
322		outb %al,$0x0a			#  slave
323		movb $0x80,%al			# ICW3 to
324		outb %al,$0x02			#  master
325		movb $0x7,%al			# ICW3 to
326		outb %al,$0x0a			#  slave
327		movb $0x1d,%al			# ICW4 to
328		outb %al,$0x02			#  master,
329		movb $0x9,%al			# ICW4 to
330		outb %al,$0x0a			#  slave
331		popl %eax			# Restore slave
332		outb %al,$0x0a			#  IMR
333		popl %eax			# Restore master
334		outb %al,$0x02			#  IMR
335.else
336setpic: 	inb $0x21,%al			# Save master
337		pushl %eax			#  IMR
338		inb $0xa1,%al			# Save slave
339		pushl %eax			#  IMR
340		movb $0x11,%al			# ICW1 to
341		outb %al,$0x20			#  master,
342		outb %al,$0xa0			#  slave
343		movb %bl,%al			# ICW2 to
344		outb %al,$0x21			#  master
345		movb %bh,%al			# ICW2 to
346		outb %al,$0xa1			#  slave
347		movb $0x4,%al			# ICW3 to
348		outb %al,$0x21			#  master
349		movb $0x2,%al			# ICW3 to
350		outb %al,$0xa1			#  slave
351		movb $0x1,%al			# ICW4 to
352		outb %al,$0x21			#  master,
353		outb %al,$0xa1			#  slave
354		popl %eax			# Restore slave
355		outb %al,$0xa1			#  IMR
356		popl %eax			# Restore master
357		outb %al,$0x21			#  IMR
358.endif
359		ret				# To caller
360#
361# Initiate return from V86 mode to user mode.
362#
363inthlt: 	hlt				# To supervisor mode
364#
365# Exception jump table.
366#
367intx00: 	pushb $0x0			# Int 0x0: #DE
368		jmp ex_noc			# Divide error
369		pushb $0x1			# Int 0x1: #DB
370		jmp ex_noc			# Debug
371		pushb $0x3			# Int 0x3: #BP
372		jmp ex_noc			# Breakpoint
373		pushb $0x4			# Int 0x4: #OF
374		jmp ex_noc			# Overflow
375		pushb $0x5			# Int 0x5: #BR
376		jmp ex_noc			# BOUND range exceeded
377		pushb $0x6			# Int 0x6: #UD
378		jmp ex_noc			# Invalid opcode
379		pushb $0x7			# Int 0x7: #NM
380		jmp ex_noc			# Device not available
381		pushb $0x8			# Int 0x8: #DF
382		jmp except			# Double fault
383		pushb $0xa			# Int 0xa: #TS
384		jmp except			# Invalid TSS
385		pushb $0xb			# Int 0xb: #NP
386		jmp except			# Segment not present
387		pushb $0xc			# Int 0xc: #SS
388		jmp except			# Stack segment fault
389		pushb $0xd			# Int 0xd: #GP
390		jmp ex_v86			# General protection
391		pushb $0xe			# Int 0xe: #PF
392		jmp except			# Page fault
393intx10: 	pushb $0x10			# Int 0x10: #MF
394		jmp ex_noc			# Floating-point error
395#
396# Handle #GP exception.
397#
398ex_v86: 	testb $0x2,0x12(%esp,1) 	# V86 mode?
399		jz except			# No
400		jmp v86mon			# To monitor
401#
402# Save a zero error code.
403#
404ex_noc: 	pushl (%esp,1)			# Duplicate int no
405		movb $0x0,0x4(%esp,1)		# Fake error code
406#
407# Handle exception.
408#
409except: 	cld				# String ops inc
410		pushl %ds			# Save
411		pushl %es			#  most
412		pusha				#  registers
413		movb $0x6,%al			# Push loop count
414		testb $0x2,0x3a(%esp,1) 	# V86 mode?
415		jnz except.1			# Yes
416		pushl %gs			# Set GS
417		pushl %fs			# Set FS
418		pushl %ds			# Set DS
419		pushl %es			# Set ES
420		movb $0x2,%al			# Push loop count
421		cmpw $SEL_SCODE,0x44(%esp,1)	# Supervisor mode?
422		jne except.1			# No
423		pushl %ss			# Set SS
424		leal 0x50(%esp,1),%eax		# Set
425		pushl %eax			#  ESP
426		jmp except.2			# Join common code
427except.1:	pushl 0x50(%esp,1)		# Set GS, FS, DS, ES
428		decb %al			#  (if V86 mode), and
429		jne except.1			#  SS, ESP
430except.2:	pushl $SEL_SDATA		# Set up
431		popl %ds			#  to
432		pushl %ds			#  address
433		popl %es			#  data
434		movl %esp,%ebx			# Stack frame
435		movl $dmpfmt,%esi		# Dump format string
436		movl $MEM_BUF,%edi		# Buffer
437.`ifdef' PC98
438		pushl %eax
439		pushl %edx
440wait.1:
441		inb  $0x60,%al
442		testb $0x04,%al
443		jz   wait.1
444		movb $0xe0,%al
445		outb %al,$0x62
446wait.2:
447		inb  $0x60,%al
448		testb $0x01,%al
449		jz   wait.2
450		xorl %edx,%edx
451		inb  $0x62,%al
452		movb %al,%dl
453		inb  $0x62,%al
454		movb %al,%dh
455		inb  $0x62,%al
456		inb  $0x62,%al
457		inb  $0x62,%al
458		movl %edx,%eax
459		shlw $1,%ax
460		movl $BDA_POS,%edx
461		movw %ax,(%edx)
462		popl  %edx
463		popl  %eax
464.endif
465		pushl %edi			# Dump to
466		call dump			#  buffer
467		popl %esi			#  and
468		call putstr			#  display
469		leal 0x18(%esp,1),%esp		# Discard frame
470		popa				# Restore
471		popl %es			#  registers
472		popl %ds			#  saved
473		cmpb $0x3,(%esp,1)		# Breakpoint?
474		je except.3			# Yes
475		jmp exit			# Exit
476except.3:	leal 0x8(%esp,1),%esp		# Discard err, int no
477		iret				# From interrupt
478#
479# Return to user mode from V86 mode.
480#
481intrtn: 	cld				# String ops inc
482		pushl %ds			# Address
483		popl %es			#  data
484		leal 0x3c(%ebp),%edx		# V86 Segment registers
485		movl MEM_TSS+TSS_ESP1,%esi	# Link stack pointer
486		lodsl				# INT_V86 args pointer
487		movl %esi,%ebx			# Saved exception frame
488		testl %eax,%eax 		# INT_V86 args?
489		jz intrtn.2			# No
490		movl $MEM_USR,%edi		# User base
491		movl 0x1c(%esi),%ebx		# User ESP
492		movl %eax,(%edi,%ebx,1) 	# Restore to user stack
493		leal 0x8(%edi,%eax,1),%edi	# Arg segment registers
494		testb $0x4,-0x6(%edi)		# Return flags?
495		jz intrtn.1			# No
496		movl 0x30(%ebp),%eax		# Get V86 flags
497		movw %ax,0x18(%esi)		# Set user flags
498intrtn.1:	leal 0x10(%esi),%ebx		# Saved exception frame
499		xchgl %edx,%esi 		# Segment registers
500		movb $0x4,%cl			# Update seg regs
501		rep				#  in INT_V86
502		movsl				#  args
503intrtn.2:	movl %edx,%esi			# Segment registers
504		leal 0x28(%ebp),%edi		# Set up seg
505		movb $0x4,%cl			#  regs for
506		rep				#  later
507		movsl				#  pop
508		movl %ebx,%esi			# Restore exception
509		movb $0x5,%cl			#  frame to
510		rep				#  supervisor
511		movsl				#  stack
512		movl %esi,MEM_TSS+TSS_ESP1	# Link stack pointer
513		popa				# Restore
514		leal 0x8(%esp,1),%esp		# Discard err, int no
515		popl %es			# Restore
516		popl %ds			#  user
517		popl %fs			#  segment
518		popl %gs			#  registers
519		iret				# To user mode
520#
521# V86 monitor.
522#
523v86mon: 	cld				# String ops inc
524		pushl $SEL_SDATA		# Set up for
525		popl %ds			#  flat addressing
526		pusha				# Save registers
527		movl %esp,%ebp			# Address stack frame
528		movzwl 0x2c(%ebp),%edi		# Load V86 CS
529		shll $0x4,%edi			# To linear
530		movl 0x28(%ebp),%esi		# Load V86 IP
531		addl %edi,%esi			# Code pointer
532		xorl %ecx,%ecx			# Zero
533		movb $0x2,%cl			# 16-bit operands
534		xorl %eax,%eax			# Zero
535v86mon.1:	lodsb				# Get opcode
536		cmpb $0x66,%al			# Operand size prefix?
537		jne v86mon.2			# No
538		movb $0x4,%cl			# 32-bit operands
539		jmp v86mon.1			# Continue
540v86mon.2:	cmpb $0xf4,%al			# HLT?
541		jne v86mon.3			# No
542		cmpl $inthlt+0x1,%esi		# Is inthlt?
543		jne v86mon.6			# No (ignore)
544		jmp intrtn			# Return to user mode
545v86mon.3:	cmpb $0xfa,%al			# CLI?
546		je v86cli			# Yes
547		cmpb $0xfb,%al			# STI?
548		je v86sti			# Yes
549		movzwl 0x38(%ebp),%ebx		# Load V86 SS
550		shll $0x4,%ebx			# To offset
551		pushl %ebx			# Save
552		addl 0x34(%ebp),%ebx		# Add V86 SP
553		movl 0x30(%ebp),%edx		# Load V86 flags
554		cmpb $0x9c,%al			# PUSHF/PUSHFD?
555		je v86pushf			# Yes
556		cmpb $0x9d,%al			# POPF/POPFD?
557		je v86popf			# Yes
558		cmpb $0xcd,%al			# INT imm8?
559		je v86intn			# Yes
560		cmpb $0xcf,%al			# IRET/IRETD?
561		je v86iret			# Yes
562		popl %ebx			# Restore
563		popa				# Restore
564		jmp except			# Handle exception
565v86mon.4:	movl %edx,0x30(%ebp)		# Save V86 flags
566v86mon.5:	popl %edx			# V86 SS adjustment
567		subl %edx,%ebx			# Save V86
568		movl %ebx,0x34(%ebp)		#  SP
569v86mon.6:	subl %edi,%esi			# From linear
570		movl %esi,0x28(%ebp)		# Save V86 IP
571		popa				# Restore
572		leal 0x8(%esp,1),%esp		# Discard int no, error
573		iret				# To V86 mode
574#
575# Emulate CLI.
576#
577v86cli: 	andb $~0x2,0x31(%ebp)		# Clear IF
578		jmp v86mon.6			# Finish up
579#
580# Emulate STI.
581#
582v86sti: 	orb $0x2,0x31(%ebp)		# Set IF
583		jmp v86mon.6			# Finish up
584#
585# Emulate PUSHF/PUSHFD.
586#
587v86pushf:	subl %ecx,%ebx			# Adjust SP
588		cmpb $0x4,%cl			# 32-bit
589		je v86pushf.1			# Yes
590		o16				# 16-bit
591v86pushf.1:	movl %edx,(%ebx)		# Save flags
592		jmp v86mon.5			# Finish up
593#
594# Emulate IRET/IRETD.
595#
596v86iret:	movzwl (%ebx),%esi		# Load V86 IP
597		movzwl 0x2(%ebx),%edi		# Load V86 CS
598		leal 0x4(%ebx),%ebx		# Adjust SP
599		movl %edi,0x2c(%ebp)		# Save V86 CS
600		xorl %edi,%edi			# No ESI adjustment
601#
602# Emulate POPF/POPFD (and remainder of IRET/IRETD).
603#
604v86popf:	cmpb $0x4,%cl			# 32-bit?
605		je v86popf.1			# Yes
606		movl %edx,%eax			# Initialize
607		o16				# 16-bit
608v86popf.1:	movl (%ebx),%eax		# Load flags
609		addl %ecx,%ebx			# Adjust SP
610		andl $V86_FLG,%eax		# Merge
611		andl $~V86_FLG,%edx		#  the
612		orl %eax,%edx			#  flags
613		jmp v86mon.4			# Finish up
614#
615# Emulate INT imm8.
616#
617v86intn:	lodsb				# Get int no
618		subl %edi,%esi			# From
619		shrl $0x4,%edi			#  linear
620		movw %dx,-0x2(%ebx)		# Save flags
621		movw %di,-0x4(%ebx)		# Save CS
622		leal -0x6(%ebx),%ebx		# Adjust SP
623		movw %si,(%ebx) 		# Save IP
624		shll $0x2,%eax			# Scale
625		movzwl (%eax),%esi		# Load IP
626		movzwl 0x2(%eax),%edi		# Load CS
627		movl %edi,0x2c(%ebp)		# Save CS
628		xorl %edi,%edi			# No ESI adjustment
629		andb $~0x3,%dh			# Clear IF and TF
630		jmp v86mon.4			# Finish up
631#
632# Hardware interrupt jump table.
633#
634intx20: 	pushb $0x8			# Int 0x20: IRQ0
635		jmp int_hw			# V86 int 0x8
636		pushb $0x9			# Int 0x21: IRQ1
637		jmp int_hw			# V86 int 0x9
638		pushb $0xa			# Int 0x22: IRQ2
639		jmp int_hw			# V86 int 0xa
640		pushb $0xb			# Int 0x23: IRQ3
641		jmp int_hw			# V86 int 0xb
642		pushb $0xc			# Int 0x24: IRQ4
643		jmp int_hw			# V86 int 0xc
644		pushb $0xd			# Int 0x25: IRQ5
645		jmp int_hw			# V86 int 0xd
646		pushb $0xe			# Int 0x26: IRQ6
647		jmp int_hw			# V86 int 0xe
648		pushb $0xf			# Int 0x27: IRQ7
649		jmp int_hw			# V86 int 0xf
650.`ifdef' PC98
651		pushb $0x10			# Int 0x28: IRQ8
652		jmp int_hw			# V86 int 0x10
653		pushb $0x11			# Int 0x29: IRQ9
654		jmp int_hw			# V86 int 0x11
655		pushb $0x12			# Int 0x2a: IRQ10
656		jmp int_hw			# V86 int 0x12
657		pushb $0x13			# Int 0x2b: IRQ11
658		jmp int_hw			# V86 int 0x13
659		pushb $0x14			# Int 0x2c: IRQ12
660		jmp int_hw			# V86 int 0x14
661		pushb $0x15			# Int 0x2d: IRQ13
662		jmp int_hw			# V86 int 0x15
663		pushb $0x16			# Int 0x2e: IRQ14
664		jmp int_hw			# V86 int 0x16
665		pushb $0x17			# Int 0x2f: IRQ15
666		jmp int_hw			# V86 int 0x17
667.else
668		pushb $0x70			# Int 0x28: IRQ8
669		jmp int_hw			# V86 int 0x70
670		pushb $0x71			# Int 0x29: IRQ9
671		jmp int_hw			# V86 int 0x71
672		pushb $0x72			# Int 0x2a: IRQ10
673		jmp int_hw			# V86 int 0x72
674		pushb $0x73			# Int 0x2b: IRQ11
675		jmp int_hw			# V86 int 0x73
676		pushb $0x74			# Int 0x2c: IRQ12
677		jmp int_hw			# V86 int 0x74
678		pushb $0x75			# Int 0x2d: IRQ13
679		jmp int_hw			# V86 int 0x75
680		pushb $0x76			# Int 0x2e: IRQ14
681		jmp int_hw			# V86 int 0x76
682		pushb $0x77			# Int 0x2f: IRQ15
683		jmp int_hw			# V86 int 0x77
684.endif
685#
686# Reflect hardware interrupts.
687#
688int_hw: 	testb $0x2,0xe(%esp,1)		# V86 mode?
689		jz intusr			# No
690		pushl $SEL_SDATA		# Address
691		popl %ds			#  data
692		xchgl %eax,(%esp,1)		# Swap EAX, int no
693		pushl %ebp			# Address
694		movl %esp,%ebp			#  stack frame
695		pushl %ebx			# Save
696		shll $0x2,%eax			# Get int
697		movl (%eax),%eax		#  vector
698		subl $0x6,0x14(%ebp)		# Adjust V86 ESP
699		movzwl 0x18(%ebp),%ebx		# V86 SS
700		shll $0x4,%ebx			#  * 0x10
701		addl 0x14(%ebp),%ebx		#  + V86 ESP
702		xchgw %ax,0x8(%ebp)		# Swap V86 IP
703		rorl $0x10,%eax 		# Swap words
704		xchgw %ax,0xc(%ebp)		# Swap V86 CS
705		roll $0x10,%eax 		# Swap words
706		movl %eax,(%ebx)		# CS:IP for IRET
707		movl 0x10(%ebp),%eax		# V86 flags
708		movw %ax,0x4(%ebx)		# Flags for IRET
709		andb $~0x3,0x11(%ebp)		# Clear IF, TF
710		popl %ebx			# Restore
711		popl %ebp			#  saved
712		popl %eax			#  registers
713		iret				# To V86 mode
714#
715# Invoke V86 interrupt from user mode, with arguments.
716#
717intx31: 	stc				# Have btx_v86
718		pushl %eax			# Missing int no
719#
720# Invoke V86 interrupt from user mode.
721#
722intusr: 	std				# String ops dec
723		pushl %eax			# Expand
724		pushl %eax			#  stack
725		pushl %eax			#  frame
726		pusha				# Save
727		pushl %gs			# Save
728		movl %esp,%eax			#  seg regs
729		pushl %fs			#  and
730		pushl %ds			#  point
731		pushl %es			#  to them
732		pushb $SEL_SDATA		# Set up
733		popl %ds			#  to
734		pushl %ds			#  address
735		popl %es			#  data
736		movl $MEM_USR,%ebx		# User base
737		movl %ebx,%edx			#  address
738		jc intusr.1			# If btx_v86
739		xorl %edx,%edx			# Control flags
740		xorl %ebp,%ebp			# btx_v86 pointer
741intusr.1:	leal 0x50(%esp,1),%esi		# Base of frame
742		pushl %esi			# Save
743		addl -0x4(%esi),%ebx		# User ESP
744		movl MEM_TSS+TSS_ESP1,%edi	# Link stack pointer
745		leal -0x4(%edi),%edi		# Adjust for push
746		xorl %ecx,%ecx			# Zero
747		movb $0x5,%cl			# Push exception
748		rep				#  frame on
749		movsl				#  link stack
750		xchgl %eax,%esi 		# Saved seg regs
751		movl 0x40(%esp,1),%eax		# Get int no
752		testl %edx,%edx 		# Have btx_v86?
753		jz intusr.2			# No
754		movl (%ebx),%ebp		# btx_v86 pointer
755		movb $0x4,%cl			# Count
756		addl %ecx,%ebx			# Adjust for pop
757		rep				# Push saved seg regs
758		movsl				#  on link stack
759		addl %ebp,%edx			# Flatten btx_v86 ptr
760		leal 0x14(%edx),%esi		# Seg regs pointer
761		movl 0x4(%edx),%eax		# Get int no/address
762		movzwl 0x2(%edx),%edx		# Get control flags
763intusr.2:	movl %ebp,(%edi)		# Push btx_v86 and
764		movl %edi,MEM_TSS+TSS_ESP1	#  save link stack ptr
765		popl %edi			# Base of frame
766		xchgl %eax,%ebp 		# Save intno/address
767		movl 0x48(%esp,1),%eax		# Get flags
768		testb $0x2,%dl			# Simulate CALLF?
769		jnz intusr.3			# Yes
770		decl %ebx			# Push flags
771		decl %ebx			#  on V86
772		movw %ax,(%ebx) 		#  stack
773intusr.3:	movb $0x4,%cl			# Count
774		subl %ecx,%ebx			# Push return address
775		movl $inthlt,(%ebx)		#  on V86 stack
776		rep				# Copy seg regs to
777		movsl				#  exception frame
778		xchgl %eax,%ecx 		# Save flags
779		movl %ebx,%eax			# User ESP
780		subl $V86_STK,%eax		# Less bytes
781		ja intusr.4			#  to
782		xorl %eax,%eax			#  keep
783intusr.4:	shrl $0x4,%eax			# Gives segment
784		stosl				# Set SS
785		shll $0x4,%eax			# To bytes
786		xchgl %eax,%ebx 		# Swap
787		subl %ebx,%eax			# Gives offset
788		stosl				# Set ESP
789		xchgl %eax,%ecx 		# Get flags
790		btsl $0x11,%eax 		# Set VM
791		andb $~0x3,%ah			# Clear IF and TF
792		stosl				# Set EFL
793		xchgl %eax,%ebp 		# Get int no/address
794		testb $0x1,%dl			# Address?
795		jnz intusr.5			# Yes
796		shll $0x2,%eax			# Scale
797		movl (%eax),%eax		# Load int vector
798intusr.5:	movl %eax,%ecx			# Save
799		shrl $0x10,%eax 		# Gives segment
800		stosl				# Set CS
801		movw %cx,%ax			# Restore
802		stosl				# Set EIP
803		leal 0x10(%esp,1),%esp		# Discard seg regs
804		popa				# Restore
805		iret				# To V86 mode
806#
807# System Call.
808#
809intx30: 	cmpl $SYS_EXEC,%eax		# Exec system call?
810		jne intx30.1			# No
811		pushl %ss			# Set up
812		popl %es			#  all
813		pushl %es			#  segment
814		popl %ds			#  registers
815		pushl %ds			#  for the
816		popl %fs			#  program
817		pushl %fs			#  we're
818		popl %gs			#  invoking
819		movl $MEM_USR,%eax		# User base address
820		addl 0xc(%esp,1),%eax		# Change to user
821		leal 0x4(%eax),%esp		#  stack
822		movl %cr0,%eax			# Turn
823		andl $~0x80000000,%eax		#  off
824		movl %eax,%cr0			#  paging
825		xorl %eax,%eax			# Flush
826		movl %eax,%cr3			#  TLB
827		popl %eax			# Call
828		call *%eax			#  program
829intx30.1:	incb %ss:btx_hdr+0x7		# Flag reboot
830		jmp exit			# Exit
831#
832# Dump structure [EBX] to [EDI], using format string [ESI].
833#
834dump.0: 	stosb				# Save char
835dump:		lodsb				# Load char
836		testb %al,%al			# End of string?
837		jz dump.10			# Yes
838		testb $0x80,%al 		# Control?
839		jz dump.0			# No
840		movb %al,%ch			# Save control
841		movb $'=',%al			# Append
842		stosb				#  '='
843		lodsb				# Get offset
844		pushl %esi			# Save
845		movsbl %al,%esi 		# To
846		addl %ebx,%esi			#  pointer
847		testb $DMP_X16,%ch		# Dump word?
848		jz dump.1			# No
849		lodsw				# Get and
850		call hex16			#  dump it
851dump.1: 	testb $DMP_X32,%ch		# Dump long?
852		jz dump.2			# No
853		lodsl				# Get and
854		call hex32			#  dump it
855dump.2: 	testb $DMP_MEM,%ch		# Dump memory?
856		jz dump.8			# No
857		pushl %ds			# Save
858		testb $0x2,0x52(%ebx)		# V86 mode?
859		jnz dump.3			# Yes
860		verrl 0x4(%esi) 		# Readable selector?
861		jnz dump.3			# No
862		ldsl (%esi),%esi		# Load pointer
863		jmp dump.4			# Join common code
864dump.3: 	lodsl				# Set offset
865		xchgl %eax,%edx 		# Save
866		lodsl				# Get segment
867		shll $0x4,%eax			#  * 0x10
868		addl %edx,%eax			#  + offset
869		xchgl %eax,%esi 		# Set pointer
870dump.4: 	movb $0x10,%cl			# Bytes to dump
871dump.5: 	lodsb				# Get byte and
872		call hex8			#  dump it
873		decb %cl			# Keep count
874		jz dump.7			# If done
875		movb $'-',%al			# Separator
876		cmpb $0x8,%cl			# Half way?
877		je dump.6			# Yes
878		movb $' ',%al			# Use space
879dump.6: 	stosb				# Save separator
880		jmp dump.5			# Continue
881dump.7: 	popl %ds			# Restore
882dump.8: 	popl %esi			# Restore
883		movb $0xa,%al			# Line feed
884		testb $DMP_EOL,%ch		# End of line?
885		jnz dump.9			# Yes
886		movb $' ',%al			# Use spaces
887		stosb				# Save one
888dump.9: 	jmp dump.0			# Continue
889dump.10:	stosb				# Terminate string
890		ret				# To caller
891#
892# Convert EAX, AX, or AL to hex, saving the result to [EDI].
893#
894hex32:		pushl %eax			# Save
895		shrl $0x10,%eax 		# Do upper
896		call hex16			#  16
897		popl %eax			# Restore
898hex16:		call hex16.1			# Do upper 8
899hex16.1:	xchgb %ah,%al			# Save/restore
900hex8:		pushl %eax			# Save
901		shrb $0x4,%al			# Do upper
902		call hex8.1			#  4
903		popl %eax			# Restore
904hex8.1: 	andb $0xf,%al			# Get lower 4
905		cmpb $0xa,%al			# Convert
906		sbbb $0x69,%al			#  to hex
907		das				#  digit
908		orb $0x20,%al			# To lower case
909		stosb				# Save char
910		ret				# (Recursive)
911#
912# Output zero-terminated string [ESI] to the console.
913#
914putstr.0:	call putchr			# Output char
915putstr: 	lodsb				# Load char
916		testb %al,%al			# End of string?
917		jnz putstr.0			# No
918		ret				# To caller
919#
920# Output character AL to the console.
921#
922putchr: 	pusha				# Save
923		xorl %ecx,%ecx			# Zero for loops
924		movb $SCR_MAT,%ah		# Mode/attribute
925		movl $BDA_POS,%ebx		# BDA pointer
926		movw (%ebx),%dx 		# Cursor position
927.`ifdef' PC98
928		movl $0xa0000,%edi
929.else
930		movl $0xb8000,%edi		# Regen buffer (color)
931		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
932		jne putchr.1			# No
933		xorw %di,%di			# Regen buffer (mono)
934.endif
935putchr.1:	cmpb $0xa,%al			# New line?
936		je putchr.2			# Yes
937.`ifdef' PC98
938		movw %dx,%cx
939		movb %al,(%edi,%ecx,1)		# Write char
940		addl $0x2000,%ecx
941		movb %ah,(%edi,%ecx,1)		# Write attr
942		addw $0x02,%dx
943		jmp putchr.3
944putchr.2:	movw %dx,%ax
945		movb $SCR_COL*2,%dl
946		div %dl
947		incb %al
948		mul %dl
949		movw %ax,%dx
950putchr.3:	cmpw $SCR_ROW*SCR_COL*2,%dx
951.else
952		xchgl %eax,%ecx 		# Save char
953		movb $SCR_COL,%al		# Columns per row
954		mulb %dh			#  * row position
955		addb %dl,%al			#  + column
956		adcb $0x0,%ah			#  position
957		shll %eax			#  * 2
958		xchgl %eax,%ecx 		# Swap char, offset
959		movw %ax,(%edi,%ecx,1)		# Write attr:char
960		incl %edx			# Bump cursor
961		cmpb $SCR_COL,%dl		# Beyond row?
962		jb putchr.3			# No
963putchr.2:	xorb %dl,%dl			# Zero column
964		incb %dh			# Bump row
965putchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
966.endif
967		jb putchr.4			# No
968		leal 2*SCR_COL(%edi),%esi	# New top line
969		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
970		rep				# Scroll
971		movsl				#  screen
972		movb $' ',%al			# Space
973.`ifdef' PC98
974		xorb %ah,%ah
975.endif
976		movb $SCR_COL,%cl		# Columns to clear
977		rep				# Clear
978		stosw				#  line
979.`ifdef' PC98
980		movw $(SCR_ROW-1)*SCR_COL*2,%dx
981.else
982		movb $SCR_ROW-1,%dh		# Bottom line
983.endif
984putchr.4:	movw %dx,(%ebx) 		# Update position
985		popa				# Restore
986		ret				# To caller
987
988		.p2align 4
989#
990# Global descriptor table.
991#
992gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
993		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
994		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
995		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
996		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
997		.word 0xffff,MEM_USR,0xfa00,0xcf# SEL_UCODE
998		.word 0xffff,MEM_USR,0xf200,0xcf# SEL_UDATA
999		.word _TSSLM,MEM_TSS,0x8900,0x0 # SEL_TSS
1000gdt.1:
1001#
1002# Pseudo-descriptors.
1003#
1004gdtdesc:	.word gdt.1-gdt-1,gdt,0x0	# GDT
1005idtdesc:	.word _IDTLM,MEM_IDT,0x0	# IDT
1006ivtdesc:	.word 0x400-0x0-1,0x0,0x0	# IVT
1007#
1008# IDT construction control string.
1009#
1010idtctl: 	.byte 0x10,  0x8e		# Int 0x0-0xf
1011		.word 0x7dfb,intx00		#  (exceptions)
1012		.byte 0x10,  0x8e		# Int 0x10
1013		.word 0x1,   intx10		#  (exception)
1014		.byte 0x10,  0x8e		# Int 0x20-0x2f
1015		.word 0xffff,intx20		#  (hardware)
1016		.byte 0x1,   0xee		# int 0x30
1017		.word 0x1,   intx30		#  (system call)
1018		.byte 0x2,   0xee		# Int 0x31-0x32
1019		.word 0x1,   intx31		#  (V86, null)
1020		.byte 0x0			# End of string
1021#
1022# Dump format string.
1023#
1024dmpfmt: 	.byte '\n'			# "\n"
1025		.ascii "int"			# "int="
1026		.byte 0x80|DMP_X32,	   0x40 # "00000000  "
1027		.ascii "err"			# "err="
1028		.byte 0x80|DMP_X32,	   0x44 # "00000000  "
1029		.ascii "efl"			# "efl="
1030		.byte 0x80|DMP_X32,	   0x50 # "00000000  "
1031		.ascii "eip"			# "eip="
1032		.byte 0x80|DMP_X32|DMP_EOL,0x48 # "00000000\n"
1033		.ascii "eax"			# "eax="
1034		.byte 0x80|DMP_X32,	   0x34 # "00000000  "
1035		.ascii "ebx"			# "ebx="
1036		.byte 0x80|DMP_X32,	   0x28 # "00000000  "
1037		.ascii "ecx"			# "ecx="
1038		.byte 0x80|DMP_X32,	   0x30 # "00000000  "
1039		.ascii "edx"			# "edx="
1040		.byte 0x80|DMP_X32|DMP_EOL,0x2c # "00000000\n"
1041		.ascii "esi"			# "esi="
1042		.byte 0x80|DMP_X32,	   0x1c # "00000000  "
1043		.ascii "edi"			# "edi="
1044		.byte 0x80|DMP_X32,	   0x18 # "00000000  "
1045		.ascii "ebp"			# "ebp="
1046		.byte 0x80|DMP_X32,	   0x20 # "00000000  "
1047		.ascii "esp"			# "esp="
1048		.byte 0x80|DMP_X32|DMP_EOL,0x0	# "00000000\n"
1049		.ascii "cs"			# "cs="
1050		.byte 0x80|DMP_X16,	   0x4c # "0000  "
1051		.ascii "ds"			# "ds="
1052		.byte 0x80|DMP_X16,	   0xc	# "0000  "
1053		.ascii "es"			# "es="
1054		.byte 0x80|DMP_X16,	   0x8	# "0000  "
1055		.ascii "  "			# "  "
1056		.ascii "fs"			# "fs="
1057		.byte 0x80|DMP_X16,	   0x10 # "0000  "
1058		.ascii "gs"			# "gs="
1059		.byte 0x80|DMP_X16,	   0x14 # "0000  "
1060		.ascii "ss"			# "ss="
1061		.byte 0x80|DMP_X16|DMP_EOL,0x4	# "0000\n"
1062		.ascii "cs:eip" 		# "cs:eip="
1063		.byte 0x80|DMP_MEM|DMP_EOL,0x48 # "00 00 ... 00 00\n"
1064		.ascii "ss:esp" 		# "ss:esp="
1065		.byte 0x80|DMP_MEM|DMP_EOL,0x0	# "00 00 ... 00 00\n"
1066		.asciz "System halted"		# End
1067#
1068# End of BTX memory.
1069#
1070		.p2align 4
1071break:
1072