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