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