btx.S revision 176645
1144518Sdavidxu/*
2144518Sdavidxu * Copyright (c) 1998 Robert Nordier
3144518Sdavidxu * All rights reserved.
4144518Sdavidxu *
5144518Sdavidxu * Redistribution and use in source and binary forms are freely
6144518Sdavidxu * permitted provided that the above copyright notice and this
7144518Sdavidxu * paragraph and the following disclaimer are duplicated in all
8144518Sdavidxu * such forms.
9144518Sdavidxu *
10144518Sdavidxu * This software is provided "AS IS" and without any express or
11144518Sdavidxu * implied warranties, including, without limitation, the implied
12144518Sdavidxu * warranties of merchantability and fitness for a particular
13144518Sdavidxu * purpose.
14144518Sdavidxu *
15144518Sdavidxu * $FreeBSD: head/sys/boot/pc98/btx/btx/btx.S 176645 2008-02-28 17:33:06Z nyan $
16144518Sdavidxu */
17144518Sdavidxu
18144518Sdavidxu/*
19144518Sdavidxu * Memory layout.
20144518Sdavidxu */
21144518Sdavidxu		.set MEM_BTX,0x1000		# Start of BTX memory
22144518Sdavidxu		.set MEM_ESP0,0x1800		# Supervisor stack
23144518Sdavidxu		.set MEM_BUF,0x1800		# Scratch buffer
24144518Sdavidxu		.set MEM_ESP1,0x1e00		# Link stack
25144518Sdavidxu		.set MEM_IDT,0x1e00		# IDT
26144518Sdavidxu		.set MEM_TSS,0x1f98		# TSS
27144518Sdavidxu		.set MEM_MAP,0x2000		# I/O bit map
28144518Sdavidxu		.set MEM_TSS_END,0x3fff		# Page directory
29144518Sdavidxu		.set MEM_ORG,0x9000		# BTX code
30144518Sdavidxu		.set MEM_USR,0xa000		# Start of user memory
31144518Sdavidxu/*
32144518Sdavidxu * Paging control.
33177853Sdavidxu */
34177853Sdavidxu		.set PAG_SIZ,0x1000		# Page size
35177853Sdavidxu		.set PAG_CNT,0x1000		# Pages to map
36177853Sdavidxu/*
37177853Sdavidxu * Segment selectors.
38177853Sdavidxu */
39177853Sdavidxu		.set SEL_SCODE,0x8		# Supervisor code
40177853Sdavidxu		.set SEL_SDATA,0x10		# Supervisor data
41177853Sdavidxu		.set SEL_RCODE,0x18		# Real mode code
42163334Sdavidxu		.set SEL_RDATA,0x20		# Real mode data
43163334Sdavidxu		.set SEL_UCODE,0x28|3		# User code
44163334Sdavidxu		.set SEL_UDATA,0x30|3		# User data
45163334Sdavidxu		.set SEL_TSS,0x38		# TSS
46163334Sdavidxu/*
47163334Sdavidxu * Task state segment fields.
48163334Sdavidxu */
49163334Sdavidxu		.set TSS_ESP0,0x4		# PL 0 ESP
50212077Sdavidxu		.set TSS_SS0,0x8		# PL 0 SS
51212077Sdavidxu		.set TSS_ESP1,0xc		# PL 1 ESP
52212077Sdavidxu		.set TSS_MAP,0x66		# I/O bit map base
53212077Sdavidxu/*
54212077Sdavidxu * System calls.
55212077Sdavidxu */
56212077Sdavidxu		.set SYS_EXIT,0x0		# Exit
57144518Sdavidxu		.set SYS_EXEC,0x1		# Exec
58179970Sdavidxu/*
59161680Sdavidxu * V86 constants.
60179970Sdavidxu */
61179970Sdavidxu		.set V86_FLG,0x208eff		# V86 flag mask
62179970Sdavidxu		.set V86_STK,0x400		# V86 stack allowance
63179970Sdavidxu/*
64179970Sdavidxu * Dump format control bytes.
65179970Sdavidxu */
66179970Sdavidxu		.set DMP_X16,0x1		# Word
67179970Sdavidxu		.set DMP_X32,0x2		# Long
68179970Sdavidxu		.set DMP_MEM,0x4		# Memory
69179970Sdavidxu		.set DMP_EOL,0x8		# End of line
70179970Sdavidxu/*
71179970Sdavidxu * Screen defaults and assumptions.
72179970Sdavidxu */
73179970Sdavidxu		.set SCR_MAT,0xe1		# Mode/attribute
74179970Sdavidxu		.set SCR_COL,0x50		# Columns per row
75161680Sdavidxu		.set SCR_ROW,0x19		# Rows per screen
76161680Sdavidxu/*
77161680Sdavidxu * BIOS Data Area locations.
78179970Sdavidxu */
79179970Sdavidxu		.set BDA_MEM,0x501		# Free memory
80161680Sdavidxu		.set BDA_KEYFLAGS,0x53a		# Keyboard shift-state flags
81179970Sdavidxu		.set BDA_POS,0x53e		# Cursor position
82179970Sdavidxu/*
83179970Sdavidxu * Derivations, for brevity.
84179970Sdavidxu */
85179970Sdavidxu		.set _ESP0H,MEM_ESP0>>0x8	# Byte 1 of ESP0
86179970Sdavidxu		.set _ESP1H,MEM_ESP1>>0x8	# Byte 1 of ESP1
87179970Sdavidxu		.set _TSSIO,MEM_MAP-MEM_TSS	# TSS I/O base
88179970Sdavidxu		.set _TSSLM,MEM_TSS_END-MEM_TSS	# TSS limit
89161680Sdavidxu		.set _IDTLM,MEM_TSS-MEM_IDT-1	# IDT limit
90179970Sdavidxu/*
91179970Sdavidxu * Code segment.
92179970Sdavidxu */
93179970Sdavidxu		.globl start
94179970Sdavidxu		.code16
95179970Sdavidxustart:						# Start of code
96179970Sdavidxu/*
97179970Sdavidxu * BTX header.
98179970Sdavidxu */
99179970Sdavidxubtx_hdr:	.byte 0xeb			# Machine ID
100179970Sdavidxu		.byte 0xe			# Header size
101179970Sdavidxu		.ascii "BTX"			# Magic
102179970Sdavidxu		.byte 0x1			# Major version
103179970Sdavidxu		.byte 0x1			# Minor version
104179970Sdavidxu		.byte BTX_FLAGS			# Flags
105179970Sdavidxu		.word PAG_CNT-MEM_ORG>>0xc	# Paging control
106179970Sdavidxu		.word break-start		# Text size
107179970Sdavidxu		.long 0x0			# Entry address
108179970Sdavidxu/*
109179970Sdavidxu * Initialization routine.
110179970Sdavidxu */
111179970Sdavidxuinit:		cli				# Disable interrupts
112179970Sdavidxu		xor %ax,%ax			# Zero/segment
113179970Sdavidxu		mov %ax,%ss			# Set up
114179970Sdavidxu		mov $MEM_ESP0,%sp		#  stack
115179970Sdavidxu		mov %ax,%es			# Address
116179970Sdavidxu		mov %ax,%ds			#  data
117161680Sdavidxu		pushl $0x2			# Clear
118161680Sdavidxu		popfl				#  flags
119161680Sdavidxu/*
120179970Sdavidxu * Initialize memory.
121161680Sdavidxu */
122200498Smarcel		mov $MEM_IDT,%di		# Memory to initialize
123200498Smarcel		mov $(MEM_ORG-MEM_IDT)/2,%cx	# Words to zero
124179970Sdavidxu		push %di			# Save
125179970Sdavidxu		rep				# Zero-fill
126179970Sdavidxu		stosw				#  memory
127179970Sdavidxu		pop %di				# Restore
128200498Smarcel/*
129177853Sdavidxu * Create IDT.
130161680Sdavidxu */
131161680Sdavidxu		mov $idtctl,%si			# Control string
132161680Sdavidxuinit.1: 	lodsb				# Get entry
133163334Sdavidxu		cbw				#  count
134161680Sdavidxu		xchg %ax,%cx			#  as word
135177853Sdavidxu		jcxz init.4			# If done
136161680Sdavidxu		lodsb				# Get segment
137161680Sdavidxu		xchg %ax,%dx	 		#  P:DPL:type
138161680Sdavidxu		lodsw				# Get control
139161680Sdavidxu		xchg %ax,%bx			#  set
140161680Sdavidxu		lodsw				# Get handler offset
141161680Sdavidxu		mov $SEL_SCODE,%dh		# Segment selector
142177853Sdavidxuinit.2: 	shr %bx				# Handle this int?
143161680Sdavidxu		jnc init.3			# No
144161680Sdavidxu		mov %ax,(%di)			# Set handler offset
145161680Sdavidxu		mov %dh,0x2(%di)		#  and selector
146173801Sdavidxu		mov %dl,0x5(%di)		# Set P:DPL:type
147144518Sdavidxu		add $0x4,%ax			# Next handler
148144518Sdavidxuinit.3: 	lea 0x8(%di),%di		# Next entry
149144518Sdavidxu		loop init.2			# Till set done
150144518Sdavidxu		jmp init.1			# Continue
151177853Sdavidxu/*
152177853Sdavidxu * Initialize TSS.
153144518Sdavidxu */
154144518Sdavidxuinit.4: 	movb $_ESP0H,TSS_ESP0+1(%di)	# Set ESP0
155144518Sdavidxu		movb $SEL_SDATA,TSS_SS0(%di)	# Set SS0
156178647Sdavidxu		movb $_ESP1H,TSS_ESP1+1(%di)	# Set ESP1
157144518Sdavidxu		movb $_TSSIO,TSS_MAP(%di)	# Set I/O bit map base
158173801Sdavidxu/*
159173801Sdavidxu * Bring up the system.
160173801Sdavidxu */
161178647Sdavidxu		mov $0x2820,%bx			# Set protected mode
162178647Sdavidxu		callw setpic			#  IRQ offsets
163178647Sdavidxu		lidt idtdesc	 		# Set IDT
164173801Sdavidxu		lgdt gdtdesc	 		# Set GDT
165173801Sdavidxu		mov %cr0,%eax			# Switch to protected
166173801Sdavidxu		inc %ax				#  mode
167178647Sdavidxu		mov %eax,%cr0			#
168173801Sdavidxu		ljmp $SEL_SCODE,$init.8		# To 32-bit code
169178647Sdavidxu		.code32
170177853Sdavidxuinit.8: 	xorl %ecx,%ecx			# Zero
171144518Sdavidxu		movb $SEL_SDATA,%cl		# To 32-bit
172164877Sdavidxu		movw %cx,%ss			#  stack
173164902Sdavidxu/*
174164902Sdavidxu * Launch user task.
175164902Sdavidxu */
176164902Sdavidxu		movb $SEL_TSS,%cl		# Set task
177164902Sdavidxu		ltr %cx				#  register
178164902Sdavidxu		movl $MEM_USR,%edx		# User base address
179164877Sdavidxu		movzwl %ss:BDA_MEM,%eax 	# Get free memory
180164877Sdavidxu		andl $0x7,%eax
181164877Sdavidxu		incl %eax
182164877Sdavidxu		shll $0x11,%eax			# To bytes
183164877Sdavidxu		subl $0x1000,%eax		# Less arg space
184164877Sdavidxu		subl %edx,%eax			# Less base
185179970Sdavidxu		movb $SEL_UDATA,%cl		# User data selector
186179970Sdavidxu		pushl %ecx			# Set SS
187164877Sdavidxu		pushl %eax			# Set ESP
188164877Sdavidxu		push $0x202			# Set flags (IF set)
189177853Sdavidxu		push $SEL_UCODE			# Set CS
190164878Sdavidxu		pushl btx_hdr+0xc		# Set EIP
191177853Sdavidxu		pushl %ecx			# Set GS
192164877Sdavidxu		pushl %ecx			# Set FS
193164877Sdavidxu		pushl %ecx			# Set DS
194164877Sdavidxu		pushl %ecx			# Set ES
195164877Sdavidxu		pushl %edx			# Set EAX
196164877Sdavidxu		movb $0x7,%cl			# Set remaining
197165110Sdavidxuinit.9:		push $0x0			#  general
198165110Sdavidxu		loop init.9			#  registers
199177853Sdavidxu#ifdef BTX_SERIAL
200164877Sdavidxu		call sio_init			# setup the serial console
201164877Sdavidxu#endif
202164877Sdavidxu		popa				#  and initialize
203164877Sdavidxu		popl %es			# Initialize
204164877Sdavidxu		popl %ds			#  user
205165110Sdavidxu		popl %fs			#  segment
206165110Sdavidxu		popl %gs			#  registers
207177853Sdavidxu		iret				# To user mode
208164877Sdavidxu/*
209177850Sdavidxu * Exit routine.
210177850Sdavidxu */
211177850Sdavidxuexit:		cli				# Disable interrupts
212177850Sdavidxu		movl $MEM_ESP0,%esp		# Clear stack
213177853Sdavidxu/*
214177850Sdavidxu * Turn off paging.
215177850Sdavidxu */
216177850Sdavidxu		movl %cr0,%eax			# Get CR0
217177850Sdavidxu		andl $~0x80000000,%eax		# Disable
218177850Sdavidxu		movl %eax,%cr0			#  paging
219177853Sdavidxu		xorl %ecx,%ecx			# Zero
220177850Sdavidxu		movl %ecx,%cr3			# Flush TLB
221177850Sdavidxu/*
222177850Sdavidxu * Restore the GDT in case we caught a kernel trap.
223177850Sdavidxu */
224177850Sdavidxu		lgdt gdtdesc	 		# Set GDT
225177853Sdavidxu/*
226177850Sdavidxu * To 16 bits.
227212076Sdavidxu */
228212076Sdavidxu		ljmpw $SEL_RCODE,$exit.1	# Reload CS
229212076Sdavidxu		.code16
230212076Sdavidxuexit.1: 	mov $SEL_RDATA,%cl		# 16-bit selector
231212076Sdavidxu		mov %cx,%ss			# Reload SS
232212076Sdavidxu		mov %cx,%ds			# Load
233212076Sdavidxu		mov %cx,%es			#  remaining
234212076Sdavidxu		mov %cx,%fs			#  segment
235212076Sdavidxu		mov %cx,%gs			#  registers
236212076Sdavidxu/*
237212076Sdavidxu * To real-address mode.
238212076Sdavidxu */
239212076Sdavidxu		dec %ax				# Switch to
240212076Sdavidxu		mov %eax,%cr0			#  real mode
241212076Sdavidxu		ljmp $0x0,$exit.2		# Reload CS
242212076Sdavidxuexit.2: 	xor %ax,%ax			# Real mode segment
243212076Sdavidxu		mov %ax,%ss			# Reload SS
244212076Sdavidxu		mov %ax,%ds			# Address data
245212076Sdavidxu		mov $0x1008,%bx			# Set real mode
246212076Sdavidxu		callw setpic			#  IRQ offsets
247212076Sdavidxu		lidt ivtdesc	 		# Set IVT
248212076Sdavidxu/*
249212076Sdavidxu * Reboot or await reset.
250212076Sdavidxu */
251212076Sdavidxu		sti				# Enable interrupts
252212076Sdavidxu		testb $0x1,btx_hdr+0x7		# Reboot?
253212076Sdavidxuexit.3:		jz exit.3			# No
254212076Sdavidxu		movb $0xa0,%al
255212076Sdavidxu		outb %al,$0x35
256212076Sdavidxu		movb 0,%al
257212076Sdavidxu		outb %al,$0xf0
258212076Sdavidxuexit.4:		jmp exit.4
259212076Sdavidxu/*
260212076Sdavidxu * Set IRQ offsets by reprogramming 8259A PICs.
261212076Sdavidxu */
262212076Sdavidxusetpic: 	in $0x02,%al			# Save master
263212076Sdavidxu		push %ax			#  IMR
264212076Sdavidxu		in $0x0a,%al			# Save slave
265212076Sdavidxu		push %ax			#  IMR
266		movb $0x11,%al			# ICW1 to
267		outb %al,$0x00			#  master,
268		outb %al,$0x08			#  slave
269		movb %bl,%al			# ICW2 to
270		outb %al,$0x02			#  master
271		movb %bh,%al			# ICW2 to
272		outb %al,$0x0a			#  slave
273		movb $0x80,%al			# ICW3 to
274		outb %al,$0x02			#  master
275		movb $0x7,%al			# ICW3 to
276		outb %al,$0x0a			#  slave
277		movb $0x1d,%al			# ICW4 to
278		outb %al,$0x02			#  master,
279		movb $0x9,%al			# ICW4 to
280		outb %al,$0x0a			#  slave
281		pop %ax				# Restore slave
282		outb %al,$0x0a			#  IMR
283		pop %ax				# Restore master
284		outb %al,$0x02			#  IMR
285		retw				# To caller
286		.code32
287/*
288 * Initiate return from V86 mode to user mode.
289 */
290inthlt: 	hlt				# To supervisor mode
291/*
292 * Exception jump table.
293 */
294intx00: 	push $0x0			# Int 0x0: #DE
295		jmp ex_noc			# Divide error
296		push $0x1			# Int 0x1: #DB
297		jmp ex_noc			# Debug
298		push $0x3			# Int 0x3: #BP
299		jmp ex_noc			# Breakpoint
300		push $0x4			# Int 0x4: #OF
301		jmp ex_noc			# Overflow
302		push $0x5			# Int 0x5: #BR
303		jmp ex_noc			# BOUND range exceeded
304		push $0x6			# Int 0x6: #UD
305		jmp ex_noc			# Invalid opcode
306		push $0x7			# Int 0x7: #NM
307		jmp ex_noc			# Device not available
308		push $0x8			# Int 0x8: #DF
309		jmp except			# Double fault
310		push $0xa			# Int 0xa: #TS
311		jmp except			# Invalid TSS
312		push $0xb			# Int 0xb: #NP
313		jmp except			# Segment not present
314		push $0xc			# Int 0xc: #SS
315		jmp except			# Stack segment fault
316		push $0xd			# Int 0xd: #GP
317		jmp ex_v86			# General protection
318		push $0xe			# Int 0xe: #PF
319		jmp except			# Page fault
320intx10: 	push $0x10			# Int 0x10: #MF
321		jmp ex_noc			# Floating-point error
322/*
323 * Handle #GP exception.
324 */
325ex_v86: 	testb $0x2,0x12(%esp,1) 	# V86 mode?
326		jz except			# No
327		jmp v86mon			# To monitor
328/*
329 * Save a zero error code.
330 */
331ex_noc: 	pushl (%esp,1)			# Duplicate int no
332		movb $0x0,0x4(%esp,1)		# Fake error code
333/*
334 * Handle exception.
335 */
336except: 	cld				# String ops inc
337		pushl %ds			# Save
338		pushl %es			#  most
339		pusha				#  registers
340		movb $0x6,%al			# Push loop count
341		testb $0x2,0x3a(%esp,1) 	# V86 mode?
342		jnz except.1			# Yes
343		pushl %gs			# Set GS
344		pushl %fs			# Set FS
345		pushl %ds			# Set DS
346		pushl %es			# Set ES
347		movb $0x2,%al			# Push loop count
348		cmpw $SEL_SCODE,0x44(%esp,1)	# Supervisor mode?
349		jne except.1			# No
350		pushl %ss			# Set SS
351		leal 0x50(%esp,1),%eax		# Set
352		pushl %eax			#  ESP
353		jmp except.2			# Join common code
354except.1:	pushl 0x50(%esp,1)		# Set GS, FS, DS, ES
355		decb %al			#  (if V86 mode), and
356		jne except.1			#  SS, ESP
357except.2:	push $SEL_SDATA			# Set up
358		popl %ds			#  to
359		pushl %ds			#  address
360		popl %es			#  data
361		movl %esp,%ebx			# Stack frame
362		movl $dmpfmt,%esi		# Dump format string
363		movl $MEM_BUF,%edi		# Buffer
364		pushl %eax
365		pushl %edx
366wait.1:
367		inb  $0x60,%al
368		testb $0x04,%al
369		jz   wait.1
370		movb $0xe0,%al
371		outb %al,$0x62
372wait.2:
373		inb  $0x60,%al
374		testb $0x01,%al
375		jz   wait.2
376		xorl %edx,%edx
377		inb  $0x62,%al
378		movb %al,%dl
379		inb  $0x62,%al
380		movb %al,%dh
381		inb  $0x62,%al
382		inb  $0x62,%al
383		inb  $0x62,%al
384		movl %edx,%eax
385		shlw $1,%ax
386		movl $BDA_POS,%edx
387		movw %ax,(%edx)
388		popl  %edx
389		popl  %eax
390		pushl %edi			# Dump to
391		call dump			#  buffer
392		popl %esi			#  and
393		call putstr			#  display
394		leal 0x18(%esp,1),%esp		# Discard frame
395		popa				# Restore
396		popl %es			#  registers
397		popl %ds			#  saved
398		cmpb $0x3,(%esp,1)		# Breakpoint?
399		je except.3			# Yes
400		cmpb $0x1,(%esp,1)		# Debug?
401		jne except.2a			# No
402		testl $0x100,0x10(%esp,1)	# Trap flag set?
403		jnz except.3			# Yes
404except.2a:	jmp exit			# Exit
405except.3:	leal 0x8(%esp,1),%esp		# Discard err, int no
406		iret				# From interrupt
407/*
408 * Return to user mode from V86 mode.
409 */
410intrtn: 	cld				# String ops inc
411		pushl %ds			# Address
412		popl %es			#  data
413		leal 0x3c(%ebp),%edx		# V86 Segment registers
414		movl MEM_TSS+TSS_ESP1,%esi	# Link stack pointer
415		lodsl				# INT_V86 args pointer
416		movl %esi,%ebx			# Saved exception frame
417		testl %eax,%eax 		# INT_V86 args?
418		jz intrtn.2			# No
419		movl $MEM_USR,%edi		# User base
420		movl 0x1c(%esi),%ebx		# User ESP
421		movl %eax,(%edi,%ebx,1) 	# Restore to user stack
422		leal 0x8(%edi,%eax,1),%edi	# Arg segment registers
423		testb $0x4,-0x6(%edi)		# Return flags?
424		jz intrtn.1			# No
425		movl 0x30(%ebp),%eax		# Get V86 flags
426		movw %ax,0x18(%esi)		# Set user flags
427intrtn.1:	leal 0x10(%esi),%ebx		# Saved exception frame
428		xchgl %edx,%esi 		# Segment registers
429		movb $0x4,%cl			# Update seg regs
430		rep				#  in INT_V86
431		movsl				#  args
432intrtn.2:	xchgl %edx,%esi			# Segment registers
433		leal 0x28(%ebp),%edi		# Set up seg
434		movb $0x4,%cl			#  regs for
435		rep				#  later
436		movsl				#  pop
437		xchgl %ebx,%esi			# Restore exception
438		movb $0x5,%cl			#  frame to
439		rep				#  supervisor
440		movsl				#  stack
441		movl %esi,MEM_TSS+TSS_ESP1	# Link stack pointer
442		popa				# Restore
443		leal 0x8(%esp,1),%esp		# Discard err, int no
444		popl %es			# Restore
445		popl %ds			#  user
446		popl %fs			#  segment
447		popl %gs			#  registers
448		iret				# To user mode
449/*
450 * V86 monitor.
451 */
452v86mon: 	cld				# String ops inc
453		pushl $SEL_SDATA		# Set up for
454		popl %ds			#  flat addressing
455		pusha				# Save registers
456		movl %esp,%ebp			# Address stack frame
457		movzwl 0x2c(%ebp),%edi		# Load V86 CS
458		shll $0x4,%edi			# To linear
459		movl 0x28(%ebp),%esi		# Load V86 IP
460		addl %edi,%esi			# Code pointer
461		xorl %ecx,%ecx			# Zero
462		movb $0x2,%cl			# 16-bit operands
463		xorl %eax,%eax			# Zero
464v86mon.1:	lodsb				# Get opcode
465		cmpb $0x66,%al			# Operand size prefix?
466		jne v86mon.2			# No
467		movb $0x4,%cl			# 32-bit operands
468		jmp v86mon.1			# Continue
469v86mon.2:	cmpb $0xf4,%al			# HLT?
470		jne v86mon.3			# No
471		cmpl $inthlt+0x1,%esi		# Is inthlt?
472		jne v86mon.7			# No (ignore)
473		jmp intrtn			# Return to user mode
474v86mon.3:	cmpb $0xf,%al			# Prefixed instruction?
475		jne v86mon.4			# No
476		cmpb $0x09,(%esi)		# Is it a WBINVD?
477		je v86wbinvd			# Yes
478		cmpb $0x30,(%esi)		# Is it a WRMSR?
479		je v86wrmsr			# Yes
480		cmpb $0x32,(%esi)		# Is it a RDMSR?
481		je v86rdmsr			# Yes
482		cmpb $0x20,(%esi)		# Is this a MOV reg,CRx?
483		je v86mov			# Yes
484v86mon.4:	cmpb $0xfa,%al			# CLI?
485		je v86cli			# Yes
486		cmpb $0xfb,%al			# STI?
487		je v86sti			# Yes
488		movzwl 0x38(%ebp),%ebx		# Load V86 SS
489		shll $0x4,%ebx			# To offset
490		pushl %ebx			# Save
491		addl 0x34(%ebp),%ebx		# Add V86 SP
492		movl 0x30(%ebp),%edx		# Load V86 flags
493		cmpb $0x9c,%al			# PUSHF/PUSHFD?
494		je v86pushf			# Yes
495		cmpb $0x9d,%al			# POPF/POPFD?
496		je v86popf			# Yes
497		cmpb $0xcd,%al			# INT imm8?
498		je v86intn			# Yes
499		cmpb $0xcf,%al			# IRET/IRETD?
500		je v86iret			# Yes
501		popl %ebx			# Restore
502		popa				# Restore
503		jmp except			# Handle exception
504v86mon.5:	movl %edx,0x30(%ebp)		# Save V86 flags
505v86mon.6:	popl %edx			# V86 SS adjustment
506		subl %edx,%ebx			# Save V86
507		movl %ebx,0x34(%ebp)		#  SP
508v86mon.7:	subl %edi,%esi			# From linear
509		movl %esi,0x28(%ebp)		# Save V86 IP
510		popa				# Restore
511		leal 0x8(%esp,1),%esp		# Discard int no, error
512		iret				# To V86 mode
513/*
514 * Emulate MOV reg,CRx.
515 */
516v86mov: 	movb 0x1(%esi),%bl		# Fetch Mod R/M byte
517		testb $0x10,%bl			# Read CR2 or CR3?
518		jnz v86mov.1			# Yes
519		movl %cr0,%eax			# Read CR0
520		testb $0x20,%bl			# Read CR4 instead?
521		jz v86mov.2			# No
522		movl %cr4,%eax			# Read CR4
523		jmp v86mov.2
524v86mov.1:	movl %cr2,%eax			# Read CR2
525		testb $0x08,%bl			# Read CR3 instead?
526		jz v86mov.2			# No
527		movl %cr3,%eax			# Read CR3
528v86mov.2:	andl $0x7,%ebx			# Compute offset in
529		shl $2,%ebx			#  frame of destination
530		neg %ebx			#  register
531		movl %eax,0x1c(%ebp,%ebx,1)	# Store CR to reg
532		incl %esi			# Adjust IP
533/*
534 * Return from emulating a 0x0f prefixed instruction
535 */
536v86preret:	incl %esi			# Adjust IP
537		jmp v86mon.7			# Finish up
538/*
539 * Emulate WBINVD
540 */
541v86wbinvd:	wbinvd				# Write back and invalidate
542						#  cache
543		jmp v86preret			# Finish up
544/*
545 * Emulate WRMSR
546 */
547v86wrmsr:	movl 0x18(%ebp),%ecx		# Get user's %ecx (MSR to write)
548		movl 0x14(%ebp),%edx		# Load the value
549		movl 0x1c(%ebp),%eax		#  to write
550		wrmsr				# Write MSR
551		jmp v86preret			# Finish up
552/*
553 * Emulate RDMSR
554 */
555v86rdmsr:	movl 0x18(%ebp),%ecx		# MSR to read
556		rdmsr				# Read the MSR
557		movl %eax,0x1c(%ebp)		# Return the value of
558		movl %edx,0x14(%ebp)		#  the MSR to the user
559		jmp v86preret			# Finish up
560/*
561 * Emulate CLI.
562 */
563v86cli: 	andb $~0x2,0x31(%ebp)		# Clear IF
564		jmp v86mon.7			# Finish up
565/*
566 * Emulate STI.
567 */
568v86sti: 	orb $0x2,0x31(%ebp)		# Set IF
569		jmp v86mon.7			# Finish up
570/*
571 * Emulate PUSHF/PUSHFD.
572 */
573v86pushf:	subl %ecx,%ebx			# Adjust SP
574		cmpb $0x4,%cl			# 32-bit
575		je v86pushf.1			# Yes
576		data16				# 16-bit
577v86pushf.1:	movl %edx,(%ebx)		# Save flags
578		jmp v86mon.6			# Finish up
579/*
580 * Emulate IRET/IRETD.
581 */
582v86iret:	movzwl (%ebx),%esi		# Load V86 IP
583		movzwl 0x2(%ebx),%edi		# Load V86 CS
584		leal 0x4(%ebx),%ebx		# Adjust SP
585		movl %edi,0x2c(%ebp)		# Save V86 CS
586		xorl %edi,%edi			# No ESI adjustment
587/*
588 * Emulate POPF/POPFD (and remainder of IRET/IRETD).
589 */
590v86popf:	cmpb $0x4,%cl			# 32-bit?
591		je v86popf.1			# Yes
592		movl %edx,%eax			# Initialize
593		data16				# 16-bit
594v86popf.1:	movl (%ebx),%eax		# Load flags
595		addl %ecx,%ebx			# Adjust SP
596		andl $V86_FLG,%eax		# Merge
597		andl $~V86_FLG,%edx		#  the
598		orl %eax,%edx			#  flags
599		jmp v86mon.5			# Finish up
600/*
601 * trap int 15, function 87
602 * reads %es:%si from saved registers on stack to find a GDT containing
603 * source and destination locations
604 * reads count of words from saved %cx
605 * returns success by setting %ah to 0
606 */
607int15_87:	pushl %esi			# Save
608		pushl %edi			#  registers
609		movl 0x3C(%ebp),%edi		# Load ES
610		movzwl 0x4(%ebp),%eax		# Load user's SI
611		shll $0x4,%edi			# EDI = (ES << 4) +
612		addl %eax,%edi			#   SI
613		movl 0x11(%edi),%eax		# Read base of
614		movb 0x17(%edi),%al		#  GDT entry
615		ror $8,%eax			#  for source
616		xchgl %eax,%esi			#  into %esi
617		movl 0x19(%edi),%eax		# Read base of
618		movb 0x1f(%edi),%al		#  GDT entry for
619		ror $8,%eax			#  destination
620		xchgl %eax,%edi			#  into %edi
621		pushl %ds			# Make:
622		popl %es			# es = ds
623		movzwl 0x18(%ebp),%ecx		# Get user's CX
624		shll $0x1,%ecx			# Convert count from words
625		rep				# repeat...
626		movsb				#  perform copy.
627		popl %edi			# Restore
628		popl %esi			#  registers
629		movb $0x0,0x1d(%ebp)		# set ah = 0 to indicate
630						#  success
631		andb $0xfe,%dl			# clear CF
632		jmp v86mon.5			# Finish up
633
634/*
635 * Reboot the machine by setting the reboot flag and exiting
636 */
637reboot:		orb $0x1,btx_hdr+0x7		# Set the reboot flag
638		jmp exit			# Terminate BTX and reboot
639
640/*
641 * Emulate INT imm8... also make sure to check if it's int 15/87
642 */
643v86intn:	lodsb				# Get int no
644		cmpb $0x19,%al			# is it int 19?
645		je reboot			#  yes, reboot the machine
646		cmpb $0x15,%al			# is it int 15?
647		jne v86intn.1			#  no, skip parse
648		cmpb $0x87,0x1d(%ebp)		# is it the memcpy subfunction?
649		je int15_87			#  yes
650		cmpw $0x4f53,0x1c(%ebp)		# is it the delete key callout?
651		jne v86intn.1			#  no, handle the int normally
652		movb BDA_KEYFLAGS,%ch		# get the shift key state
653		andb $0x18,%ch			# mask off just Ctrl and Alt
654		cmpb $0x18,%ch			# are both Ctrl and Alt down?
655		je reboot			# yes, reboot the machine
656v86intn.1:	subl %edi,%esi			# From
657		shrl $0x4,%edi			#  linear
658		movw %dx,-0x2(%ebx)		# Save flags
659		movw %di,-0x4(%ebx)		# Save CS
660		leal -0x6(%ebx),%ebx		# Adjust SP
661		movw %si,(%ebx) 		# Save IP
662		shll $0x2,%eax			# Scale
663		movzwl (%eax),%esi		# Load IP
664		movzwl 0x2(%eax),%edi		# Load CS
665		movl %edi,0x2c(%ebp)		# Save CS
666		xorl %edi,%edi			# No ESI adjustment
667		andb $~0x1,%dh			# Clear TF
668		jmp v86mon.5			# Finish up
669/*
670 * Hardware interrupt jump table.
671 */
672intx20: 	push $0x8			# Int 0x20: IRQ0
673		jmp int_hw			# V86 int 0x8
674		push $0x9			# Int 0x21: IRQ1
675		jmp int_hw			# V86 int 0x9
676		push $0xa			# Int 0x22: IRQ2
677		jmp int_hw			# V86 int 0xa
678		push $0xb			# Int 0x23: IRQ3
679		jmp int_hw			# V86 int 0xb
680		push $0xc			# Int 0x24: IRQ4
681		jmp int_hw			# V86 int 0xc
682		push $0xd			# Int 0x25: IRQ5
683		jmp int_hw			# V86 int 0xd
684		push $0xe			# Int 0x26: IRQ6
685		jmp int_hw			# V86 int 0xe
686		push $0xf			# Int 0x27: IRQ7
687		jmp int_hw			# V86 int 0xf
688		push $0x10			# Int 0x28: IRQ8
689		jmp int_hw			# V86 int 0x10
690		push $0x11			# Int 0x29: IRQ9
691		jmp int_hw			# V86 int 0x11
692		push $0x12			# Int 0x2a: IRQ10
693		jmp int_hw			# V86 int 0x12
694		push $0x13			# Int 0x2b: IRQ11
695		jmp int_hw			# V86 int 0x13
696		push $0x14			# Int 0x2c: IRQ12
697		jmp int_hw			# V86 int 0x14
698		push $0x15			# Int 0x2d: IRQ13
699		jmp int_hw			# V86 int 0x15
700		push $0x16			# Int 0x2e: IRQ14
701		jmp int_hw			# V86 int 0x16
702		push $0x17			# Int 0x2f: IRQ15
703		jmp int_hw			# V86 int 0x17
704/*
705 * Reflect hardware interrupts.
706 */
707int_hw: 	testb $0x2,0xe(%esp,1)		# V86 mode?
708		jz intusr			# No
709		pushl $SEL_SDATA		# Address
710		popl %ds			#  data
711		xchgl %eax,(%esp,1)		# Swap EAX, int no
712		pushl %ebp			# Address
713		movl %esp,%ebp			#  stack frame
714		pushl %ebx			# Save
715		shll $0x2,%eax			# Get int
716		movl (%eax),%eax		#  vector
717		subl $0x6,0x14(%ebp)		# Adjust V86 ESP
718		movzwl 0x18(%ebp),%ebx		# V86 SS
719		shll $0x4,%ebx			#  * 0x10
720		addl 0x14(%ebp),%ebx		#  + V86 ESP
721		xchgw %ax,0x8(%ebp)		# Swap V86 IP
722		rorl $0x10,%eax 		# Swap words
723		xchgw %ax,0xc(%ebp)		# Swap V86 CS
724		roll $0x10,%eax 		# Swap words
725		movl %eax,(%ebx)		# CS:IP for IRET
726		movl 0x10(%ebp),%eax		# V86 flags
727		movw %ax,0x4(%ebx)		# Flags for IRET
728		andb $~0x3,0x11(%ebp)		# Clear IF, TF
729		popl %ebx			# Restore
730		popl %ebp			#  saved
731		popl %eax			#  registers
732		iret				# To V86 mode
733/*
734 * Invoke V86 interrupt from user mode, with arguments.
735 */
736intx31: 	stc				# Have btx_v86
737		pushl %eax			# Missing int no
738/*
739 * Invoke V86 interrupt from user mode.
740 */
741intusr: 	std				# String ops dec
742		pushl %eax			# Expand
743		pushl %eax			#  stack
744		pushl %eax			#  frame
745		pusha				# Save
746		pushl %gs			# Save
747		movl %esp,%eax			#  seg regs
748		pushl %fs			#  and
749		pushl %ds			#  point
750		pushl %es			#  to them
751		push $SEL_SDATA			# Set up
752		popl %ds			#  to
753		pushl %ds			#  address
754		popl %es			#  data
755		movl $MEM_USR,%ebx		# User base
756		movl %ebx,%edx			#  address
757		jc intusr.1			# If btx_v86
758		xorl %edx,%edx			# Control flags
759		xorl %ebp,%ebp			# btx_v86 pointer
760intusr.1:	leal 0x50(%esp,1),%esi		# Base of frame
761		pushl %esi			# Save
762		addl -0x4(%esi),%ebx		# User ESP
763		movl MEM_TSS+TSS_ESP1,%edi	# Link stack pointer
764		leal -0x4(%edi),%edi		# Adjust for push
765		xorl %ecx,%ecx			# Zero
766		movb $0x5,%cl			# Push exception
767		rep				#  frame on
768		movsl				#  link stack
769		xchgl %eax,%esi 		# Saved seg regs
770		movl 0x40(%esp,1),%eax		# Get int no
771		testl %edx,%edx 		# Have btx_v86?
772		jz intusr.2			# No
773		movl (%ebx),%ebp		# btx_v86 pointer
774		movb $0x4,%cl			# Count
775		addl %ecx,%ebx			# Adjust for pop
776		rep				# Push saved seg regs
777		movsl				#  on link stack
778		addl %ebp,%edx			# Flatten btx_v86 ptr
779		leal 0x14(%edx),%esi		# Seg regs pointer
780		movl 0x4(%edx),%eax		# Get int no/address
781		movzwl 0x2(%edx),%edx		# Get control flags
782intusr.2:	movl %ebp,(%edi)		# Push btx_v86 and
783		movl %edi,MEM_TSS+TSS_ESP1	#  save link stack ptr
784		popl %edi			# Base of frame
785		xchgl %eax,%ebp 		# Save intno/address
786		movl 0x48(%esp,1),%eax		# Get flags
787		testb $0x2,%dl			# Simulate CALLF?
788		jnz intusr.3			# Yes
789		decl %ebx			# Push flags
790		decl %ebx			#  on V86
791		movw %ax,(%ebx) 		#  stack
792intusr.3:	movb $0x4,%cl			# Count
793		subl %ecx,%ebx			# Push return address
794		movl $inthlt,(%ebx)		#  on V86 stack
795		rep				# Copy seg regs to
796		movsl				#  exception frame
797		xchgl %eax,%ecx 		# Save flags
798		movl %ebx,%eax			# User ESP
799		subl $V86_STK,%eax		# Less bytes
800		ja intusr.4			#  to
801		xorl %eax,%eax			#  keep
802intusr.4:	shrl $0x4,%eax			# Gives segment
803		stosl				# Set SS
804		shll $0x4,%eax			# To bytes
805		xchgl %eax,%ebx 		# Swap
806		subl %ebx,%eax			# Gives offset
807		stosl				# Set ESP
808		xchgl %eax,%ecx 		# Get flags
809		btsl $0x11,%eax 		# Set VM
810		andb $~0x1,%ah			# Clear TF
811		stosl				# Set EFL
812		xchgl %eax,%ebp 		# Get int no/address
813		testb $0x1,%dl			# Address?
814		jnz intusr.5			# Yes
815		shll $0x2,%eax			# Scale
816		movl (%eax),%eax		# Load int vector
817intusr.5:	movl %eax,%ecx			# Save
818		shrl $0x10,%eax 		# Gives segment
819		stosl				# Set CS
820		movw %cx,%ax			# Restore
821		stosl				# Set EIP
822		leal 0x10(%esp,1),%esp		# Discard seg regs
823		popa				# Restore
824		iret				# To V86 mode
825/*
826 * System Call.
827 */
828intx30: 	cmpl $SYS_EXEC,%eax		# Exec system call?
829		jne intx30.1			# No
830		pushl %ss			# Set up
831		popl %es			#  all
832		pushl %es			#  segment
833		popl %ds			#  registers
834		pushl %ds			#  for the
835		popl %fs			#  program
836		pushl %fs			#  we're
837		popl %gs			#  invoking
838		movl $MEM_USR,%eax		# User base address
839		addl 0xc(%esp,1),%eax		# Change to user
840		leal 0x4(%eax),%esp		#  stack
841		popl %eax			# Call
842		call *%eax			#  program
843intx30.1:	orb $0x1,%ss:btx_hdr+0x7	# Flag reboot
844		jmp exit			# Exit
845/*
846 * Dump structure [EBX] to [EDI], using format string [ESI].
847 */
848dump.0: 	stosb				# Save char
849dump:		lodsb				# Load char
850		testb %al,%al			# End of string?
851		jz dump.10			# Yes
852		testb $0x80,%al 		# Control?
853		jz dump.0			# No
854		movb %al,%ch			# Save control
855		movb $'=',%al			# Append
856		stosb				#  '='
857		lodsb				# Get offset
858		pushl %esi			# Save
859		movsbl %al,%esi 		# To
860		addl %ebx,%esi			#  pointer
861		testb $DMP_X16,%ch		# Dump word?
862		jz dump.1			# No
863		lodsw				# Get and
864		call hex16			#  dump it
865dump.1: 	testb $DMP_X32,%ch		# Dump long?
866		jz dump.2			# No
867		lodsl				# Get and
868		call hex32			#  dump it
869dump.2: 	testb $DMP_MEM,%ch		# Dump memory?
870		jz dump.8			# No
871		pushl %ds			# Save
872		testb $0x2,0x52(%ebx)		# V86 mode?
873		jnz dump.3			# Yes
874		verr 0x4(%esi)	 		# Readable selector?
875		jnz dump.3			# No
876		ldsl (%esi),%esi		# Load pointer
877		jmp dump.4			# Join common code
878dump.3: 	lodsl				# Set offset
879		xchgl %eax,%edx 		# Save
880		lodsl				# Get segment
881		shll $0x4,%eax			#  * 0x10
882		addl %edx,%eax			#  + offset
883		xchgl %eax,%esi 		# Set pointer
884dump.4: 	movb $2,%dl			# Num lines
885dump.4a:	movb $0x10,%cl			# Bytes to dump
886dump.5: 	lodsb				# Get byte and
887		call hex8			#  dump it
888		decb %cl			# Keep count
889		jz dump.6a			# If done
890		movb $'-',%al			# Separator
891		cmpb $0x8,%cl			# Half way?
892		je dump.6			# Yes
893		movb $' ',%al			# Use space
894dump.6: 	stosb				# Save separator
895		jmp dump.5			# Continue
896dump.6a:	decb %dl			# Keep count
897		jz dump.7			# If done
898		movb $0xa,%al			# Line feed
899		stosb				# Save one
900		movb $7,%cl			# Leading
901		movb $' ',%al			#  spaces
902dump.6b:	stosb				# Dump
903		decb %cl			#  spaces
904		jnz dump.6b
905		jmp dump.4a			# Next line
906dump.7: 	popl %ds			# Restore
907dump.8: 	popl %esi			# Restore
908		movb $0xa,%al			# Line feed
909		testb $DMP_EOL,%ch		# End of line?
910		jnz dump.9			# Yes
911		movb $' ',%al			# Use spaces
912		stosb				# Save one
913dump.9: 	jmp dump.0			# Continue
914dump.10:	stosb				# Terminate string
915		ret				# To caller
916/*
917 * Convert EAX, AX, or AL to hex, saving the result to [EDI].
918 */
919hex32:		pushl %eax			# Save
920		shrl $0x10,%eax 		# Do upper
921		call hex16			#  16
922		popl %eax			# Restore
923hex16:		call hex16.1			# Do upper 8
924hex16.1:	xchgb %ah,%al			# Save/restore
925hex8:		pushl %eax			# Save
926		shrb $0x4,%al			# Do upper
927		call hex8.1			#  4
928		popl %eax			# Restore
929hex8.1: 	andb $0xf,%al			# Get lower 4
930		cmpb $0xa,%al			# Convert
931		sbbb $0x69,%al			#  to hex
932		das				#  digit
933		orb $0x20,%al			# To lower case
934		stosb				# Save char
935		ret				# (Recursive)
936/*
937 * Output zero-terminated string [ESI] to the console.
938 */
939putstr.0:	call putchr			# Output char
940putstr: 	lodsb				# Load char
941		testb %al,%al			# End of string?
942		jnz putstr.0			# No
943		ret				# To caller
944#ifdef BTX_SERIAL
945		.set SIO_PRT,SIOPRT		# Base port
946		.set SIO_FMT,SIOFMT		# 8N1
947		.set SIO_DIV,(115200/SIOSPD)	# 115200 / SPD
948
949/*
950 * void sio_init(void)
951 */
952sio_init:	movw $SIO_PRT+0x3,%dx		# Data format reg
953		movb $SIO_FMT|0x80,%al		# Set format
954		outb %al,(%dx)			#  and DLAB
955		pushl %edx			# Save
956		subb $0x3,%dl			# Divisor latch reg
957		movw $SIO_DIV,%ax		# Set
958		outw %ax,(%dx)			#  BPS
959		popl %edx			# Restore
960		movb $SIO_FMT,%al		# Clear
961		outb %al,(%dx)			#  DLAB
962		incl %edx			# Modem control reg
963		movb $0x3,%al			# Set RTS,
964		outb %al,(%dx)			#  DTR
965		incl %edx			# Line status reg
966
967/*
968 * void sio_flush(void)
969 */
970sio_flush.0:	call sio_getc.1 		# Get character
971sio_flush:	call sio_ischar 		# Check for character
972		jnz sio_flush.0 		# Till none
973		ret				# To caller
974
975/*
976 * void sio_putc(int c)
977 */
978sio_putc:	movw $SIO_PRT+0x5,%dx		# Line status reg
979		xor %ecx,%ecx			# Timeout
980		movb $0x40,%ch			#  counter
981sio_putc.1:	inb (%dx),%al			# Transmitter
982		testb $0x20,%al 		#  buffer empty?
983		loopz sio_putc.1		# No
984		jz sio_putc.2			# If timeout
985		movb 0x4(%esp,1),%al		# Get character
986		subb $0x5,%dl			# Transmitter hold reg
987		outb %al,(%dx)			# Write character
988sio_putc.2:	ret $0x4			# To caller
989
990/*
991 * int sio_getc(void)
992 */
993sio_getc:	call sio_ischar 		# Character available?
994		jz sio_getc			# No
995sio_getc.1:	subb $0x5,%dl			# Receiver buffer reg
996		inb (%dx),%al			# Read character
997		ret				# To caller
998
999/*
1000 * int sio_ischar(void)
1001 */
1002sio_ischar:	movw $SIO_PRT+0x5,%dx		# Line status register
1003		xorl %eax,%eax			# Zero
1004		inb (%dx),%al			# Received data
1005		andb $0x1,%al			#  ready?
1006		ret				# To caller
1007
1008/*
1009 * Output character AL to the serial console.
1010 */
1011putchr: 	pusha				# Save
1012		cmpb $10, %al			# is it a newline?
1013		jne putchr.1			#  no?, then leave
1014		push $13			# output a carriage
1015		call sio_putc			#  return first
1016		movb $10, %al			# restore %al
1017putchr.1:	pushl %eax			# Push the character
1018						#  onto the stack
1019		call sio_putc			# Output the character
1020		popa				# Restore
1021		ret				# To caller
1022#else
1023/*
1024 * Output character AL to the console.
1025 */
1026putchr: 	pusha				# Save
1027		xorl %ecx,%ecx			# Zero for loops
1028		movb $SCR_MAT,%ah		# Mode/attribute
1029		movl $BDA_POS,%ebx		# BDA pointer
1030		movw (%ebx),%dx 		# Cursor position
1031		movl $0xa0000,%edi
1032putchr.1:	cmpb $0xa,%al			# New line?
1033		je putchr.2			# Yes
1034		movw %dx,%cx
1035		movb %al,(%edi,%ecx,1)		# Write char
1036		addl $0x2000,%ecx
1037		movb %ah,(%edi,%ecx,1)		# Write attr
1038		addw $0x02,%dx
1039		jmp putchr.3
1040putchr.2:	movw %dx,%ax
1041		movb $SCR_COL*2,%dl
1042		div %dl
1043		incb %al
1044		mul %dl
1045		movw %ax,%dx
1046putchr.3:	cmpw $SCR_ROW*SCR_COL*2,%dx
1047		jb putchr.4			# No
1048		leal 2*SCR_COL(%edi),%esi	# New top line
1049		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
1050		rep				# Scroll
1051		movsl				#  screen
1052		movb $0x20,%al			# Space
1053		xorb %ah,%ah
1054		movb $SCR_COL,%cl		# Columns to clear
1055		rep				# Clear
1056		stosw				#  line
1057		movw $(SCR_ROW-1)*SCR_COL*2,%dx
1058putchr.4:	movw %dx,(%ebx) 		# Update position
1059		popa				# Restore
1060		ret				# To caller
1061#endif
1062
1063		.p2align 4
1064/*
1065 * Global descriptor table.
1066 */
1067gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
1068		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
1069		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
1070		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
1071		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
1072		.word 0xffff,MEM_USR,0xfa00,0xcf# SEL_UCODE
1073		.word 0xffff,MEM_USR,0xf200,0xcf# SEL_UDATA
1074		.word _TSSLM,MEM_TSS,0x8900,0x0 # SEL_TSS
1075gdt.1:
1076/*
1077 * Pseudo-descriptors.
1078 */
1079gdtdesc:	.word gdt.1-gdt-1,gdt,0x0	# GDT
1080idtdesc:	.word _IDTLM,MEM_IDT,0x0	# IDT
1081ivtdesc:	.word 0x400-0x0-1,0x0,0x0	# IVT
1082/*
1083 * IDT construction control string.
1084 */
1085idtctl: 	.byte 0x10,  0x8e		# Int 0x0-0xf
1086		.word 0x7dfb,intx00		#  (exceptions)
1087		.byte 0x10,  0x8e		# Int 0x10
1088		.word 0x1,   intx10		#  (exception)
1089		.byte 0x10,  0x8e		# Int 0x20-0x2f
1090		.word 0xffff,intx20		#  (hardware)
1091		.byte 0x1,   0xee		# int 0x30
1092		.word 0x1,   intx30		#  (system call)
1093		.byte 0x2,   0xee		# Int 0x31-0x32
1094		.word 0x1,   intx31		#  (V86, null)
1095		.byte 0x0			# End of string
1096/*
1097 * Dump format string.
1098 */
1099dmpfmt: 	.byte '\n'			# "\n"
1100		.ascii "int"			# "int="
1101		.byte 0x80|DMP_X32,	   0x40 # "00000000  "
1102		.ascii "err"			# "err="
1103		.byte 0x80|DMP_X32,	   0x44 # "00000000  "
1104		.ascii "efl"			# "efl="
1105		.byte 0x80|DMP_X32,	   0x50 # "00000000  "
1106		.ascii "eip"			# "eip="
1107		.byte 0x80|DMP_X32|DMP_EOL,0x48 # "00000000\n"
1108		.ascii "eax"			# "eax="
1109		.byte 0x80|DMP_X32,	   0x34 # "00000000  "
1110		.ascii "ebx"			# "ebx="
1111		.byte 0x80|DMP_X32,	   0x28 # "00000000  "
1112		.ascii "ecx"			# "ecx="
1113		.byte 0x80|DMP_X32,	   0x30 # "00000000  "
1114		.ascii "edx"			# "edx="
1115		.byte 0x80|DMP_X32|DMP_EOL,0x2c # "00000000\n"
1116		.ascii "esi"			# "esi="
1117		.byte 0x80|DMP_X32,	   0x1c # "00000000  "
1118		.ascii "edi"			# "edi="
1119		.byte 0x80|DMP_X32,	   0x18 # "00000000  "
1120		.ascii "ebp"			# "ebp="
1121		.byte 0x80|DMP_X32,	   0x20 # "00000000  "
1122		.ascii "esp"			# "esp="
1123		.byte 0x80|DMP_X32|DMP_EOL,0x0	# "00000000\n"
1124		.ascii "cs"			# "cs="
1125		.byte 0x80|DMP_X16,	   0x4c # "0000  "
1126		.ascii "ds"			# "ds="
1127		.byte 0x80|DMP_X16,	   0xc	# "0000  "
1128		.ascii "es"			# "es="
1129		.byte 0x80|DMP_X16,	   0x8	# "0000  "
1130		.ascii "  "			# "  "
1131		.ascii "fs"			# "fs="
1132		.byte 0x80|DMP_X16,	   0x10 # "0000  "
1133		.ascii "gs"			# "gs="
1134		.byte 0x80|DMP_X16,	   0x14 # "0000  "
1135		.ascii "ss"			# "ss="
1136		.byte 0x80|DMP_X16|DMP_EOL,0x4	# "0000\n"
1137		.ascii "cs:eip" 		# "cs:eip="
1138		.byte 0x80|DMP_MEM|DMP_EOL,0x48 # "00 00 ... 00 00\n"
1139		.ascii "ss:esp" 		# "ss:esp="
1140		.byte 0x80|DMP_MEM|DMP_EOL,0x0	# "00 00 ... 00 00\n"
1141		.asciz "BTX halted\n"		# End
1142/*
1143 * End of BTX memory.
1144 */
1145		.p2align 4
1146break:
1147