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