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