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