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