xref: /illumos-gate/usr/src/boot/i386/btx/btx/btx.S (revision 55fea89d)
1199767f8SToomas Soome/*
2199767f8SToomas Soome * Copyright (c) 1998 Robert Nordier
3199767f8SToomas Soome * All rights reserved.
4199767f8SToomas Soome *
5199767f8SToomas Soome * Redistribution and use in source and binary forms are freely
6199767f8SToomas Soome * permitted provided that the above copyright notice and this
7199767f8SToomas Soome * paragraph and the following disclaimer are duplicated in all
8199767f8SToomas Soome * such forms.
9199767f8SToomas Soome *
10199767f8SToomas Soome * This software is provided "AS IS" and without any express or
11199767f8SToomas Soome * implied warranties, including, without limitation, the implied
12199767f8SToomas Soome * warranties of merchantability and fitness for a particular
13199767f8SToomas Soome * purpose.
14199767f8SToomas Soome *
15199767f8SToomas Soome * $FreeBSD$
16199767f8SToomas Soome */
17199767f8SToomas Soome
18199767f8SToomas Soome#include <bootargs.h>
19199767f8SToomas Soome
20199767f8SToomas Soome/*
21199767f8SToomas Soome * Memory layout.
22199767f8SToomas Soome */
23199767f8SToomas Soome		.set MEM_BTX,0x1000		# Start of BTX memory
24199767f8SToomas Soome		.set MEM_ESP0,0x1800		# Supervisor stack
25199767f8SToomas Soome		.set MEM_BUF,0x1800		# Scratch buffer
26199767f8SToomas Soome		.set MEM_ESPR,0x5e00		# Real mode stack
27199767f8SToomas Soome		.set MEM_IDT,0x5e00		# IDT
28199767f8SToomas Soome		.set MEM_TSS,0x5f98		# TSS
29199767f8SToomas Soome		.set MEM_MAP,0x6000		# I/O bit map
30199767f8SToomas Soome		.set MEM_TSS_END,0x7fff		# End of TSS
31199767f8SToomas Soome		.set MEM_ORG,0x9000		# BTX code
32199767f8SToomas Soome		.set MEM_USR,0xa000		# Start of user memory
33199767f8SToomas Soome/*
34199767f8SToomas Soome * Paging control.
35199767f8SToomas Soome */
36199767f8SToomas Soome		.set PAG_SIZ,0x1000		# Page size
37199767f8SToomas Soome		.set PAG_CNT,0x1000		# Pages to map
38199767f8SToomas Soome/*
39199767f8SToomas Soome * Fields in %eflags.
40199767f8SToomas Soome */
41199767f8SToomas Soome		.set PSL_RESERVED_DEFAULT,0x00000002
42199767f8SToomas Soome		.set PSL_T,0x00000100		# Trap flag
43199767f8SToomas Soome		.set PSL_I,0x00000200		# Interrupt enable flag
44199767f8SToomas Soome		.set PSL_D,0x00000400		# String instruction direction
45199767f8SToomas Soome		.set PSL_NT,0x00004000		# Nested task flag
46199767f8SToomas Soome		.set PSL_VM,0x00020000		# Virtual 8086 mode flag
47199767f8SToomas Soome		.set PSL_AC,0x00040000		# Alignment check flag
48199767f8SToomas Soome/*
49199767f8SToomas Soome * Segment selectors.
50199767f8SToomas Soome */
51199767f8SToomas Soome		.set SEL_SCODE,0x8		# Supervisor code
52199767f8SToomas Soome		.set SEL_SDATA,0x10		# Supervisor data
53199767f8SToomas Soome		.set SEL_RCODE,0x18		# Real mode code
54199767f8SToomas Soome		.set SEL_RDATA,0x20		# Real mode data
55199767f8SToomas Soome		.set SEL_UCODE,0x28|3		# User code
56199767f8SToomas Soome		.set SEL_UDATA,0x30|3		# User data
57199767f8SToomas Soome		.set SEL_TSS,0x38		# TSS
58199767f8SToomas Soome/*
59199767f8SToomas Soome * Task state segment fields.
60199767f8SToomas Soome */
61199767f8SToomas Soome		.set TSS_ESP0,0x4		# PL 0 ESP
62199767f8SToomas Soome		.set TSS_SS0,0x8		# PL 0 SS
63199767f8SToomas Soome		.set TSS_MAP,0x66		# I/O bit map base
64199767f8SToomas Soome/*
65199767f8SToomas Soome * System calls.
66199767f8SToomas Soome */
67199767f8SToomas Soome		.set SYS_EXIT,0x0		# Exit
68199767f8SToomas Soome		.set SYS_EXEC,0x1		# Exec
69199767f8SToomas Soome/*
70199767f8SToomas Soome * Fields in V86 interface structure.
71199767f8SToomas Soome */
72199767f8SToomas Soome		.set V86_CTL,0x0		# Control flags
73199767f8SToomas Soome		.set V86_ADDR,0x4		# Int number/address
74199767f8SToomas Soome		.set V86_ES,0x8			# V86 ES
75199767f8SToomas Soome		.set V86_DS,0xc			# V86 DS
76199767f8SToomas Soome		.set V86_FS,0x10		# V86 FS
77199767f8SToomas Soome		.set V86_GS,0x14		# V86 GS
78199767f8SToomas Soome/*
79199767f8SToomas Soome * V86 control flags.
80199767f8SToomas Soome */
81199767f8SToomas Soome		.set V86F_ADDR,0x10000		# Segment:offset address
82199767f8SToomas Soome		.set V86F_CALLF,0x20000		# Emulate far call
83199767f8SToomas Soome		.set V86F_FLAGS,0x40000		# Return flags
84199767f8SToomas Soome/*
85199767f8SToomas Soome * Dump format control bytes.
86199767f8SToomas Soome */
87199767f8SToomas Soome		.set DMP_X16,0x1		# Word
88199767f8SToomas Soome		.set DMP_X32,0x2		# Long
89199767f8SToomas Soome		.set DMP_MEM,0x4		# Memory
90199767f8SToomas Soome		.set DMP_EOL,0x8		# End of line
91199767f8SToomas Soome/*
92199767f8SToomas Soome * Screen defaults and assumptions.
93199767f8SToomas Soome */
94199767f8SToomas Soome		.set SCR_MAT,0x7		# Mode/attribute
95199767f8SToomas Soome		.set SCR_COL,0x50		# Columns per row
96199767f8SToomas Soome		.set SCR_ROW,0x19		# Rows per screen
97199767f8SToomas Soome/*
98199767f8SToomas Soome * BIOS Data Area locations.
99199767f8SToomas Soome */
100199767f8SToomas Soome		.set BDA_MEM,0x413		# Free memory
101199767f8SToomas Soome		.set BDA_SCR,0x449		# Video mode
102199767f8SToomas Soome		.set BDA_POS,0x450		# Cursor position
103199767f8SToomas Soome		.set BDA_BOOT,0x472		# Boot howto flag
104199767f8SToomas Soome/*
105199767f8SToomas Soome * Derivations, for brevity.
106199767f8SToomas Soome */
107199767f8SToomas Soome		.set _ESP0H,MEM_ESP0>>0x8	# Byte 1 of ESP0
108199767f8SToomas Soome		.set _TSSIO,MEM_MAP-MEM_TSS	# TSS I/O base
109199767f8SToomas Soome		.set _TSSLM,MEM_TSS_END-MEM_TSS	# TSS limit
110199767f8SToomas Soome		.set _IDTLM,MEM_TSS-MEM_IDT-1	# IDT limit
111199767f8SToomas Soome/*
112199767f8SToomas Soome * Code segment.
113199767f8SToomas Soome */
114199767f8SToomas Soome		.globl start
115199767f8SToomas Soome		.code16
116199767f8SToomas Soomestart:						# Start of code
117199767f8SToomas Soome/*
118199767f8SToomas Soome * BTX header.
119199767f8SToomas Soome */
120199767f8SToomas Soomebtx_hdr:	.byte 0xeb			# Machine ID
121199767f8SToomas Soome		.byte 0xe			# Header size
122199767f8SToomas Soome		.ascii "BTX"			# Magic
123199767f8SToomas Soome		.byte 0x1			# Major version
124199767f8SToomas Soome		.byte 0x2			# Minor version
125199767f8SToomas Soome		.byte BTX_FLAGS			# Flags
126199767f8SToomas Soome		.word PAG_CNT-MEM_ORG>>0xc	# Paging control
127199767f8SToomas Soome		.word break-start		# Text size
128199767f8SToomas Soome		.long 0x0			# Entry address
129199767f8SToomas Soome/*
130199767f8SToomas Soome * Initialization routine.
131199767f8SToomas Soome */
132199767f8SToomas Soomeinit:		cli				# Disable interrupts
133199767f8SToomas Soome		xor %ax,%ax			# Zero/segment
134199767f8SToomas Soome		mov %ax,%ss			# Set up
135199767f8SToomas Soome		mov $MEM_ESP0,%sp		#  stack
136199767f8SToomas Soome		mov %ax,%es			# Address
137199767f8SToomas Soome		mov %ax,%ds			#  data
138199767f8SToomas Soome		pushl $0x2			# Clear
139199767f8SToomas Soome		popfl				#  flags
140199767f8SToomas Soome/*
141199767f8SToomas Soome * Initialize memory.
142199767f8SToomas Soome */
143199767f8SToomas Soome		mov $MEM_IDT,%di		# Memory to initialize
144199767f8SToomas Soome		mov $(MEM_ORG-MEM_IDT)/2,%cx	# Words to zero
145199767f8SToomas Soome		rep				# Zero-fill
146199767f8SToomas Soome		stosw				#  memory
147199767f8SToomas Soome/*
148199767f8SToomas Soome * Update real mode IDT for reflecting hardware interrupts.
149199767f8SToomas Soome */
150199767f8SToomas Soome		mov $intr20,%bx			# Address first handler
151199767f8SToomas Soome		mov $0x10,%cx			# Number of handlers
152199767f8SToomas Soome		mov $0x20*4,%di			# First real mode IDT entry
153199767f8SToomas Soomeinit.0:		mov %bx,(%di)			# Store IP
154199767f8SToomas Soome		inc %di				# Address next
155199767f8SToomas Soome		inc %di				#  entry
156199767f8SToomas Soome		stosw				# Store CS
157199767f8SToomas Soome		add $4,%bx			# Next handler
158199767f8SToomas Soome		loop init.0			# Next IRQ
159199767f8SToomas Soome/*
160199767f8SToomas Soome * Create IDT.
161199767f8SToomas Soome */
162199767f8SToomas Soome		mov $MEM_IDT,%di
163199767f8SToomas Soome		mov $idtctl,%si			# Control string
164199767f8SToomas Soomeinit.1: 	lodsb				# Get entry
165199767f8SToomas Soome		cbw				#  count
166199767f8SToomas Soome		xchg %ax,%cx			#  as word
167199767f8SToomas Soome		jcxz init.4			# If done
168199767f8SToomas Soome		lodsb				# Get segment
169199767f8SToomas Soome		xchg %ax,%dx	 		#  P:DPL:type
170199767f8SToomas Soome		lodsw				# Get control
171199767f8SToomas Soome		xchg %ax,%bx			#  set
172199767f8SToomas Soome		lodsw				# Get handler offset
173199767f8SToomas Soome		mov $SEL_SCODE,%dh		# Segment selector
174199767f8SToomas Soomeinit.2: 	shr %bx				# Handle this int?
175199767f8SToomas Soome		jnc init.3			# No
176199767f8SToomas Soome		mov %ax,(%di)			# Set handler offset
177199767f8SToomas Soome		mov %dh,0x2(%di)		#  and selector
178199767f8SToomas Soome		mov %dl,0x5(%di)		# Set P:DPL:type
179199767f8SToomas Soome		add $0x4,%ax			# Next handler
180199767f8SToomas Soomeinit.3: 	lea 0x8(%di),%di		# Next entry
181199767f8SToomas Soome		loop init.2			# Till set done
182199767f8SToomas Soome		jmp init.1			# Continue
183199767f8SToomas Soome/*
184199767f8SToomas Soome * Initialize TSS.
185199767f8SToomas Soome */
186199767f8SToomas Soomeinit.4: 	movb $_ESP0H,TSS_ESP0+1(%di)	# Set ESP0
187199767f8SToomas Soome		movb $SEL_SDATA,TSS_SS0(%di)	# Set SS0
188199767f8SToomas Soome		movb $_TSSIO,TSS_MAP(%di)	# Set I/O bit map base
189199767f8SToomas Soome/*
190199767f8SToomas Soome * Bring up the system.
191199767f8SToomas Soome */
192199767f8SToomas Soome		mov $0x2820,%bx			# Set protected mode
193199767f8SToomas Soome		callw setpic			#  IRQ offsets
194199767f8SToomas Soome		lidt idtdesc	 		# Set IDT
195199767f8SToomas Soome		lgdt gdtdesc	 		# Set GDT
196199767f8SToomas Soome		mov %cr0,%eax			# Switch to protected
197199767f8SToomas Soome		inc %ax				#  mode
198199767f8SToomas Soome		mov %eax,%cr0			#
199199767f8SToomas Soome		ljmp $SEL_SCODE,$init.8		# To 32-bit code
200199767f8SToomas Soome		.code32
201199767f8SToomas Soomeinit.8: 	xorl %ecx,%ecx			# Zero
202199767f8SToomas Soome		movb $SEL_SDATA,%cl		# To 32-bit
203199767f8SToomas Soome		movw %cx,%ss			#  stack
204199767f8SToomas Soome/*
205199767f8SToomas Soome * Launch user task.
206199767f8SToomas Soome */
207199767f8SToomas Soome		movb $SEL_TSS,%cl		# Set task
208199767f8SToomas Soome		ltr %cx				#  register
209199767f8SToomas Soome		movl $MEM_USR,%edx		# User base address
210199767f8SToomas Soome		movzwl %ss:BDA_MEM,%eax 	# Get free memory
211199767f8SToomas Soome		shll $0xa,%eax			# To bytes
212199767f8SToomas Soome		subl $ARGSPACE,%eax		# Less arg space
213199767f8SToomas Soome		subl %edx,%eax			# Less base
214199767f8SToomas Soome		movb $SEL_UDATA,%cl		# User data selector
215199767f8SToomas Soome		pushl %ecx			# Set SS
216199767f8SToomas Soome		pushl %eax			# Set ESP
217199767f8SToomas Soome		push $0x202			# Set flags (IF set)
218199767f8SToomas Soome		push $SEL_UCODE			# Set CS
219199767f8SToomas Soome		pushl btx_hdr+0xc		# Set EIP
220199767f8SToomas Soome		pushl %ecx			# Set GS
221199767f8SToomas Soome		pushl %ecx			# Set FS
222199767f8SToomas Soome		pushl %ecx			# Set DS
223199767f8SToomas Soome		pushl %ecx			# Set ES
224199767f8SToomas Soome		pushl %edx			# Set EAX
225199767f8SToomas Soome		movb $0x7,%cl			# Set remaining
226199767f8SToomas Soomeinit.9:		push $0x0			#  general
227199767f8SToomas Soome		loop init.9			#  registers
228199767f8SToomas Soome#ifdef BTX_SERIAL
229199767f8SToomas Soome		call sio_init			# setup the serial console
230199767f8SToomas Soome#endif
231199767f8SToomas Soome		popa				#  and initialize
232199767f8SToomas Soome		popl %es			# Initialize
233199767f8SToomas Soome		popl %ds			#  user
234199767f8SToomas Soome		popl %fs			#  segment
235199767f8SToomas Soome		popl %gs			#  registers
236199767f8SToomas Soome		iret				# To user mode
237199767f8SToomas Soome/*
238199767f8SToomas Soome * Exit routine.
239199767f8SToomas Soome */
240199767f8SToomas Soomeexit:		cli				# Disable interrupts
241199767f8SToomas Soome		movl $MEM_ESP0,%esp		# Clear stack
242199767f8SToomas Soome/*
243199767f8SToomas Soome * Turn off paging.
244199767f8SToomas Soome */
245199767f8SToomas Soome		movl %cr0,%eax			# Get CR0
246199767f8SToomas Soome		andl $~0x80000000,%eax		# Disable
247199767f8SToomas Soome		movl %eax,%cr0			#  paging
248199767f8SToomas Soome		xorl %ecx,%ecx			# Zero
249199767f8SToomas Soome		movl %ecx,%cr3			# Flush TLB
250199767f8SToomas Soome/*
251199767f8SToomas Soome * Restore the GDT in case we caught a kernel trap.
252199767f8SToomas Soome */
253199767f8SToomas Soome		lgdt %cs:gdtdesc		# Set GDT
254199767f8SToomas Soome/*
255199767f8SToomas Soome * To 16 bits.
256199767f8SToomas Soome */
257199767f8SToomas Soome		ljmpw $SEL_RCODE,$exit.1	# Reload CS
258199767f8SToomas Soome		.code16
259199767f8SToomas Soomeexit.1: 	mov $SEL_RDATA,%cl		# 16-bit selector
260199767f8SToomas Soome		mov %cx,%ss			# Reload SS
261199767f8SToomas Soome		mov %cx,%ds			# Load
262199767f8SToomas Soome		mov %cx,%es			#  remaining
263199767f8SToomas Soome		mov %cx,%fs			#  segment
264199767f8SToomas Soome		mov %cx,%gs			#  registers
265199767f8SToomas Soome/*
266199767f8SToomas Soome * To real-address mode.
267199767f8SToomas Soome */
268199767f8SToomas Soome		dec %ax				# Switch to
269199767f8SToomas Soome		mov %eax,%cr0			#  real mode
270199767f8SToomas Soome		ljmp $0x0,$exit.2		# Reload CS
271199767f8SToomas Soomeexit.2: 	xor %ax,%ax			# Real mode segment
272199767f8SToomas Soome		mov %ax,%ss			# Reload SS
273199767f8SToomas Soome		mov %ax,%ds			# Address data
274199767f8SToomas Soome		mov $0x7008,%bx			# Set real mode
275199767f8SToomas Soome		callw setpic			#  IRQ offsets
276199767f8SToomas Soome		lidt ivtdesc	 		# Set IVT
277199767f8SToomas Soome/*
278199767f8SToomas Soome * Reboot or await reset.
279199767f8SToomas Soome */
280199767f8SToomas Soome		sti				# Enable interrupts
281199767f8SToomas Soome		testb $0x1,btx_hdr+0x7		# Reboot?
282199767f8SToomas Soomeexit.3:		jz exit.3			# No
283199767f8SToomas Soome		movw $0x1234, BDA_BOOT		# Do a warm boot
284199767f8SToomas Soome		ljmp $0xf000,$0xfff0		# reboot the machine
285199767f8SToomas Soome/*
286199767f8SToomas Soome * Set IRQ offsets by reprogramming 8259A PICs.
287199767f8SToomas Soome */
288199767f8SToomas Soomesetpic: 	in $0x21,%al			# Save master
289199767f8SToomas Soome		push %ax			#  IMR
290199767f8SToomas Soome		in $0xa1,%al			# Save slave
291199767f8SToomas Soome		push %ax			#  IMR
292199767f8SToomas Soome		movb $0x11,%al			# ICW1 to
293199767f8SToomas Soome		outb %al,$0x20			#  master,
294199767f8SToomas Soome		outb %al,$0xa0			#  slave
295199767f8SToomas Soome		movb %bl,%al			# ICW2 to
296199767f8SToomas Soome		outb %al,$0x21			#  master
297199767f8SToomas Soome		movb %bh,%al			# ICW2 to
298199767f8SToomas Soome		outb %al,$0xa1			#  slave
299199767f8SToomas Soome		movb $0x4,%al			# ICW3 to
300199767f8SToomas Soome		outb %al,$0x21			#  master
301199767f8SToomas Soome		movb $0x2,%al			# ICW3 to
302199767f8SToomas Soome		outb %al,$0xa1			#  slave
303199767f8SToomas Soome		movb $0x1,%al			# ICW4 to
304199767f8SToomas Soome		outb %al,$0x21			#  master,
305199767f8SToomas Soome		outb %al,$0xa1			#  slave
306199767f8SToomas Soome		pop %ax				# Restore slave
307199767f8SToomas Soome		outb %al,$0xa1			#  IMR
308199767f8SToomas Soome		pop %ax				# Restore master
309199767f8SToomas Soome		outb %al,$0x21			#  IMR
310199767f8SToomas Soome		retw				# To caller
311199767f8SToomas Soome		.code32
312199767f8SToomas Soome/*
313199767f8SToomas Soome * Exception jump table.
314199767f8SToomas Soome */
315199767f8SToomas Soomeintx00: 	push $0x0			# Int 0x0: #DE
316199767f8SToomas Soome		jmp ex_noc			# Divide error
317199767f8SToomas Soome		push $0x1			# Int 0x1: #DB
318199767f8SToomas Soome		jmp ex_noc			# Debug
319199767f8SToomas Soome		push $0x3			# Int 0x3: #BP
320199767f8SToomas Soome		jmp ex_noc			# Breakpoint
321199767f8SToomas Soome		push $0x4			# Int 0x4: #OF
322199767f8SToomas Soome		jmp ex_noc			# Overflow
323199767f8SToomas Soome		push $0x5			# Int 0x5: #BR
324199767f8SToomas Soome		jmp ex_noc			# BOUND range exceeded
325199767f8SToomas Soome		push $0x6			# Int 0x6: #UD
326199767f8SToomas Soome		jmp ex_noc			# Invalid opcode
327199767f8SToomas Soome		push $0x7			# Int 0x7: #NM
328199767f8SToomas Soome		jmp ex_noc			# Device not available
329199767f8SToomas Soome		push $0x8			# Int 0x8: #DF
330199767f8SToomas Soome		jmp except			# Double fault
331199767f8SToomas Soome		push $0xa			# Int 0xa: #TS
332199767f8SToomas Soome		jmp except			# Invalid TSS
333199767f8SToomas Soome		push $0xb			# Int 0xb: #NP
334199767f8SToomas Soome		jmp except			# Segment not present
335199767f8SToomas Soome		push $0xc			# Int 0xc: #SS
336199767f8SToomas Soome		jmp except			# Stack segment fault
337199767f8SToomas Soome		push $0xd			# Int 0xd: #GP
338199767f8SToomas Soome		jmp except			# General protection
339199767f8SToomas Soome		push $0xe			# Int 0xe: #PF
340199767f8SToomas Soome		jmp except			# Page fault
341199767f8SToomas Soomeintx10: 	push $0x10			# Int 0x10: #MF
342199767f8SToomas Soome		jmp ex_noc			# Floating-point error
343199767f8SToomas Soome/*
344199767f8SToomas Soome * Save a zero error code.
345199767f8SToomas Soome */
346199767f8SToomas Soomeex_noc: 	pushl (%esp,1)			# Duplicate int no
347199767f8SToomas Soome		movb $0x0,0x4(%esp,1)		# Fake error code
348199767f8SToomas Soome/*
349199767f8SToomas Soome * Handle exception.
350199767f8SToomas Soome */
351199767f8SToomas Soomeexcept: 	cld				# String ops inc
352199767f8SToomas Soome		pushl %ds			# Save
353199767f8SToomas Soome		pushl %es			#  most
354199767f8SToomas Soome		pusha				#  registers
355199767f8SToomas Soome		pushl %gs			# Set GS
356199767f8SToomas Soome		pushl %fs			# Set FS
357199767f8SToomas Soome		pushl %ds			# Set DS
358199767f8SToomas Soome		pushl %es			# Set ES
359199767f8SToomas Soome		cmpw $SEL_SCODE,0x44(%esp,1)	# Supervisor mode?
360199767f8SToomas Soome		jne except.1			# No
361199767f8SToomas Soome		pushl %ss			# Set SS
362199767f8SToomas Soome		jmp except.2			# Join common code
363199767f8SToomas Soomeexcept.1:	pushl 0x50(%esp,1)		# Set SS
364199767f8SToomas Soomeexcept.2:	pushl 0x50(%esp,1)		# Set ESP
365199767f8SToomas Soome		push $SEL_SDATA			# Set up
366199767f8SToomas Soome		popl %ds			#  to
367199767f8SToomas Soome		pushl %ds			#  address
368199767f8SToomas Soome		popl %es			#  data
369199767f8SToomas Soome		movl %esp,%ebx			# Stack frame
370199767f8SToomas Soome		movl $dmpfmt,%esi		# Dump format string
371199767f8SToomas Soome		movl $MEM_BUF,%edi		# Buffer
372199767f8SToomas Soome		pushl %edi			# Dump to
373199767f8SToomas Soome		call dump			#  buffer
374199767f8SToomas Soome		popl %esi			#  and
375199767f8SToomas Soome		call putstr			#  display
376199767f8SToomas Soome		leal 0x18(%esp,1),%esp		# Discard frame
377199767f8SToomas Soome		popa				# Restore
378199767f8SToomas Soome		popl %es			#  registers
379199767f8SToomas Soome		popl %ds			#  saved
380199767f8SToomas Soome		cmpb $0x3,(%esp,1)		# Breakpoint?
381199767f8SToomas Soome		je except.3			# Yes
382199767f8SToomas Soome		cmpb $0x1,(%esp,1)		# Debug?
383199767f8SToomas Soome		jne except.2a			# No
384199767f8SToomas Soome		testl $PSL_T,0x10(%esp,1)	# Trap flag set?
385199767f8SToomas Soome		jnz except.3			# Yes
386199767f8SToomas Soomeexcept.2a:	jmp exit			# Exit
387199767f8SToomas Soomeexcept.3:	leal 0x8(%esp,1),%esp		# Discard err, int no
388199767f8SToomas Soome		iret				# From interrupt
389199767f8SToomas Soome
390199767f8SToomas Soome/*
391199767f8SToomas Soome * Reboot the machine by setting the reboot flag and exiting
392199767f8SToomas Soome */
393199767f8SToomas Soomereboot:		orb $0x1,btx_hdr+0x7		# Set the reboot flag
394199767f8SToomas Soome		jmp exit			# Terminate BTX and reboot
395199767f8SToomas Soome
396199767f8SToomas Soome/*
397199767f8SToomas Soome * Protected Mode Hardware interrupt jump table.
398199767f8SToomas Soome */
399199767f8SToomas Soomeintx20: 	push $0x8			# Int 0x20: IRQ0
400199767f8SToomas Soome		jmp int_hw			# V86 int 0x8
401199767f8SToomas Soome		push $0x9			# Int 0x21: IRQ1
402199767f8SToomas Soome		jmp int_hw			# V86 int 0x9
403199767f8SToomas Soome		push $0xa			# Int 0x22: IRQ2
404199767f8SToomas Soome		jmp int_hw			# V86 int 0xa
405199767f8SToomas Soome		push $0xb			# Int 0x23: IRQ3
406199767f8SToomas Soome		jmp int_hw			# V86 int 0xb
407199767f8SToomas Soome		push $0xc			# Int 0x24: IRQ4
408199767f8SToomas Soome		jmp int_hw			# V86 int 0xc
409199767f8SToomas Soome		push $0xd			# Int 0x25: IRQ5
410199767f8SToomas Soome		jmp int_hw			# V86 int 0xd
411199767f8SToomas Soome		push $0xe			# Int 0x26: IRQ6
412199767f8SToomas Soome		jmp int_hw			# V86 int 0xe
413199767f8SToomas Soome		push $0xf			# Int 0x27: IRQ7
414199767f8SToomas Soome		jmp int_hw			# V86 int 0xf
415199767f8SToomas Soome		push $0x70			# Int 0x28: IRQ8
416199767f8SToomas Soome		jmp int_hw			# V86 int 0x70
417199767f8SToomas Soome		push $0x71			# Int 0x29: IRQ9
418199767f8SToomas Soome		jmp int_hw			# V86 int 0x71
419199767f8SToomas Soome		push $0x72			# Int 0x2a: IRQ10
420199767f8SToomas Soome		jmp int_hw			# V86 int 0x72
421199767f8SToomas Soome		push $0x73			# Int 0x2b: IRQ11
422199767f8SToomas Soome		jmp int_hw			# V86 int 0x73
423199767f8SToomas Soome		push $0x74			# Int 0x2c: IRQ12
424199767f8SToomas Soome		jmp int_hw			# V86 int 0x74
425199767f8SToomas Soome		push $0x75			# Int 0x2d: IRQ13
426199767f8SToomas Soome		jmp int_hw			# V86 int 0x75
427199767f8SToomas Soome		push $0x76			# Int 0x2e: IRQ14
428199767f8SToomas Soome		jmp int_hw			# V86 int 0x76
429199767f8SToomas Soome		push $0x77			# Int 0x2f: IRQ15
430199767f8SToomas Soome		jmp int_hw			# V86 int 0x77
431199767f8SToomas Soome
432199767f8SToomas Soome/*
433199767f8SToomas Soome * Invoke real mode interrupt/function call from user mode with arguments.
434199767f8SToomas Soome */
435199767f8SToomas Soomeintx31: 	pushl $-1			# Dummy int no for btx_v86
436199767f8SToomas Soome/*
437199767f8SToomas Soome * Invoke real mode interrupt/function call from protected mode.
438199767f8SToomas Soome *
439199767f8SToomas Soome * We place a trampoline on the user stack that will return to rret_tramp
440199767f8SToomas Soome * which will reenter protected mode and then finally return to the user
441199767f8SToomas Soome * client.
442199767f8SToomas Soome *
443199767f8SToomas Soome * Kernel frame %esi points to:		Real mode stack frame at MEM_ESPR:
444199767f8SToomas Soome *
445199767f8SToomas Soome * -0x00 user %ss			-0x04 kernel %esp (with full frame)
446199767f8SToomas Soome * -0x04 user %esp			-0x08 btx_v86 pointer
447199767f8SToomas Soome * -0x08 user %eflags			-0x0c flags (only used if interrupt)
448199767f8SToomas Soome * -0x0c user %cs			-0x10 real mode CS:IP return trampoline
449199767f8SToomas Soome * -0x10 user %eip			-0x12 real mode flags
450199767f8SToomas Soome * -0x14 int no				-0x16 real mode CS:IP (target)
451199767f8SToomas Soome * -0x18 %eax
452199767f8SToomas Soome * -0x1c %ecx
453199767f8SToomas Soome * -0x20 %edx
454199767f8SToomas Soome * -0x24 %ebx
455199767f8SToomas Soome * -0x28 %esp
456199767f8SToomas Soome * -0x2c %ebp
457199767f8SToomas Soome * -0x30 %esi
458199767f8SToomas Soome * -0x34 %edi
459199767f8SToomas Soome * -0x38 %gs
460199767f8SToomas Soome * -0x3c %fs
461199767f8SToomas Soome * -0x40 %ds
462199767f8SToomas Soome * -0x44 %es
463*55fea89dSDan Cross * -0x48 zero %eax (hardware int only)
464199767f8SToomas Soome * -0x4c zero %ecx (hardware int only)
465199767f8SToomas Soome * -0x50 zero %edx (hardware int only)
466199767f8SToomas Soome * -0x54 zero %ebx (hardware int only)
467199767f8SToomas Soome * -0x58 zero %esp (hardware int only)
468199767f8SToomas Soome * -0x5c zero %ebp (hardware int only)
469199767f8SToomas Soome * -0x60 zero %esi (hardware int only)
470199767f8SToomas Soome * -0x64 zero %edi (hardware int only)
471199767f8SToomas Soome * -0x68 zero %gs (hardware int only)
472199767f8SToomas Soome * -0x6c zero %fs (hardware int only)
473199767f8SToomas Soome * -0x70 zero %ds (hardware int only)
474199767f8SToomas Soome * -0x74 zero %es (hardware int only)
475199767f8SToomas Soome */
476199767f8SToomas Soomeint_hw: 	cld				# String ops inc
477199767f8SToomas Soome		pusha				# Save gp regs
478199767f8SToomas Soome		pushl %gs			# Save
479199767f8SToomas Soome		pushl %fs			#  seg
480199767f8SToomas Soome		pushl %ds			#  regs
481199767f8SToomas Soome		pushl %es
482199767f8SToomas Soome		push $SEL_SDATA			# Set up
483199767f8SToomas Soome		popl %ds			#  to
484199767f8SToomas Soome		pushl %ds			#  address
485199767f8SToomas Soome		popl %es			#  data
486199767f8SToomas Soome		leal 0x44(%esp,1),%esi		# Base of frame
487199767f8SToomas Soome		movl %esp,MEM_ESPR-0x04		# Save kernel stack pointer
488199767f8SToomas Soome		movl -0x14(%esi),%eax		# Get Int no
489199767f8SToomas Soome		cmpl $-1,%eax			# Hardware interrupt?
490199767f8SToomas Soome		jne intusr.1			# Yes
491199767f8SToomas Soome/*
492199767f8SToomas Soome * v86 calls save the btx_v86 pointer on the real mode stack and read
493199767f8SToomas Soome * the address and flags from the btx_v86 structure.  For interrupt
494199767f8SToomas Soome * handler invocations (VM86 INTx requests), disable interrupts,
495199767f8SToomas Soome * tracing, and alignment checking while the handler runs.
496199767f8SToomas Soome */
497199767f8SToomas Soome		movl $MEM_USR,%ebx		# User base
498199767f8SToomas Soome		movl %ebx,%edx			#  address
499199767f8SToomas Soome		addl -0x4(%esi),%ebx		# User ESP
500199767f8SToomas Soome		movl (%ebx),%ebp		# btx_v86 pointer
501199767f8SToomas Soome		addl %ebp,%edx			# Flatten btx_v86 ptr
502199767f8SToomas Soome		movl %edx,MEM_ESPR-0x08		# Save btx_v86 ptr
503199767f8SToomas Soome		movl V86_ADDR(%edx),%eax	# Get int no/address
504199767f8SToomas Soome		movl V86_CTL(%edx),%edx		# Get control flags
505199767f8SToomas Soome		movl -0x08(%esi),%ebx		# Save user flags in %ebx
506199767f8SToomas Soome		testl $V86F_ADDR,%edx		# Segment:offset?
507199767f8SToomas Soome		jnz intusr.4			# Yes
508199767f8SToomas Soome		andl $~(PSL_I|PSL_T|PSL_AC),%ebx # Disable interrupts, tracing,
509199767f8SToomas Soome						#  and alignment checking for
510199767f8SToomas Soome						#  interrupt handler
511199767f8SToomas Soome		jmp intusr.3			# Skip hardware interrupt
512199767f8SToomas Soome/*
513199767f8SToomas Soome * Hardware interrupts store a NULL btx_v86 pointer and use the
514199767f8SToomas Soome * address (interrupt number) from the stack with empty flags.  Also,
515199767f8SToomas Soome * push a dummy frame of zeros onto the stack for all the general
516199767f8SToomas Soome * purpose and segment registers and clear %eflags.  This gives the
517199767f8SToomas Soome * hardware interrupt handler a clean slate.
518199767f8SToomas Soome */
519199767f8SToomas Soomeintusr.1:	xorl %edx,%edx			# Control flags
520199767f8SToomas Soome		movl %edx,MEM_ESPR-0x08		# NULL btx_v86 ptr
521199767f8SToomas Soome		movl $12,%ecx			# Frame is 12 dwords
522199767f8SToomas Soomeintusr.2:	pushl $0x0			# Fill frame
523199767f8SToomas Soome		loop intusr.2			#  with zeros
524199767f8SToomas Soome		movl $PSL_RESERVED_DEFAULT,%ebx # Set clean %eflags
525199767f8SToomas Soome/*
526199767f8SToomas Soome * Look up real mode IDT entry for hardware interrupts and VM86 INTx
527199767f8SToomas Soome * requests.
528199767f8SToomas Soome */
529199767f8SToomas Soomeintusr.3:	shll $0x2,%eax			# Scale
530199767f8SToomas Soome		movl (%eax),%eax		# Load int vector
531199767f8SToomas Soome		jmp intusr.5			# Skip CALLF test
532199767f8SToomas Soome/*
533199767f8SToomas Soome * Panic if V86F_CALLF isn't set with V86F_ADDR.
534199767f8SToomas Soome */
535199767f8SToomas Soomeintusr.4:	testl $V86F_CALLF,%edx		# Far call?
536199767f8SToomas Soome		jnz intusr.5			# Ok
537199767f8SToomas Soome		movl %edx,0x30(%esp,1)		# Place VM86 flags in int no
538199767f8SToomas Soome		movl $badvm86,%esi		# Display bad
539199767f8SToomas Soome		call putstr			#  VM86 call
540199767f8SToomas Soome		popl %es			# Restore
541199767f8SToomas Soome		popl %ds			#  seg
542199767f8SToomas Soome		popl %fs			#  regs
543199767f8SToomas Soome		popl %gs
544199767f8SToomas Soome		popal				# Restore gp regs
545199767f8SToomas Soome		jmp ex_noc			# Panic
546199767f8SToomas Soome/*
547199767f8SToomas Soome * %eax now holds the segment:offset of the function.
548199767f8SToomas Soome * %ebx now holds the %eflags to pass to real mode.
549199767f8SToomas Soome * %edx now holds the V86F_* flags.
550199767f8SToomas Soome */
551199767f8SToomas Soomeintusr.5:	movw %bx,MEM_ESPR-0x12		# Pass user flags to real mode
552199767f8SToomas Soome						#  target
553199767f8SToomas Soome/*
554199767f8SToomas Soome * If this is a v86 call, copy the seg regs out of the btx_v86 structure.
555199767f8SToomas Soome */
556199767f8SToomas Soome		movl MEM_ESPR-0x08,%ecx		# Get btx_v86 ptr
557199767f8SToomas Soome		jecxz intusr.6			# Skip for hardware ints
558199767f8SToomas Soome		leal -0x44(%esi),%edi		# %edi => kernel stack seg regs
559199767f8SToomas Soome		pushl %esi			# Save
560199767f8SToomas Soome		leal V86_ES(%ecx),%esi		# %esi => btx_v86 seg regs
561199767f8SToomas Soome		movl $4,%ecx			# Copy seg regs
562199767f8SToomas Soome		rep				#  from btx_v86
563199767f8SToomas Soome		movsl				#  to kernel stack
564199767f8SToomas Soome		popl %esi			# Restore
565199767f8SToomas Soomeintusr.6:	movl -0x08(%esi),%ebx		# Copy user flags to real
566199767f8SToomas Soome		movl %ebx,MEM_ESPR-0x0c		#  mode return trampoline
567199767f8SToomas Soome		movl $rret_tramp,%ebx		# Set return trampoline
568199767f8SToomas Soome		movl %ebx,MEM_ESPR-0x10		#  CS:IP
569199767f8SToomas Soome		movl %eax,MEM_ESPR-0x16		# Real mode target CS:IP
570199767f8SToomas Soome		ljmpw $SEL_RCODE,$intusr.7	# Change to 16-bit segment
571199767f8SToomas Soome		.code16
572199767f8SToomas Soomeintusr.7:	movl %cr0,%eax			# Leave
573199767f8SToomas Soome		dec %al				#  protected
574199767f8SToomas Soome		movl %eax,%cr0			#  mode
575199767f8SToomas Soome		ljmpw $0x0,$intusr.8
576199767f8SToomas Soomeintusr.8:	xorw %ax,%ax			# Reset %ds
577199767f8SToomas Soome		movw %ax,%ds			#  and
578199767f8SToomas Soome		movw %ax,%ss			#  %ss
579199767f8SToomas Soome		lidt ivtdesc	 		# Set IVT
580199767f8SToomas Soome		popl %es			# Restore
581199767f8SToomas Soome		popl %ds			#  seg
582199767f8SToomas Soome		popl %fs			#  regs
583199767f8SToomas Soome		popl %gs
584199767f8SToomas Soome		popal				# Restore gp regs
585199767f8SToomas Soome		movw $MEM_ESPR-0x16,%sp		# Switch to real mode stack
586199767f8SToomas Soome		iret				# Call target routine
587199767f8SToomas Soome/*
588199767f8SToomas Soome * For the return to real mode we setup a stack frame like this on the real
589199767f8SToomas Soome * mode stack.  Note that callf calls won't pop off the flags, but we just
590199767f8SToomas Soome * ignore that by repositioning %sp to be just above the btx_v86 pointer
591199767f8SToomas Soome * so it is aligned.  The stack is relative to MEM_ESPR.
592199767f8SToomas Soome *
593199767f8SToomas Soome * -0x04	kernel %esp
594199767f8SToomas Soome * -0x08	btx_v86
595199767f8SToomas Soome * -0x0c	%eax
596199767f8SToomas Soome * -0x10	%ecx
597199767f8SToomas Soome * -0x14	%edx
598199767f8SToomas Soome * -0x18	%ebx
599199767f8SToomas Soome * -0x1c	%esp
600199767f8SToomas Soome * -0x20	%ebp
601199767f8SToomas Soome * -0x24	%esi
602199767f8SToomas Soome * -0x28	%edi
603199767f8SToomas Soome * -0x2c	%gs
604199767f8SToomas Soome * -0x30	%fs
605199767f8SToomas Soome * -0x34	%ds
606199767f8SToomas Soome * -0x38	%es
607199767f8SToomas Soome * -0x3c	%eflags
608199767f8SToomas Soome */
609199767f8SToomas Soomerret_tramp:	movw $MEM_ESPR-0x08,%sp		# Reset stack pointer
610199767f8SToomas Soome		pushal				# Save gp regs
611199767f8SToomas Soome		pushl %gs			# Save
612199767f8SToomas Soome		pushl %fs			#  seg
613199767f8SToomas Soome		pushl %ds			#  regs
614199767f8SToomas Soome		pushl %es
615199767f8SToomas Soome		pushfl				# Save %eflags
616199767f8SToomas Soome		pushl $PSL_RESERVED_DEFAULT|PSL_D # Use clean %eflags with
617199767f8SToomas Soome		popfl				#  string ops dec
618*55fea89dSDan Cross		xorw %ax,%ax			# Reset seg
619199767f8SToomas Soome		movw %ax,%ds			#  regs
620199767f8SToomas Soome		movw %ax,%es			#  (%ss is already 0)
621199767f8SToomas Soome		lidt idtdesc	 		# Set IDT
622199767f8SToomas Soome		lgdt gdtdesc	 		# Set GDT
623199767f8SToomas Soome		mov %cr0,%eax			# Switch to protected
624199767f8SToomas Soome		inc %ax				#  mode
625199767f8SToomas Soome		mov %eax,%cr0			#
626199767f8SToomas Soome		ljmp $SEL_SCODE,$rret_tramp.1	# To 32-bit code
627199767f8SToomas Soome		.code32
628199767f8SToomas Soomerret_tramp.1:	xorl %ecx,%ecx			# Zero
629199767f8SToomas Soome		movb $SEL_SDATA,%cl		# Setup
630199767f8SToomas Soome		movw %cx,%ss			#  32-bit
631199767f8SToomas Soome		movw %cx,%ds			#  seg
632199767f8SToomas Soome		movw %cx,%es			#  regs
633199767f8SToomas Soome		movl MEM_ESPR-0x04,%esp		# Switch to kernel stack
634199767f8SToomas Soome		leal 0x44(%esp,1),%esi		# Base of frame
635199767f8SToomas Soome		andb $~0x2,tss_desc+0x5		# Clear TSS busy
636199767f8SToomas Soome		movb $SEL_TSS,%cl		# Set task
637199767f8SToomas Soome		ltr %cx				#  register
638199767f8SToomas Soome/*
639199767f8SToomas Soome * Now we are back in protected mode.  The kernel stack frame set up
640199767f8SToomas Soome * before entering real mode is still intact. For hardware interrupts,
641199767f8SToomas Soome * leave the frame unchanged.
642199767f8SToomas Soome */
643199767f8SToomas Soome		cmpl $0,MEM_ESPR-0x08		# Leave saved regs unchanged
644199767f8SToomas Soome		jz rret_tramp.3			#  for hardware ints
645199767f8SToomas Soome/*
646199767f8SToomas Soome * For V86 calls, copy the registers off of the real mode stack onto
647199767f8SToomas Soome * the kernel stack as we want their updated values.  Also, initialize
648199767f8SToomas Soome * the segment registers on the kernel stack.
649199767f8SToomas Soome *
650199767f8SToomas Soome * Note that the %esp in the kernel stack after this is garbage, but popa
651199767f8SToomas Soome * ignores it, so we don't have to fix it up.
652199767f8SToomas Soome */
653199767f8SToomas Soome		leal -0x18(%esi),%edi		# Kernel stack GP regs
654199767f8SToomas Soome		pushl %esi			# Save
655199767f8SToomas Soome		movl $MEM_ESPR-0x0c,%esi	# Real mode stack GP regs
656199767f8SToomas Soome		movl $8,%ecx			# Copy GP regs from
657199767f8SToomas Soome		rep				#  real mode stack
658199767f8SToomas Soome		movsl				#  to kernel stack
659199767f8SToomas Soome		movl $SEL_UDATA,%eax		# Selector for data seg regs
660199767f8SToomas Soome		movl $4,%ecx			# Initialize %ds,
661199767f8SToomas Soome		rep				#  %es, %fs, and
662199767f8SToomas Soome		stosl				#  %gs
663199767f8SToomas Soome/*
664199767f8SToomas Soome * For V86 calls, copy the saved seg regs on the real mode stack back
665199767f8SToomas Soome * over to the btx_v86 structure.  Also, conditionally update the
666199767f8SToomas Soome * saved eflags on the kernel stack based on the flags from the user.
667199767f8SToomas Soome */
668199767f8SToomas Soome		movl MEM_ESPR-0x08,%ecx		# Get btx_v86 ptr
669199767f8SToomas Soome		leal V86_GS(%ecx),%edi		# %edi => btx_v86 seg regs
670199767f8SToomas Soome		leal MEM_ESPR-0x2c,%esi		# %esi => real mode seg regs
671199767f8SToomas Soome		xchgl %ecx,%edx			# Save btx_v86 ptr
672199767f8SToomas Soome		movl $4,%ecx			# Copy seg regs
673199767f8SToomas Soome		rep				#  from real mode stack
674199767f8SToomas Soome		movsl				#  to btx_v86
675199767f8SToomas Soome		popl %esi			# Restore
676199767f8SToomas Soome		movl V86_CTL(%edx),%edx		# Read V86 control flags
677199767f8SToomas Soome		testl $V86F_FLAGS,%edx		# User wants flags?
678199767f8SToomas Soome		jz rret_tramp.3			# No
679199767f8SToomas Soome		movl MEM_ESPR-0x3c,%eax		# Read real mode flags
680199767f8SToomas Soome		andl $~(PSL_T|PSL_NT),%eax	# Clear unsafe flags
681199767f8SToomas Soome		movw %ax,-0x08(%esi)		# Update user flags (low 16)
682199767f8SToomas Soome/*
683199767f8SToomas Soome * Return to the user task
684199767f8SToomas Soome */
685199767f8SToomas Soomerret_tramp.3:	popl %es			# Restore
686199767f8SToomas Soome		popl %ds			#  seg
687199767f8SToomas Soome		popl %fs			#  regs
688199767f8SToomas Soome		popl %gs
689199767f8SToomas Soome		popal				# Restore gp regs
690199767f8SToomas Soome		addl $4,%esp			# Discard int no
691199767f8SToomas Soome		iret				# Return to user mode
692199767f8SToomas Soome
693199767f8SToomas Soome/*
694199767f8SToomas Soome * System Call.
695199767f8SToomas Soome */
696199767f8SToomas Soomeintx30: 	cmpl $SYS_EXEC,%eax		# Exec system call?
697199767f8SToomas Soome		jne intx30.1			# No
698199767f8SToomas Soome		pushl %ss			# Set up
699199767f8SToomas Soome		popl %es			#  all
700199767f8SToomas Soome		pushl %es			#  segment
701199767f8SToomas Soome		popl %ds			#  registers
702199767f8SToomas Soome		pushl %ds			#  for the
703199767f8SToomas Soome		popl %fs			#  program
704199767f8SToomas Soome		pushl %fs			#  we're
705199767f8SToomas Soome		popl %gs			#  invoking
706199767f8SToomas Soome		movl $MEM_USR,%eax		# User base address
707199767f8SToomas Soome		addl 0xc(%esp,1),%eax		# Change to user
708199767f8SToomas Soome		leal 0x4(%eax),%esp		#  stack
709199767f8SToomas Soome		popl %eax			# Call
710199767f8SToomas Soome		call *%eax			#  program
711199767f8SToomas Soomeintx30.1:	orb $0x1,%ss:btx_hdr+0x7	# Flag reboot
712199767f8SToomas Soome		jmp exit			# Exit
713199767f8SToomas Soome/*
714199767f8SToomas Soome * Dump structure [EBX] to [EDI], using format string [ESI].
715199767f8SToomas Soome */
716199767f8SToomas Soomedump.0: 	stosb				# Save char
717199767f8SToomas Soomedump:		lodsb				# Load char
718199767f8SToomas Soome		testb %al,%al			# End of string?
719199767f8SToomas Soome		jz dump.10			# Yes
720199767f8SToomas Soome		testb $0x80,%al 		# Control?
721199767f8SToomas Soome		jz dump.0			# No
722199767f8SToomas Soome		movb %al,%ch			# Save control
723199767f8SToomas Soome		movb $'=',%al			# Append
724199767f8SToomas Soome		stosb				#  '='
725199767f8SToomas Soome		lodsb				# Get offset
726199767f8SToomas Soome		pushl %esi			# Save
727199767f8SToomas Soome		movsbl %al,%esi 		# To
728199767f8SToomas Soome		addl %ebx,%esi			#  pointer
729199767f8SToomas Soome		testb $DMP_X16,%ch		# Dump word?
730199767f8SToomas Soome		jz dump.1			# No
731199767f8SToomas Soome		lodsw				# Get and
732199767f8SToomas Soome		call hex16			#  dump it
733199767f8SToomas Soomedump.1: 	testb $DMP_X32,%ch		# Dump long?
734199767f8SToomas Soome		jz dump.2			# No
735199767f8SToomas Soome		lodsl				# Get and
736199767f8SToomas Soome		call hex32			#  dump it
737199767f8SToomas Soomedump.2: 	testb $DMP_MEM,%ch		# Dump memory?
738199767f8SToomas Soome		jz dump.8			# No
739199767f8SToomas Soome		pushl %ds			# Save
740199767f8SToomas Soome		testl $PSL_VM,0x50(%ebx)	# V86 mode?
741199767f8SToomas Soome		jnz dump.3			# Yes
742199767f8SToomas Soome		verr 0x4(%esi)	 		# Readable selector?
743199767f8SToomas Soome		jnz dump.3			# No
744199767f8SToomas Soome		ldsl (%esi),%esi		# Load pointer
745199767f8SToomas Soome		jmp dump.4			# Join common code
746199767f8SToomas Soomedump.3: 	lodsl				# Set offset
747199767f8SToomas Soome		xchgl %eax,%edx 		# Save
748199767f8SToomas Soome		lodsl				# Get segment
749199767f8SToomas Soome		shll $0x4,%eax			#  * 0x10
750199767f8SToomas Soome		addl %edx,%eax			#  + offset
751199767f8SToomas Soome		xchgl %eax,%esi 		# Set pointer
752199767f8SToomas Soomedump.4: 	movb $2,%dl			# Num lines
753199767f8SToomas Soomedump.4a:	movb $0x10,%cl			# Bytes to dump
754199767f8SToomas Soomedump.5: 	lodsb				# Get byte and
755199767f8SToomas Soome		call hex8			#  dump it
756199767f8SToomas Soome		decb %cl			# Keep count
757199767f8SToomas Soome		jz dump.6a			# If done
758199767f8SToomas Soome		movb $'-',%al			# Separator
759199767f8SToomas Soome		cmpb $0x8,%cl			# Half way?
760199767f8SToomas Soome		je dump.6			# Yes
761199767f8SToomas Soome		movb $' ',%al			# Use space
762199767f8SToomas Soomedump.6: 	stosb				# Save separator
763199767f8SToomas Soome		jmp dump.5			# Continue
764199767f8SToomas Soomedump.6a:	decb %dl			# Keep count
765199767f8SToomas Soome		jz dump.7			# If done
766199767f8SToomas Soome		movb $0xa,%al			# Line feed
767199767f8SToomas Soome		stosb				# Save one
768199767f8SToomas Soome		movb $7,%cl			# Leading
769199767f8SToomas Soome		movb $' ',%al			#  spaces
770199767f8SToomas Soomedump.6b:	stosb				# Dump
771199767f8SToomas Soome		decb %cl			#  spaces
772199767f8SToomas Soome		jnz dump.6b
773199767f8SToomas Soome		jmp dump.4a			# Next line
774199767f8SToomas Soomedump.7: 	popl %ds			# Restore
775199767f8SToomas Soomedump.8: 	popl %esi			# Restore
776199767f8SToomas Soome		movb $0xa,%al			# Line feed
777199767f8SToomas Soome		testb $DMP_EOL,%ch		# End of line?
778199767f8SToomas Soome		jnz dump.9			# Yes
779199767f8SToomas Soome		movb $' ',%al			# Use spaces
780199767f8SToomas Soome		stosb				# Save one
781199767f8SToomas Soomedump.9: 	jmp dump.0			# Continue
782199767f8SToomas Soomedump.10:	stosb				# Terminate string
783199767f8SToomas Soome		ret				# To caller
784199767f8SToomas Soome/*
785199767f8SToomas Soome * Convert EAX, AX, or AL to hex, saving the result to [EDI].
786199767f8SToomas Soome */
787199767f8SToomas Soomehex32:		pushl %eax			# Save
788199767f8SToomas Soome		shrl $0x10,%eax 		# Do upper
789199767f8SToomas Soome		call hex16			#  16
790199767f8SToomas Soome		popl %eax			# Restore
791199767f8SToomas Soomehex16:		call hex16.1			# Do upper 8
792199767f8SToomas Soomehex16.1:	xchgb %ah,%al			# Save/restore
793199767f8SToomas Soomehex8:		pushl %eax			# Save
794199767f8SToomas Soome		shrb $0x4,%al			# Do upper
795199767f8SToomas Soome		call hex8.1			#  4
796199767f8SToomas Soome		popl %eax			# Restore
797199767f8SToomas Soomehex8.1: 	andb $0xf,%al			# Get lower 4
798199767f8SToomas Soome		cmpb $0xa,%al			# Convert
799199767f8SToomas Soome		sbbb $0x69,%al			#  to hex
800199767f8SToomas Soome		das				#  digit
801199767f8SToomas Soome		orb $0x20,%al			# To lower case
802199767f8SToomas Soome		stosb				# Save char
803199767f8SToomas Soome		ret				# (Recursive)
804199767f8SToomas Soome/*
805199767f8SToomas Soome * Output zero-terminated string [ESI] to the console.
806199767f8SToomas Soome */
807199767f8SToomas Soomeputstr.0:	call putchr			# Output char
808199767f8SToomas Soomeputstr: 	lodsb				# Load char
809199767f8SToomas Soome		testb %al,%al			# End of string?
810199767f8SToomas Soome		jnz putstr.0			# No
811199767f8SToomas Soome		ret				# To caller
812199767f8SToomas Soome#ifdef BTX_SERIAL
813199767f8SToomas Soome		.set SIO_PRT,SIOPRT		# Base port
814199767f8SToomas Soome		.set SIO_FMT,SIOFMT		# 8N1
815199767f8SToomas Soome		.set SIO_DIV,(115200/SIOSPD)	# 115200 / SPD
816199767f8SToomas Soome
817199767f8SToomas Soome/*
818199767f8SToomas Soome * int sio_init(void)
819199767f8SToomas Soome */
820199767f8SToomas Soomesio_init:	movw $SIO_PRT+0x3,%dx		# Data format reg
821199767f8SToomas Soome		movb $SIO_FMT|0x80,%al		# Set format
822199767f8SToomas Soome		outb %al,(%dx)			#  and DLAB
823199767f8SToomas Soome		pushl %edx			# Save
824199767f8SToomas Soome		subb $0x3,%dl			# Divisor latch reg
825199767f8SToomas Soome		movw $SIO_DIV,%ax		# Set
826199767f8SToomas Soome		outw %ax,(%dx)			#  BPS
827199767f8SToomas Soome		popl %edx			# Restore
828199767f8SToomas Soome		movb $SIO_FMT,%al		# Clear
829199767f8SToomas Soome		outb %al,(%dx)			#  DLAB
830199767f8SToomas Soome		incl %edx			# Modem control reg
831199767f8SToomas Soome		movb $0x3,%al			# Set RTS,
832199767f8SToomas Soome		outb %al,(%dx)			#  DTR
833199767f8SToomas Soome		incl %edx			# Line status reg
834199767f8SToomas Soome		call sio_getc.1 		# Get character
835199767f8SToomas Soome
836199767f8SToomas Soome/*
837199767f8SToomas Soome * int sio_flush(void)
838199767f8SToomas Soome */
839199767f8SToomas Soomesio_flush:	xorl %eax,%eax			# Return value
840199767f8SToomas Soome		xorl %ecx,%ecx			# Timeout
841199767f8SToomas Soome		movb $0x80,%ch			#  counter
842199767f8SToomas Soomesio_flush.1:	call sio_ischar 		# Check for character
843199767f8SToomas Soome		jz sio_flush.2			# Till none
844199767f8SToomas Soome		loop sio_flush.1		#  or counter is zero
845199767f8SToomas Soome		movb $1, %al			# Exhausted all tries
846199767f8SToomas Soomesio_flush.2:	ret				# To caller
847199767f8SToomas Soome
848199767f8SToomas Soome/*
849199767f8SToomas Soome * void sio_putc(int c)
850199767f8SToomas Soome */
851199767f8SToomas Soomesio_putc:	movw $SIO_PRT+0x5,%dx		# Line status reg
852199767f8SToomas Soome		xor %ecx,%ecx			# Timeout
853199767f8SToomas Soome		movb $0x40,%ch			#  counter
854199767f8SToomas Soomesio_putc.1:	inb (%dx),%al			# Transmitter
855199767f8SToomas Soome		testb $0x20,%al 		#  buffer empty?
856199767f8SToomas Soome		loopz sio_putc.1		# No
857199767f8SToomas Soome		jz sio_putc.2			# If timeout
858199767f8SToomas Soome		movb 0x4(%esp,1),%al		# Get character
859199767f8SToomas Soome		subb $0x5,%dl			# Transmitter hold reg
860199767f8SToomas Soome		outb %al,(%dx)			# Write character
861199767f8SToomas Soomesio_putc.2:	ret $0x4			# To caller
862199767f8SToomas Soome
863199767f8SToomas Soome/*
864199767f8SToomas Soome * int sio_getc(void)
865199767f8SToomas Soome */
866199767f8SToomas Soomesio_getc:	call sio_ischar 		# Character available?
867199767f8SToomas Soome		jz sio_getc			# No
868199767f8SToomas Soomesio_getc.1:	subb $0x5,%dl			# Receiver buffer reg
869199767f8SToomas Soome		inb (%dx),%al			# Read character
870199767f8SToomas Soome		ret				# To caller
871199767f8SToomas Soome
872199767f8SToomas Soome/*
873199767f8SToomas Soome * int sio_ischar(void)
874199767f8SToomas Soome */
875199767f8SToomas Soomesio_ischar:	movw $SIO_PRT+0x5,%dx		# Line status register
876199767f8SToomas Soome		xorl %eax,%eax			# Zero
877199767f8SToomas Soome		inb (%dx),%al			# Received data
878199767f8SToomas Soome		andb $0x1,%al			#  ready?
879199767f8SToomas Soome		ret				# To caller
880199767f8SToomas Soome
881199767f8SToomas Soome/*
882199767f8SToomas Soome * Output character AL to the serial console.
883199767f8SToomas Soome */
884199767f8SToomas Soomeputchr: 	pusha				# Save
885199767f8SToomas Soome		cmpb $10, %al			# is it a newline?
886199767f8SToomas Soome		jne putchr.1			#  no?, then leave
887199767f8SToomas Soome		push $13			# output a carriage
888199767f8SToomas Soome		call sio_putc			#  return first
889199767f8SToomas Soome		movb $10, %al			# restore %al
890199767f8SToomas Soomeputchr.1:	pushl %eax			# Push the character
891199767f8SToomas Soome						#  onto the stack
892199767f8SToomas Soome		call sio_putc			# Output the character
893199767f8SToomas Soome		popa				# Restore
894199767f8SToomas Soome		ret				# To caller
895199767f8SToomas Soome#else
896199767f8SToomas Soome/*
897199767f8SToomas Soome * Output character AL to the console.
898199767f8SToomas Soome */
899199767f8SToomas Soomeputchr: 	pusha				# Save
900199767f8SToomas Soome		xorl %ecx,%ecx			# Zero for loops
901199767f8SToomas Soome		movb $SCR_MAT,%ah		# Mode/attribute
902199767f8SToomas Soome		movl $BDA_POS,%ebx		# BDA pointer
903199767f8SToomas Soome		movw (%ebx),%dx 		# Cursor position
904199767f8SToomas Soome		movl $0xb8000,%edi		# Regen buffer (color)
905199767f8SToomas Soome		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
906199767f8SToomas Soome		jne putchr.1			# No
907199767f8SToomas Soome		xorw %di,%di			# Regen buffer (mono)
908199767f8SToomas Soomeputchr.1:	cmpb $0xa,%al			# New line?
909199767f8SToomas Soome		je putchr.2			# Yes
910199767f8SToomas Soome		xchgl %eax,%ecx 		# Save char
911199767f8SToomas Soome		movb $SCR_COL,%al		# Columns per row
912199767f8SToomas Soome		mulb %dh			#  * row position
913199767f8SToomas Soome		addb %dl,%al			#  + column
914199767f8SToomas Soome		adcb $0x0,%ah			#  position
915199767f8SToomas Soome		shll %eax			#  * 2
916199767f8SToomas Soome		xchgl %eax,%ecx 		# Swap char, offset
917199767f8SToomas Soome		movw %ax,(%edi,%ecx,1)		# Write attr:char
918199767f8SToomas Soome		incl %edx			# Bump cursor
919199767f8SToomas Soome		cmpb $SCR_COL,%dl		# Beyond row?
920199767f8SToomas Soome		jb putchr.3			# No
921199767f8SToomas Soomeputchr.2:	xorb %dl,%dl			# Zero column
922199767f8SToomas Soome		incb %dh			# Bump row
923199767f8SToomas Soomeputchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
924199767f8SToomas Soome		jb putchr.4			# No
925199767f8SToomas Soome		leal 2*SCR_COL(%edi),%esi	# New top line
926199767f8SToomas Soome		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
927199767f8SToomas Soome		rep				# Scroll
928199767f8SToomas Soome		movsl				#  screen
929199767f8SToomas Soome		movb $0x20,%al			# Space
930199767f8SToomas Soome		movb $SCR_COL,%cl		# Columns to clear
931199767f8SToomas Soome		rep				# Clear
932199767f8SToomas Soome		stosw				#  line
933199767f8SToomas Soome		movb $SCR_ROW-1,%dh		# Bottom line
934199767f8SToomas Soomeputchr.4:	movw %dx,(%ebx) 		# Update position
935199767f8SToomas Soome		popa				# Restore
936199767f8SToomas Soome		ret				# To caller
937199767f8SToomas Soome#endif
938199767f8SToomas Soome
939199767f8SToomas Soome		.code16
940199767f8SToomas Soome/*
941199767f8SToomas Soome * Real Mode Hardware interrupt jump table.
942199767f8SToomas Soome */
943199767f8SToomas Soomeintr20: 	push $0x8			# Int 0x20: IRQ0
944199767f8SToomas Soome		jmp int_hwr			# V86 int 0x8
945199767f8SToomas Soome		push $0x9			# Int 0x21: IRQ1
946199767f8SToomas Soome		jmp int_hwr			# V86 int 0x9
947199767f8SToomas Soome		push $0xa			# Int 0x22: IRQ2
948199767f8SToomas Soome		jmp int_hwr			# V86 int 0xa
949199767f8SToomas Soome		push $0xb			# Int 0x23: IRQ3
950199767f8SToomas Soome		jmp int_hwr			# V86 int 0xb
951199767f8SToomas Soome		push $0xc			# Int 0x24: IRQ4
952199767f8SToomas Soome		jmp int_hwr			# V86 int 0xc
953199767f8SToomas Soome		push $0xd			# Int 0x25: IRQ5
954199767f8SToomas Soome		jmp int_hwr			# V86 int 0xd
955199767f8SToomas Soome		push $0xe			# Int 0x26: IRQ6
956199767f8SToomas Soome		jmp int_hwr			# V86 int 0xe
957199767f8SToomas Soome		push $0xf			# Int 0x27: IRQ7
958199767f8SToomas Soome		jmp int_hwr			# V86 int 0xf
959199767f8SToomas Soome		push $0x70			# Int 0x28: IRQ8
960199767f8SToomas Soome		jmp int_hwr			# V86 int 0x70
961199767f8SToomas Soome		push $0x71			# Int 0x29: IRQ9
962199767f8SToomas Soome		jmp int_hwr			# V86 int 0x71
963199767f8SToomas Soome		push $0x72			# Int 0x2a: IRQ10
964199767f8SToomas Soome		jmp int_hwr			# V86 int 0x72
965199767f8SToomas Soome		push $0x73			# Int 0x2b: IRQ11
966199767f8SToomas Soome		jmp int_hwr			# V86 int 0x73
967199767f8SToomas Soome		push $0x74			# Int 0x2c: IRQ12
968199767f8SToomas Soome		jmp int_hwr			# V86 int 0x74
969199767f8SToomas Soome		push $0x75			# Int 0x2d: IRQ13
970199767f8SToomas Soome		jmp int_hwr			# V86 int 0x75
971199767f8SToomas Soome		push $0x76			# Int 0x2e: IRQ14
972199767f8SToomas Soome		jmp int_hwr			# V86 int 0x76
973199767f8SToomas Soome		push $0x77			# Int 0x2f: IRQ15
974199767f8SToomas Soome		jmp int_hwr			# V86 int 0x77
975199767f8SToomas Soome/*
976199767f8SToomas Soome * Reflect hardware interrupts in real mode.
977199767f8SToomas Soome */
978199767f8SToomas Soomeint_hwr: 	push %ax			# Save
979199767f8SToomas Soome		push %ds			# Save
980199767f8SToomas Soome		push %bp			# Save
981*55fea89dSDan Cross		mov %sp,%bp			# Address stack frame
982199767f8SToomas Soome		xchg %bx,6(%bp)			# Swap BX, int no
983199767f8SToomas Soome		xor %ax,%ax			# Set %ds:%bx to
984199767f8SToomas Soome		shl $2,%bx			#  point to
985199767f8SToomas Soome		mov %ax,%ds			#  IDT entry
986199767f8SToomas Soome		mov (%bx),%ax			# Load IP
987199767f8SToomas Soome		mov 2(%bx),%bx			# Load CS
988199767f8SToomas Soome		xchg %ax,4(%bp)			# Swap saved %ax,%bx with
989199767f8SToomas Soome		xchg %bx,6(%bp)			#  CS:IP of handler
990199767f8SToomas Soome		pop %bp				# Restore
991199767f8SToomas Soome		pop %ds				# Restore
992199767f8SToomas Soome		lret				# Jump to handler
993199767f8SToomas Soome
994199767f8SToomas Soome		.p2align 4
995199767f8SToomas Soome/*
996199767f8SToomas Soome * Global descriptor table.
997199767f8SToomas Soome */
998199767f8SToomas Soomegdt:		.word 0x0,0x0,0x0,0x0		# Null entry
999199767f8SToomas Soome		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
1000199767f8SToomas Soome		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
1001199767f8SToomas Soome		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
1002199767f8SToomas Soome		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
1003199767f8SToomas Soome		.word 0xffff,MEM_USR,0xfa00,0xcf# SEL_UCODE
1004199767f8SToomas Soome		.word 0xffff,MEM_USR,0xf200,0xcf# SEL_UDATA
1005199767f8SToomas Soometss_desc:	.word _TSSLM,MEM_TSS,0x8900,0x0 # SEL_TSS
1006199767f8SToomas Soomegdt.1:
1007199767f8SToomas Soome/*
1008199767f8SToomas Soome * Pseudo-descriptors.
1009199767f8SToomas Soome */
1010199767f8SToomas Soomegdtdesc:	.word gdt.1-gdt-1,gdt,0x0	# GDT
1011199767f8SToomas Soomeidtdesc:	.word _IDTLM,MEM_IDT,0x0	# IDT
1012199767f8SToomas Soomeivtdesc:	.word 0x400-0x0-1,0x0,0x0	# IVT
1013199767f8SToomas Soome/*
1014199767f8SToomas Soome * IDT construction control string.
1015199767f8SToomas Soome */
1016199767f8SToomas Soomeidtctl: 	.byte 0x10,  0x8e		# Int 0x0-0xf
1017199767f8SToomas Soome		.word 0x7dfb,intx00		#  (exceptions)
1018199767f8SToomas Soome		.byte 0x10,  0x8e		# Int 0x10
1019199767f8SToomas Soome		.word 0x1,   intx10		#  (exception)
1020199767f8SToomas Soome		.byte 0x10,  0x8e		# Int 0x20-0x2f
1021199767f8SToomas Soome		.word 0xffff,intx20		#  (hardware)
1022199767f8SToomas Soome		.byte 0x1,   0xee		# int 0x30
1023199767f8SToomas Soome		.word 0x1,   intx30		#  (system call)
1024199767f8SToomas Soome		.byte 0x2,   0xee		# Int 0x31-0x32
1025199767f8SToomas Soome		.word 0x1,   intx31		#  (V86, null)
1026199767f8SToomas Soome		.byte 0x0			# End of string
1027199767f8SToomas Soome/*
1028199767f8SToomas Soome * Dump format string.
1029199767f8SToomas Soome */
1030199767f8SToomas Soomedmpfmt: 	.byte '\n'			# "\n"
1031199767f8SToomas Soome		.ascii "int"			# "int="
1032199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x40 # "00000000  "
1033199767f8SToomas Soome		.ascii "err"			# "err="
1034199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x44 # "00000000  "
1035199767f8SToomas Soome		.ascii "efl"			# "efl="
1036199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x50 # "00000000  "
1037199767f8SToomas Soome		.ascii "eip"			# "eip="
1038199767f8SToomas Soome		.byte 0x80|DMP_X32|DMP_EOL,0x48 # "00000000\n"
1039199767f8SToomas Soome		.ascii "eax"			# "eax="
1040199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x34 # "00000000  "
1041199767f8SToomas Soome		.ascii "ebx"			# "ebx="
1042199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x28 # "00000000  "
1043199767f8SToomas Soome		.ascii "ecx"			# "ecx="
1044199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x30 # "00000000  "
1045199767f8SToomas Soome		.ascii "edx"			# "edx="
1046199767f8SToomas Soome		.byte 0x80|DMP_X32|DMP_EOL,0x2c # "00000000\n"
1047199767f8SToomas Soome		.ascii "esi"			# "esi="
1048199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x1c # "00000000  "
1049199767f8SToomas Soome		.ascii "edi"			# "edi="
1050199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x18 # "00000000  "
1051199767f8SToomas Soome		.ascii "ebp"			# "ebp="
1052199767f8SToomas Soome		.byte 0x80|DMP_X32,	   0x20 # "00000000  "
1053199767f8SToomas Soome		.ascii "esp"			# "esp="
1054199767f8SToomas Soome		.byte 0x80|DMP_X32|DMP_EOL,0x0	# "00000000\n"
1055199767f8SToomas Soome		.ascii "cs"			# "cs="
1056199767f8SToomas Soome		.byte 0x80|DMP_X16,	   0x4c # "0000  "
1057199767f8SToomas Soome		.ascii "ds"			# "ds="
1058199767f8SToomas Soome		.byte 0x80|DMP_X16,	   0xc	# "0000  "
1059199767f8SToomas Soome		.ascii "es"			# "es="
1060199767f8SToomas Soome		.byte 0x80|DMP_X16,	   0x8	# "0000  "
1061199767f8SToomas Soome		.ascii "  "			# "  "
1062199767f8SToomas Soome		.ascii "fs"			# "fs="
1063199767f8SToomas Soome		.byte 0x80|DMP_X16,	   0x10 # "0000  "
1064199767f8SToomas Soome		.ascii "gs"			# "gs="
1065199767f8SToomas Soome		.byte 0x80|DMP_X16,	   0x14 # "0000  "
1066199767f8SToomas Soome		.ascii "ss"			# "ss="
1067199767f8SToomas Soome		.byte 0x80|DMP_X16|DMP_EOL,0x4	# "0000\n"
1068199767f8SToomas Soome		.ascii "cs:eip" 		# "cs:eip="
1069199767f8SToomas Soome		.byte 0x80|DMP_MEM|DMP_EOL,0x48 # "00 00 ... 00 00\n"
1070199767f8SToomas Soome		.ascii "ss:esp" 		# "ss:esp="
1071199767f8SToomas Soome		.byte 0x80|DMP_MEM|DMP_EOL,0x0	# "00 00 ... 00 00\n"
1072199767f8SToomas Soome		.asciz "BTX halted\n"		# End
1073199767f8SToomas Soome/*
1074199767f8SToomas Soome * Bad VM86 call panic
1075199767f8SToomas Soome */
1076199767f8SToomas Soomebadvm86:	.asciz "Invalid VM86 Request\n"
1077199767f8SToomas Soome
1078199767f8SToomas Soome/*
1079199767f8SToomas Soome * End of BTX memory.
1080199767f8SToomas Soome */
1081199767f8SToomas Soome		.p2align 4
1082199767f8SToomas Soomebreak:
1083