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