btx.S revision 225736
1/*
2 * Copyright (c) 1998 Robert Nordier
3 * All rights reserved.
4 *
5 * Redistribution and use in source and binary forms are freely
6 * permitted provided that the above copyright notice and this
7 * paragraph and the following disclaimer are duplicated in all
8 * such forms.
9 *
10 * This software is provided "AS IS" and without any express or
11 * implied warranties, including, without limitation, the implied
12 * warranties of merchantability and fitness for a particular
13 * purpose.
14 *
15 * $FreeBSD: stable/9/sys/boot/pc98/btx/btx/btx.S 200254 2009-12-08 13:04:26Z nyan $
16 */
17
18/*
19 * Memory layout.
20 */
21		.set MEM_BTX,0x1000		# Start of BTX memory
22		.set MEM_ESP0,0x1800		# Supervisor stack
23		.set MEM_BUF,0x1800		# Scratch buffer
24		.set MEM_ESPR,0x5e00		# Real mode stack
25		.set MEM_IDT,0x5e00		# IDT
26		.set MEM_TSS,0x5f98		# TSS
27		.set MEM_MAP,0x6000		# I/O bit map
28		.set MEM_TSS_END,0x7fff		# End of TSS
29		.set MEM_ORG,0x9000		# BTX code
30		.set MEM_USR,0xa000		# Start of user memory
31/*
32 * Paging control.
33 */
34		.set PAG_SIZ,0x1000		# Page size
35		.set PAG_CNT,0x1000		# Pages to map
36/*
37 * Fields in %eflags.
38 */
39		.set PSL_RESERVED_DEFAULT,0x00000002
40		.set PSL_T,0x00000100		# Trap flag
41		.set PSL_I,0x00000200		# Interrupt enable flag
42		.set PSL_VM,0x00020000		# Virtual 8086 mode flag
43		.set PSL_AC,0x00040000		# Alignment check flag
44/*
45 * Segment selectors.
46 */
47		.set SEL_SCODE,0x8		# Supervisor code
48		.set SEL_SDATA,0x10		# Supervisor data
49		.set SEL_RCODE,0x18		# Real mode code
50		.set SEL_RDATA,0x20		# Real mode data
51		.set SEL_UCODE,0x28|3		# User code
52		.set SEL_UDATA,0x30|3		# User data
53		.set SEL_TSS,0x38		# TSS
54/*
55 * Task state segment fields.
56 */
57		.set TSS_ESP0,0x4		# PL 0 ESP
58		.set TSS_SS0,0x8		# PL 0 SS
59		.set TSS_MAP,0x66		# I/O bit map base
60/*
61 * System calls.
62 */
63		.set SYS_EXIT,0x0		# Exit
64		.set SYS_EXEC,0x1		# Exec
65/*
66 * Fields in V86 interface structure.
67 */
68		.set V86_CTL,0x0		# Control flags
69		.set V86_ADDR,0x4		# Int number/address
70		.set V86_ES,0x8			# V86 ES
71		.set V86_DS,0xc			# V86 DS
72		.set V86_FS,0x10		# V86 FS
73		.set V86_GS,0x14		# V86 GS
74/*
75 * V86 control flags.
76 */
77		.set V86F_ADDR,0x10000		# Segment:offset address
78		.set V86F_CALLF,0x20000		# Emulate far call
79		.set V86F_FLAGS,0x40000		# Return flags
80/*
81 * Dump format control bytes.
82 */
83		.set DMP_X16,0x1		# Word
84		.set DMP_X32,0x2		# Long
85		.set DMP_MEM,0x4		# Memory
86		.set DMP_EOL,0x8		# End of line
87/*
88 * Screen defaults and assumptions.
89 */
90		.set SCR_MAT,0xe1		# Mode/attribute
91		.set SCR_COL,0x50		# Columns per row
92		.set SCR_ROW,0x19		# Rows per screen
93/*
94 * BIOS Data Area locations.
95 */
96		.set BDA_MEM,0x501		# Free memory
97		.set BDA_POS,0x53e		# Cursor position
98/*
99 * Derivations, for brevity.
100 */
101		.set _ESP0H,MEM_ESP0>>0x8	# Byte 1 of ESP0
102		.set _TSSIO,MEM_MAP-MEM_TSS	# TSS I/O base
103		.set _TSSLM,MEM_TSS_END-MEM_TSS	# TSS limit
104		.set _IDTLM,MEM_TSS-MEM_IDT-1	# IDT limit
105/*
106 * Code segment.
107 */
108		.globl start
109		.code16
110start:						# Start of code
111/*
112 * BTX header.
113 */
114btx_hdr:	.byte 0xeb			# Machine ID
115		.byte 0xe			# Header size
116		.ascii "BTX"			# Magic
117		.byte 0x1			# Major version
118		.byte 0x2			# Minor version
119		.byte BTX_FLAGS			# Flags
120		.word PAG_CNT-MEM_ORG>>0xc	# Paging control
121		.word break-start		# Text size
122		.long 0x0			# Entry address
123/*
124 * Initialization routine.
125 */
126init:		cli				# Disable interrupts
127		xor %ax,%ax			# Zero/segment
128		mov %ax,%ss			# Set up
129		mov $MEM_ESP0,%sp		#  stack
130		mov %ax,%es			# Address
131		mov %ax,%ds			#  data
132		pushl $0x2			# Clear
133		popfl				#  flags
134/*
135 * Initialize memory.
136 */
137		mov $MEM_IDT,%di		# Memory to initialize
138		mov $(MEM_ORG-MEM_IDT)/2,%cx	# Words to zero
139		rep				# Zero-fill
140		stosw				#  memory
141/*
142 * Update real mode IDT for reflecting hardware interrupts.
143 */
144		mov $intr20,%bx			# Address first handler
145		mov $0x10,%cx			# Number of handlers
146		mov $0x20*4,%di			# First real mode IDT entry
147init.0:		mov %bx,(%di)			# Store IP
148		inc %di				# Address next
149		inc %di				#  entry
150		stosw				# Store CS
151		add $4,%bx			# Next handler
152		loop init.0			# Next IRQ
153/*
154 * Create IDT.
155 */
156		mov $MEM_IDT,%di
157		mov $idtctl,%si			# Control string
158init.1: 	lodsb				# Get entry
159		cbw				#  count
160		xchg %ax,%cx			#  as word
161		jcxz init.4			# If done
162		lodsb				# Get segment
163		xchg %ax,%dx	 		#  P:DPL:type
164		lodsw				# Get control
165		xchg %ax,%bx			#  set
166		lodsw				# Get handler offset
167		mov $SEL_SCODE,%dh		# Segment selector
168init.2: 	shr %bx				# Handle this int?
169		jnc init.3			# No
170		mov %ax,(%di)			# Set handler offset
171		mov %dh,0x2(%di)		#  and selector
172		mov %dl,0x5(%di)		# Set P:DPL:type
173		add $0x4,%ax			# Next handler
174init.3: 	lea 0x8(%di),%di		# Next entry
175		loop init.2			# Till set done
176		jmp init.1			# Continue
177/*
178 * Initialize TSS.
179 */
180init.4: 	movb $_ESP0H,TSS_ESP0+1(%di)	# Set ESP0
181		movb $SEL_SDATA,TSS_SS0(%di)	# Set SS0
182		movb $_TSSIO,TSS_MAP(%di)	# Set I/O bit map base
183/*
184 * Bring up the system.
185 */
186		mov $0x2820,%bx			# Set protected mode
187		callw setpic			#  IRQ offsets
188		lidt idtdesc	 		# Set IDT
189		lgdt gdtdesc	 		# Set GDT
190		mov %cr0,%eax			# Switch to protected
191		inc %ax				#  mode
192		mov %eax,%cr0			#
193		ljmp $SEL_SCODE,$init.8		# To 32-bit code
194		.code32
195init.8: 	xorl %ecx,%ecx			# Zero
196		movb $SEL_SDATA,%cl		# To 32-bit
197		movw %cx,%ss			#  stack
198/*
199 * Launch user task.
200 */
201		movb $SEL_TSS,%cl		# Set task
202		ltr %cx				#  register
203		movl $MEM_USR,%edx		# User base address
204		movzwl %ss:BDA_MEM,%eax 	# Get free memory
205		andl $0x7,%eax
206		incl %eax
207		shll $0x11,%eax			# To bytes
208		subl $0x1000,%eax		# Less arg space
209		subl %edx,%eax			# Less base
210		movb $SEL_UDATA,%cl		# User data selector
211		pushl %ecx			# Set SS
212		pushl %eax			# Set ESP
213		push $0x202			# Set flags (IF set)
214		push $SEL_UCODE			# Set CS
215		pushl btx_hdr+0xc		# Set EIP
216		pushl %ecx			# Set GS
217		pushl %ecx			# Set FS
218		pushl %ecx			# Set DS
219		pushl %ecx			# Set ES
220		pushl %edx			# Set EAX
221		movb $0x7,%cl			# Set remaining
222init.9:		push $0x0			#  general
223		loop init.9			#  registers
224#ifdef BTX_SERIAL
225		call sio_init			# setup the serial console
226#endif
227		popa				#  and initialize
228		popl %es			# Initialize
229		popl %ds			#  user
230		popl %fs			#  segment
231		popl %gs			#  registers
232		iret				# To user mode
233/*
234 * Exit routine.
235 */
236exit:		cli				# Disable interrupts
237		movl $MEM_ESP0,%esp		# Clear stack
238/*
239 * Turn off paging.
240 */
241		movl %cr0,%eax			# Get CR0
242		andl $~0x80000000,%eax		# Disable
243		movl %eax,%cr0			#  paging
244		xorl %ecx,%ecx			# Zero
245		movl %ecx,%cr3			# Flush TLB
246/*
247 * Restore the GDT in case we caught a kernel trap.
248 */
249		lgdt gdtdesc	 		# Set GDT
250/*
251 * To 16 bits.
252 */
253		ljmpw $SEL_RCODE,$exit.1	# Reload CS
254		.code16
255exit.1: 	mov $SEL_RDATA,%cl		# 16-bit selector
256		mov %cx,%ss			# Reload SS
257		mov %cx,%ds			# Load
258		mov %cx,%es			#  remaining
259		mov %cx,%fs			#  segment
260		mov %cx,%gs			#  registers
261/*
262 * To real-address mode.
263 */
264		dec %ax				# Switch to
265		mov %eax,%cr0			#  real mode
266		ljmp $0x0,$exit.2		# Reload CS
267exit.2: 	xor %ax,%ax			# Real mode segment
268		mov %ax,%ss			# Reload SS
269		mov %ax,%ds			# Address data
270		mov $0x1008,%bx			# Set real mode
271		callw setpic			#  IRQ offsets
272		lidt ivtdesc	 		# Set IVT
273/*
274 * Reboot or await reset.
275 */
276		sti				# Enable interrupts
277		testb $0x1,btx_hdr+0x7		# Reboot?
278exit.3:		jz exit.3			# No
279		movb $0xa0,%al
280		outb %al,$0x35
281		movb $0x00,%al
282		outb %al,$0xf0			# reboot the machine
283exit.4:		jmp exit.4
284/*
285 * Set IRQ offsets by reprogramming 8259A PICs.
286 */
287setpic: 	in $0x02,%al			# Save master
288		push %ax			#  IMR
289		in $0x0a,%al			# Save slave
290		push %ax			#  IMR
291		movb $0x11,%al			# ICW1 to
292		outb %al,$0x00			#  master,
293		outb %al,$0x08			#  slave
294		movb %bl,%al			# ICW2 to
295		outb %al,$0x02			#  master
296		movb %bh,%al			# ICW2 to
297		outb %al,$0x0a			#  slave
298		movb $0x80,%al			# ICW3 to
299		outb %al,$0x02			#  master
300		movb $0x7,%al			# ICW3 to
301		outb %al,$0x0a			#  slave
302		movb $0x1d,%al			# ICW4 to
303		outb %al,$0x02			#  master,
304		movb $0x9,%al			# ICW4 to
305		outb %al,$0x0a			#  slave
306		pop %ax				# Restore slave
307		outb %al,$0x0a			#  IMR
308		pop %ax				# Restore master
309		outb %al,$0x02			#  IMR
310		retw				# To caller
311		.code32
312/*
313 * Exception jump table.
314 */
315intx00: 	push $0x0			# Int 0x0: #DE
316		jmp ex_noc			# Divide error
317		push $0x1			# Int 0x1: #DB
318		jmp ex_noc			# Debug
319		push $0x3			# Int 0x3: #BP
320		jmp ex_noc			# Breakpoint
321		push $0x4			# Int 0x4: #OF
322		jmp ex_noc			# Overflow
323		push $0x5			# Int 0x5: #BR
324		jmp ex_noc			# BOUND range exceeded
325		push $0x6			# Int 0x6: #UD
326		jmp ex_noc			# Invalid opcode
327		push $0x7			# Int 0x7: #NM
328		jmp ex_noc			# Device not available
329		push $0x8			# Int 0x8: #DF
330		jmp except			# Double fault
331		push $0xa			# Int 0xa: #TS
332		jmp except			# Invalid TSS
333		push $0xb			# Int 0xb: #NP
334		jmp except			# Segment not present
335		push $0xc			# Int 0xc: #SS
336		jmp except			# Stack segment fault
337		push $0xd			# Int 0xd: #GP
338		jmp except			# General protection
339		push $0xe			# Int 0xe: #PF
340		jmp except			# Page fault
341intx10: 	push $0x10			# Int 0x10: #MF
342		jmp ex_noc			# Floating-point error
343/*
344 * Save a zero error code.
345 */
346ex_noc: 	pushl (%esp,1)			# Duplicate int no
347		movb $0x0,0x4(%esp,1)		# Fake error code
348/*
349 * Handle exception.
350 */
351except: 	cld				# String ops inc
352		pushl %ds			# Save
353		pushl %es			#  most
354		pusha				#  registers
355		pushl %gs			# Set GS
356		pushl %fs			# Set FS
357		pushl %ds			# Set DS
358		pushl %es			# Set ES
359		cmpw $SEL_SCODE,0x44(%esp,1)	# Supervisor mode?
360		jne except.1			# No
361		pushl %ss			# Set SS
362		jmp except.2			# Join common code
363except.1:	pushl 0x50(%esp,1)		# Set SS
364except.2:	pushl 0x50(%esp,1)		# Set ESP
365		push $SEL_SDATA			# Set up
366		popl %ds			#  to
367		pushl %ds			#  address
368		popl %es			#  data
369		movl %esp,%ebx			# Stack frame
370		movl $dmpfmt,%esi		# Dump format string
371		movl $MEM_BUF,%edi		# Buffer
372		pushl %eax
373		pushl %edx
374wait.1:		inb  $0x60,%al
375		testb $0x04,%al
376		jz   wait.1
377		movb $0xe0,%al
378		outb %al,$0x62
379wait.2:		inb  $0x60,%al
380		testb $0x01,%al
381		jz   wait.2
382		xorl %edx,%edx
383		inb  $0x62,%al
384		movb %al,%dl
385		inb  $0x62,%al
386		movb %al,%dh
387		inb  $0x62,%al
388		inb  $0x62,%al
389		inb  $0x62,%al
390		movl %edx,%eax
391		shlw $1,%ax
392		movl $BDA_POS,%edx
393		movw %ax,(%edx)
394		popl  %edx
395		popl  %eax
396		pushl %edi			# Dump to
397		call dump			#  buffer
398		popl %esi			#  and
399		call putstr			#  display
400		leal 0x18(%esp,1),%esp		# Discard frame
401		popa				# Restore
402		popl %es			#  registers
403		popl %ds			#  saved
404		cmpb $0x3,(%esp,1)		# Breakpoint?
405		je except.3			# Yes
406		cmpb $0x1,(%esp,1)		# Debug?
407		jne except.2a			# No
408		testl $PSL_T,0x10(%esp,1)	# Trap flag set?
409		jnz except.3			# Yes
410except.2a:	jmp exit			# Exit
411except.3:	leal 0x8(%esp,1),%esp		# Discard err, int no
412		iret				# From interrupt
413
414/*
415 * Reboot the machine by setting the reboot flag and exiting
416 */
417reboot:		orb $0x1,btx_hdr+0x7		# Set the reboot flag
418		jmp exit			# Terminate BTX and reboot
419
420/*
421 * Protected Mode Hardware interrupt jump table.
422 */
423intx20: 	push $0x8			# Int 0x20: IRQ0
424		jmp int_hw			# V86 int 0x8
425		push $0x9			# Int 0x21: IRQ1
426		jmp int_hw			# V86 int 0x9
427		push $0xa			# Int 0x22: IRQ2
428		jmp int_hw			# V86 int 0xa
429		push $0xb			# Int 0x23: IRQ3
430		jmp int_hw			# V86 int 0xb
431		push $0xc			# Int 0x24: IRQ4
432		jmp int_hw			# V86 int 0xc
433		push $0xd			# Int 0x25: IRQ5
434		jmp int_hw			# V86 int 0xd
435		push $0xe			# Int 0x26: IRQ6
436		jmp int_hw			# V86 int 0xe
437		push $0xf			# Int 0x27: IRQ7
438		jmp int_hw			# V86 int 0xf
439		push $0x10			# Int 0x28: IRQ8
440		jmp int_hw			# V86 int 0x10
441		push $0x11			# Int 0x29: IRQ9
442		jmp int_hw			# V86 int 0x11
443		push $0x12			# Int 0x2a: IRQ10
444		jmp int_hw			# V86 int 0x12
445		push $0x13			# Int 0x2b: IRQ11
446		jmp int_hw			# V86 int 0x13
447		push $0x14			# Int 0x2c: IRQ12
448		jmp int_hw			# V86 int 0x14
449		push $0x15			# Int 0x2d: IRQ13
450		jmp int_hw			# V86 int 0x15
451		push $0x16			# Int 0x2e: IRQ14
452		jmp int_hw			# V86 int 0x16
453		push $0x17			# Int 0x2f: IRQ15
454		jmp int_hw			# V86 int 0x17
455
456/*
457 * Invoke real mode interrupt/function call from user mode with arguments.
458 */
459intx31: 	pushl $-1			# Dummy int no for btx_v86
460/*
461 * Invoke real mode interrupt/function call from protected mode.
462 *
463 * We place a trampoline on the user stack that will return to rret_tramp
464 * which will reenter protected mode and then finally return to the user
465 * client.
466 *
467 * Kernel frame %esi points to:		Real mode stack frame at MEM_ESPR:
468 *
469 * -0x00 user %ss			-0x04 kernel %esp (with full frame)
470 * -0x04 user %esp			-0x08 btx_v86 pointer
471 * -0x08 user %eflags			-0x0c flags (only used if interrupt)
472 * -0x0c user %cs			-0x10 real mode CS:IP return trampoline
473 * -0x10 user %eip			-0x12 real mode flags
474 * -0x14 int no				-0x16 real mode CS:IP (target)
475 * -0x18 %eax
476 * -0x1c %ecx
477 * -0x20 %edx
478 * -0x24 %ebx
479 * -0x28 %esp
480 * -0x2c %ebp
481 * -0x30 %esi
482 * -0x34 %edi
483 * -0x38 %gs
484 * -0x3c %fs
485 * -0x40 %ds
486 * -0x44 %es
487 * -0x48 zero %eax (hardware int only)
488 * -0x4c zero %ecx (hardware int only)
489 * -0x50 zero %edx (hardware int only)
490 * -0x54 zero %ebx (hardware int only)
491 * -0x58 zero %esp (hardware int only)
492 * -0x5c zero %ebp (hardware int only)
493 * -0x60 zero %esi (hardware int only)
494 * -0x64 zero %edi (hardware int only)
495 * -0x68 zero %gs (hardware int only)
496 * -0x6c zero %fs (hardware int only)
497 * -0x70 zero %ds (hardware int only)
498 * -0x74 zero %es (hardware int only)
499 */
500int_hw: 	cld				# String ops inc
501		pusha				# Save gp regs
502		pushl %gs			# Save
503		pushl %fs			#  seg
504		pushl %ds			#  regs
505		pushl %es
506		push $SEL_SDATA			# Set up
507		popl %ds			#  to
508		pushl %ds			#  address
509		popl %es			#  data
510		leal 0x44(%esp,1),%esi		# Base of frame
511		movl %esp,MEM_ESPR-0x04		# Save kernel stack pointer
512		movl -0x14(%esi),%eax		# Get Int no
513		cmpl $-1,%eax			# Hardware interrupt?
514		jne intusr.1			# Yes
515/*
516 * v86 calls save the btx_v86 pointer on the real mode stack and read
517 * the address and flags from the btx_v86 structure.  For interrupt
518 * handler invocations (VM86 INTx requests), disable interrupts,
519 * tracing, and alignment checking while the handler runs.
520 */
521		movl $MEM_USR,%ebx		# User base
522		movl %ebx,%edx			#  address
523		addl -0x4(%esi),%ebx		# User ESP
524		movl (%ebx),%ebp		# btx_v86 pointer
525		addl %ebp,%edx			# Flatten btx_v86 ptr
526		movl %edx,MEM_ESPR-0x08		# Save btx_v86 ptr
527		movl V86_ADDR(%edx),%eax	# Get int no/address
528		movl V86_CTL(%edx),%edx		# Get control flags
529		movl -0x08(%esi),%ebx		# Save user flags in %ebx
530		testl $V86F_ADDR,%edx		# Segment:offset?
531		jnz intusr.4			# Yes
532		andl $~(PSL_I|PSL_T|PSL_AC),%ebx # Disable interrupts, tracing,
533						#  and alignment checking for
534						#  interrupt handler
535		jmp intusr.3			# Skip hardware interrupt
536/*
537 * Hardware interrupts store a NULL btx_v86 pointer and use the
538 * address (interrupt number) from the stack with empty flags.  Also,
539 * push a dummy frame of zeros onto the stack for all the general
540 * purpose and segment registers and clear %eflags.  This gives the
541 * hardware interrupt handler a clean slate.
542 */
543intusr.1:	xorl %edx,%edx			# Control flags
544		movl %edx,MEM_ESPR-0x08		# NULL btx_v86 ptr
545		movl $12,%ecx			# Frame is 12 dwords
546intusr.2:	pushl $0x0			# Fill frame
547		loop intusr.2			#  with zeros
548		movl $PSL_RESERVED_DEFAULT,%ebx # Set clean %eflags
549/*
550 * Look up real mode IDT entry for hardware interrupts and VM86 INTx
551 * requests.
552 */
553intusr.3:	shll $0x2,%eax			# Scale
554		movl (%eax),%eax		# Load int vector
555		jmp intusr.5			# Skip CALLF test
556/*
557 * Panic if V86F_CALLF isn't set with V86F_ADDR.
558 */
559intusr.4:	testl $V86F_CALLF,%edx		# Far call?
560		jnz intusr.5			# Ok
561		movl %edx,0x30(%esp,1)		# Place VM86 flags in int no
562		movl $badvm86,%esi		# Display bad
563		call putstr			#  VM86 call
564		popl %es			# Restore
565		popl %ds			#  seg
566		popl %fs			#  regs
567		popl %gs
568		popal				# Restore gp regs
569		jmp ex_noc			# Panic
570/*
571 * %eax now holds the segment:offset of the function.
572 * %ebx now holds the %eflags to pass to real mode.
573 * %edx now holds the V86F_* flags.
574 */
575intusr.5:	movw %bx,MEM_ESPR-0x12		# Pass user flags to real mode
576						#  target
577/*
578 * If this is a v86 call, copy the seg regs out of the btx_v86 structure.
579 */
580		movl MEM_ESPR-0x08,%ecx		# Get btx_v86 ptr
581		jecxz intusr.6			# Skip for hardware ints
582		leal -0x44(%esi),%edi		# %edi => kernel stack seg regs
583		pushl %esi			# Save
584		leal V86_ES(%ecx),%esi		# %esi => btx_v86 seg regs
585		movl $4,%ecx			# Copy seg regs
586		rep				#  from btx_v86
587		movsl				#  to kernel stack
588		popl %esi			# Restore
589intusr.6:	movl -0x08(%esi),%ebx		# Copy user flags to real
590		movl %ebx,MEM_ESPR-0x0c		#  mode return trampoline
591		movl $rret_tramp,%ebx		# Set return trampoline
592		movl %ebx,MEM_ESPR-0x10		#  CS:IP
593		movl %eax,MEM_ESPR-0x16		# Real mode target CS:IP
594		ljmpw $SEL_RCODE,$intusr.7	# Change to 16-bit segment
595		.code16
596intusr.7:	movl %cr0,%eax			# Leave
597		dec %al				#  protected
598		movl %eax,%cr0			#  mode
599		ljmpw $0x0,$intusr.8
600intusr.8:	xorw %ax,%ax			# Reset %ds
601		movw %ax,%ds			#  and
602		movw %ax,%ss			#  %ss
603		lidt ivtdesc	 		# Set IVT
604		popl %es			# Restore
605		popl %ds			#  seg
606		popl %fs			#  regs
607		popl %gs
608		popal				# Restore gp regs
609		movw $MEM_ESPR-0x16,%sp		# Switch to real mode stack
610		iret				# Call target routine
611/*
612 * For the return to real mode we setup a stack frame like this on the real
613 * mode stack.  Note that callf calls won't pop off the flags, but we just
614 * ignore that by repositioning %sp to be just above the btx_v86 pointer
615 * so it is aligned.  The stack is relative to MEM_ESPR.
616 *
617 * -0x04	kernel %esp
618 * -0x08	btx_v86
619 * -0x0c	%eax
620 * -0x10	%ecx
621 * -0x14	%edx
622 * -0x18	%ebx
623 * -0x1c	%esp
624 * -0x20	%ebp
625 * -0x24	%esi
626 * -0x28	%edi
627 * -0x2c	%gs
628 * -0x30	%fs
629 * -0x34	%ds
630 * -0x38	%es
631 * -0x3c	%eflags
632 */
633rret_tramp:	movw $MEM_ESPR-0x08,%sp		# Reset stack pointer
634		pushal				# Save gp regs
635		pushl %gs			# Save
636		pushl %fs			#  seg
637		pushl %ds			#  regs
638		pushl %es
639		pushfl				# Save %eflags
640		cli				# Disable interrupts
641		std				# String ops dec
642		xorw %ax,%ax			# Reset seg
643		movw %ax,%ds			#  regs
644		movw %ax,%es			#  (%ss is already 0)
645		lidt idtdesc	 		# Set IDT
646		lgdt gdtdesc	 		# Set GDT
647		mov %cr0,%eax			# Switch to protected
648		inc %ax				#  mode
649		mov %eax,%cr0			#
650		ljmp $SEL_SCODE,$rret_tramp.1	# To 32-bit code
651		.code32
652rret_tramp.1:	xorl %ecx,%ecx			# Zero
653		movb $SEL_SDATA,%cl		# Setup
654		movw %cx,%ss			#  32-bit
655		movw %cx,%ds			#  seg
656		movw %cx,%es			#  regs
657		movl MEM_ESPR-0x04,%esp		# Switch to kernel stack
658		leal 0x44(%esp,1),%esi		# Base of frame
659		andb $~0x2,tss_desc+0x5		# Clear TSS busy
660		movb $SEL_TSS,%cl		# Set task
661		ltr %cx				#  register
662/*
663 * Now we are back in protected mode.  The kernel stack frame set up
664 * before entering real mode is still intact. For hardware interrupts,
665 * leave the frame unchanged.
666 */
667		cmpl $0,MEM_ESPR-0x08		# Leave saved regs unchanged
668		jz rret_tramp.3			#  for hardware ints
669/*
670 * For V86 calls, copy the registers off of the real mode stack onto
671 * the kernel stack as we want their updated values.  Also, initialize
672 * the segment registers on the kernel stack.
673 *
674 * Note that the %esp in the kernel stack after this is garbage, but popa
675 * ignores it, so we don't have to fix it up.
676 */
677		leal -0x18(%esi),%edi		# Kernel stack GP regs
678		pushl %esi			# Save
679		movl $MEM_ESPR-0x0c,%esi	# Real mode stack GP regs
680		movl $8,%ecx			# Copy GP regs from
681		rep				#  real mode stack
682		movsl				#  to kernel stack
683		movl $SEL_UDATA,%eax		# Selector for data seg regs
684		movl $4,%ecx			# Initialize %ds,
685		rep				#  %es, %fs, and
686		stosl				#  %gs
687/*
688 * For V86 calls, copy the saved seg regs on the real mode stack back
689 * over to the btx_v86 structure.  Also, conditionally update the
690 * saved eflags on the kernel stack based on the flags from the user.
691 */
692		movl MEM_ESPR-0x08,%ecx		# Get btx_v86 ptr
693		leal V86_GS(%ecx),%edi		# %edi => btx_v86 seg regs
694		leal MEM_ESPR-0x2c,%esi		# %esi => real mode seg regs
695		xchgl %ecx,%edx			# Save btx_v86 ptr
696		movl $4,%ecx			# Copy seg regs
697		rep				#  from real mode stack
698		movsl				#  to btx_v86
699		popl %esi			# Restore
700		movl V86_CTL(%edx),%edx		# Read V86 control flags
701		testl $V86F_FLAGS,%edx		# User wants flags?
702		jz rret_tramp.3			# No
703		movl MEM_ESPR-0x3c,%eax		# Read real mode flags
704		movw %ax,-0x08(%esi)		# Update user flags (low 16)
705/*
706 * Return to the user task
707 */
708rret_tramp.3:	popl %es			# Restore
709		popl %ds			#  seg
710		popl %fs			#  regs
711		popl %gs
712		popal				# Restore gp regs
713		addl $4,%esp			# Discard int no
714		iret				# Return to user mode
715
716/*
717 * System Call.
718 */
719intx30: 	cmpl $SYS_EXEC,%eax		# Exec system call?
720		jne intx30.1			# No
721		pushl %ss			# Set up
722		popl %es			#  all
723		pushl %es			#  segment
724		popl %ds			#  registers
725		pushl %ds			#  for the
726		popl %fs			#  program
727		pushl %fs			#  we're
728		popl %gs			#  invoking
729		movl $MEM_USR,%eax		# User base address
730		addl 0xc(%esp,1),%eax		# Change to user
731		leal 0x4(%eax),%esp		#  stack
732		popl %eax			# Call
733		call *%eax			#  program
734intx30.1:	orb $0x1,%ss:btx_hdr+0x7	# Flag reboot
735		jmp exit			# Exit
736/*
737 * Dump structure [EBX] to [EDI], using format string [ESI].
738 */
739dump.0: 	stosb				# Save char
740dump:		lodsb				# Load char
741		testb %al,%al			# End of string?
742		jz dump.10			# Yes
743		testb $0x80,%al 		# Control?
744		jz dump.0			# No
745		movb %al,%ch			# Save control
746		movb $'=',%al			# Append
747		stosb				#  '='
748		lodsb				# Get offset
749		pushl %esi			# Save
750		movsbl %al,%esi 		# To
751		addl %ebx,%esi			#  pointer
752		testb $DMP_X16,%ch		# Dump word?
753		jz dump.1			# No
754		lodsw				# Get and
755		call hex16			#  dump it
756dump.1: 	testb $DMP_X32,%ch		# Dump long?
757		jz dump.2			# No
758		lodsl				# Get and
759		call hex32			#  dump it
760dump.2: 	testb $DMP_MEM,%ch		# Dump memory?
761		jz dump.8			# No
762		pushl %ds			# Save
763		testl $PSL_VM,0x50(%ebx)	# V86 mode?
764		jnz dump.3			# Yes
765		verr 0x4(%esi)	 		# Readable selector?
766		jnz dump.3			# No
767		ldsl (%esi),%esi		# Load pointer
768		jmp dump.4			# Join common code
769dump.3: 	lodsl				# Set offset
770		xchgl %eax,%edx 		# Save
771		lodsl				# Get segment
772		shll $0x4,%eax			#  * 0x10
773		addl %edx,%eax			#  + offset
774		xchgl %eax,%esi 		# Set pointer
775dump.4: 	movb $2,%dl			# Num lines
776dump.4a:	movb $0x10,%cl			# Bytes to dump
777dump.5: 	lodsb				# Get byte and
778		call hex8			#  dump it
779		decb %cl			# Keep count
780		jz dump.6a			# If done
781		movb $'-',%al			# Separator
782		cmpb $0x8,%cl			# Half way?
783		je dump.6			# Yes
784		movb $' ',%al			# Use space
785dump.6: 	stosb				# Save separator
786		jmp dump.5			# Continue
787dump.6a:	decb %dl			# Keep count
788		jz dump.7			# If done
789		movb $0xa,%al			# Line feed
790		stosb				# Save one
791		movb $7,%cl			# Leading
792		movb $' ',%al			#  spaces
793dump.6b:	stosb				# Dump
794		decb %cl			#  spaces
795		jnz dump.6b
796		jmp dump.4a			# Next line
797dump.7: 	popl %ds			# Restore
798dump.8: 	popl %esi			# Restore
799		movb $0xa,%al			# Line feed
800		testb $DMP_EOL,%ch		# End of line?
801		jnz dump.9			# Yes
802		movb $' ',%al			# Use spaces
803		stosb				# Save one
804dump.9: 	jmp dump.0			# Continue
805dump.10:	stosb				# Terminate string
806		ret				# To caller
807/*
808 * Convert EAX, AX, or AL to hex, saving the result to [EDI].
809 */
810hex32:		pushl %eax			# Save
811		shrl $0x10,%eax 		# Do upper
812		call hex16			#  16
813		popl %eax			# Restore
814hex16:		call hex16.1			# Do upper 8
815hex16.1:	xchgb %ah,%al			# Save/restore
816hex8:		pushl %eax			# Save
817		shrb $0x4,%al			# Do upper
818		call hex8.1			#  4
819		popl %eax			# Restore
820hex8.1: 	andb $0xf,%al			# Get lower 4
821		cmpb $0xa,%al			# Convert
822		sbbb $0x69,%al			#  to hex
823		das				#  digit
824		orb $0x20,%al			# To lower case
825		stosb				# Save char
826		ret				# (Recursive)
827/*
828 * Output zero-terminated string [ESI] to the console.
829 */
830putstr.0:	call putchr			# Output char
831putstr: 	lodsb				# Load char
832		testb %al,%al			# End of string?
833		jnz putstr.0			# No
834		ret				# To caller
835#ifdef BTX_SERIAL
836		.set SIO_PRT,SIOPRT		# Base port
837		.set SIO_FMT,SIOFMT		# 8N1
838		.set SIO_DIV,(115200/SIOSPD)	# 115200 / SPD
839
840/*
841 * void sio_init(void)
842 */
843sio_init:	movw $SIO_PRT+0x3,%dx		# Data format reg
844		movb $SIO_FMT|0x80,%al		# Set format
845		outb %al,(%dx)			#  and DLAB
846		pushl %edx			# Save
847		subb $0x3,%dl			# Divisor latch reg
848		movw $SIO_DIV,%ax		# Set
849		outw %ax,(%dx)			#  BPS
850		popl %edx			# Restore
851		movb $SIO_FMT,%al		# Clear
852		outb %al,(%dx)			#  DLAB
853		incl %edx			# Modem control reg
854		movb $0x3,%al			# Set RTS,
855		outb %al,(%dx)			#  DTR
856		incl %edx			# Line status reg
857
858/*
859 * void sio_flush(void)
860 */
861sio_flush.0:	call sio_getc.1 		# Get character
862sio_flush:	call sio_ischar 		# Check for character
863		jnz sio_flush.0 		# Till none
864		ret				# To caller
865
866/*
867 * void sio_putc(int c)
868 */
869sio_putc:	movw $SIO_PRT+0x5,%dx		# Line status reg
870		xor %ecx,%ecx			# Timeout
871		movb $0x40,%ch			#  counter
872sio_putc.1:	inb (%dx),%al			# Transmitter
873		testb $0x20,%al 		#  buffer empty?
874		loopz sio_putc.1		# No
875		jz sio_putc.2			# If timeout
876		movb 0x4(%esp,1),%al		# Get character
877		subb $0x5,%dl			# Transmitter hold reg
878		outb %al,(%dx)			# Write character
879sio_putc.2:	ret $0x4			# To caller
880
881/*
882 * int sio_getc(void)
883 */
884sio_getc:	call sio_ischar 		# Character available?
885		jz sio_getc			# No
886sio_getc.1:	subb $0x5,%dl			# Receiver buffer reg
887		inb (%dx),%al			# Read character
888		ret				# To caller
889
890/*
891 * int sio_ischar(void)
892 */
893sio_ischar:	movw $SIO_PRT+0x5,%dx		# Line status register
894		xorl %eax,%eax			# Zero
895		inb (%dx),%al			# Received data
896		andb $0x1,%al			#  ready?
897		ret				# To caller
898
899/*
900 * Output character AL to the serial console.
901 */
902putchr: 	pusha				# Save
903		cmpb $10, %al			# is it a newline?
904		jne putchr.1			#  no?, then leave
905		push $13			# output a carriage
906		call sio_putc			#  return first
907		movb $10, %al			# restore %al
908putchr.1:	pushl %eax			# Push the character
909						#  onto the stack
910		call sio_putc			# Output the character
911		popa				# Restore
912		ret				# To caller
913#else
914/*
915 * Output character AL to the console.
916 */
917putchr: 	pusha				# Save
918		xorl %ecx,%ecx			# Zero for loops
919		movb $SCR_MAT,%ah		# Mode/attribute
920		movl $BDA_POS,%ebx		# BDA pointer
921		movw (%ebx),%dx 		# Cursor position
922		movl $0xa0000,%edi
923putchr.1:	cmpb $0xa,%al			# New line?
924		je putchr.2			# Yes
925		movw %dx,%cx
926		movb %al,(%edi,%ecx,1)		# Write char
927		addl $0x2000,%ecx
928		movb %ah,(%edi,%ecx,1)		# Write attr
929		addw $0x02,%dx
930		jmp putchr.3
931putchr.2:	movw %dx,%ax
932		movb $SCR_COL*2,%dl
933		div %dl
934		incb %al
935		mul %dl
936		movw %ax,%dx
937putchr.3:	cmpw $SCR_ROW*SCR_COL*2,%dx
938		jb putchr.4			# No
939		leal 2*SCR_COL(%edi),%esi	# New top line
940		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
941		rep				# Scroll
942		movsl				#  screen
943		movb $0x20,%al			# Space
944		xorb %ah,%ah
945		movb $SCR_COL,%cl		# Columns to clear
946		rep				# Clear
947		stosw				#  line
948		movw $(SCR_ROW-1)*SCR_COL*2,%dx
949putchr.4:	movw %dx,(%ebx) 		# Update position
950		popa				# Restore
951		ret				# To caller
952#endif
953
954		.code16
955/*
956 * Real Mode Hardware interrupt jump table.
957 */
958intr20: 	push $0x8			# Int 0x20: IRQ0
959		jmp int_hwr			# V86 int 0x8
960		push $0x9			# Int 0x21: IRQ1
961		jmp int_hwr			# V86 int 0x9
962		push $0xa			# Int 0x22: IRQ2
963		jmp int_hwr			# V86 int 0xa
964		push $0xb			# Int 0x23: IRQ3
965		jmp int_hwr			# V86 int 0xb
966		push $0xc			# Int 0x24: IRQ4
967		jmp int_hwr			# V86 int 0xc
968		push $0xd			# Int 0x25: IRQ5
969		jmp int_hwr			# V86 int 0xd
970		push $0xe			# Int 0x26: IRQ6
971		jmp int_hwr			# V86 int 0xe
972		push $0xf			# Int 0x27: IRQ7
973		jmp int_hwr			# V86 int 0xf
974		push $0x10			# Int 0x28: IRQ8
975		jmp int_hwr			# V86 int 0x10
976		push $0x11			# Int 0x29: IRQ9
977		jmp int_hwr			# V86 int 0x11
978		push $0x12			# Int 0x2a: IRQ10
979		jmp int_hwr			# V86 int 0x12
980		push $0x13			# Int 0x2b: IRQ11
981		jmp int_hwr			# V86 int 0x13
982		push $0x14			# Int 0x2c: IRQ12
983		jmp int_hwr			# V86 int 0x14
984		push $0x15			# Int 0x2d: IRQ13
985		jmp int_hwr			# V86 int 0x15
986		push $0x16			# Int 0x2e: IRQ14
987		jmp int_hwr			# V86 int 0x16
988		push $0x17			# Int 0x2f: IRQ15
989		jmp int_hwr			# V86 int 0x17
990/*
991 * Reflect hardware interrupts in real mode.
992 */
993int_hwr: 	push %ax			# Save
994		push %ds			# Save
995		push %bp			# Save
996		mov %sp,%bp			# Address stack frame
997		xchg %bx,6(%bp)			# Swap BX, int no
998		xor %ax,%ax			# Set %ds:%bx to
999		shl $2,%bx			#  point to
1000		mov %ax,%ds			#  IDT entry
1001		mov (%bx),%ax			# Load IP
1002		mov 2(%bx),%bx			# Load CS
1003		xchg %ax,4(%bp)			# Swap saved %ax,%bx with
1004		xchg %bx,6(%bp)			#  CS:IP of handler
1005		pop %bp				# Restore
1006		pop %ds				# Restore
1007		lret				# Jump to handler
1008
1009		.p2align 4
1010/*
1011 * Global descriptor table.
1012 */
1013gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
1014		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
1015		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
1016		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
1017		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
1018		.word 0xffff,MEM_USR,0xfa00,0xcf# SEL_UCODE
1019		.word 0xffff,MEM_USR,0xf200,0xcf# SEL_UDATA
1020tss_desc:	.word _TSSLM,MEM_TSS,0x8900,0x0 # SEL_TSS
1021gdt.1:
1022/*
1023 * Pseudo-descriptors.
1024 */
1025gdtdesc:	.word gdt.1-gdt-1,gdt,0x0	# GDT
1026idtdesc:	.word _IDTLM,MEM_IDT,0x0	# IDT
1027ivtdesc:	.word 0x400-0x0-1,0x0,0x0	# IVT
1028/*
1029 * IDT construction control string.
1030 */
1031idtctl: 	.byte 0x10,  0x8e		# Int 0x0-0xf
1032		.word 0x7dfb,intx00		#  (exceptions)
1033		.byte 0x10,  0x8e		# Int 0x10
1034		.word 0x1,   intx10		#  (exception)
1035		.byte 0x10,  0x8e		# Int 0x20-0x2f
1036		.word 0xffff,intx20		#  (hardware)
1037		.byte 0x1,   0xee		# int 0x30
1038		.word 0x1,   intx30		#  (system call)
1039		.byte 0x2,   0xee		# Int 0x31-0x32
1040		.word 0x1,   intx31		#  (V86, null)
1041		.byte 0x0			# End of string
1042/*
1043 * Dump format string.
1044 */
1045dmpfmt: 	.byte '\n'			# "\n"
1046		.ascii "int"			# "int="
1047		.byte 0x80|DMP_X32,	   0x40 # "00000000  "
1048		.ascii "err"			# "err="
1049		.byte 0x80|DMP_X32,	   0x44 # "00000000  "
1050		.ascii "efl"			# "efl="
1051		.byte 0x80|DMP_X32,	   0x50 # "00000000  "
1052		.ascii "eip"			# "eip="
1053		.byte 0x80|DMP_X32|DMP_EOL,0x48 # "00000000\n"
1054		.ascii "eax"			# "eax="
1055		.byte 0x80|DMP_X32,	   0x34 # "00000000  "
1056		.ascii "ebx"			# "ebx="
1057		.byte 0x80|DMP_X32,	   0x28 # "00000000  "
1058		.ascii "ecx"			# "ecx="
1059		.byte 0x80|DMP_X32,	   0x30 # "00000000  "
1060		.ascii "edx"			# "edx="
1061		.byte 0x80|DMP_X32|DMP_EOL,0x2c # "00000000\n"
1062		.ascii "esi"			# "esi="
1063		.byte 0x80|DMP_X32,	   0x1c # "00000000  "
1064		.ascii "edi"			# "edi="
1065		.byte 0x80|DMP_X32,	   0x18 # "00000000  "
1066		.ascii "ebp"			# "ebp="
1067		.byte 0x80|DMP_X32,	   0x20 # "00000000  "
1068		.ascii "esp"			# "esp="
1069		.byte 0x80|DMP_X32|DMP_EOL,0x0	# "00000000\n"
1070		.ascii "cs"			# "cs="
1071		.byte 0x80|DMP_X16,	   0x4c # "0000  "
1072		.ascii "ds"			# "ds="
1073		.byte 0x80|DMP_X16,	   0xc	# "0000  "
1074		.ascii "es"			# "es="
1075		.byte 0x80|DMP_X16,	   0x8	# "0000  "
1076		.ascii "  "			# "  "
1077		.ascii "fs"			# "fs="
1078		.byte 0x80|DMP_X16,	   0x10 # "0000  "
1079		.ascii "gs"			# "gs="
1080		.byte 0x80|DMP_X16,	   0x14 # "0000  "
1081		.ascii "ss"			# "ss="
1082		.byte 0x80|DMP_X16|DMP_EOL,0x4	# "0000\n"
1083		.ascii "cs:eip" 		# "cs:eip="
1084		.byte 0x80|DMP_MEM|DMP_EOL,0x48 # "00 00 ... 00 00\n"
1085		.ascii "ss:esp" 		# "ss:esp="
1086		.byte 0x80|DMP_MEM|DMP_EOL,0x0	# "00 00 ... 00 00\n"
1087		.asciz "BTX halted\n"		# End
1088/*
1089 * Bad VM86 call panic
1090 */
1091badvm86:	.asciz "Invalid VM86 Request\n"
1092
1093/*
1094 * End of BTX memory.
1095 */
1096		.p2align 4
1097break:
1098