1128709Sru/*
2128709Sru * Copyright (c) 1998 Robert Nordier
3128709Sru * All rights reserved.
4128709Sru *
5128709Sru * Redistribution and use in source and binary forms are freely
6128709Sru * permitted provided that the above copyright notice and this
7128709Sru * paragraph and the following disclaimer are duplicated in all
8128709Sru * such forms.
9128709Sru *
10128709Sru * This software is provided "AS IS" and without any express or
11128709Sru * implied warranties, including, without limitation, the implied
12128709Sru * warranties of merchantability and fitness for a particular
13128709Sru * purpose.
14128709Sru *
15128709Sru * $FreeBSD$
16128709Sru */
1739088Srnordier
18235154Savg#include <bootargs.h>
19235154Savg
20128709Sru/*
21128709Sru * Memory layout.
22128709Sru */
23129240Sru		.set MEM_BTX,0x1000		# Start of BTX memory
24129240Sru		.set MEM_ESP0,0x1800		# Supervisor stack
25129240Sru		.set MEM_BUF,0x1800		# Scratch buffer
26177039Sjhb		.set MEM_ESPR,0x5e00		# Real mode stack
27177039Sjhb		.set MEM_IDT,0x5e00		# IDT
28177039Sjhb		.set MEM_TSS,0x5f98		# TSS
29177039Sjhb		.set MEM_MAP,0x6000		# I/O bit map
30177039Sjhb		.set MEM_TSS_END,0x7fff		# End of TSS
31129240Sru		.set MEM_ORG,0x9000		# BTX code
32129240Sru		.set MEM_USR,0xa000		# Start of user memory
33128709Sru/*
34128709Sru * Paging control.
35128709Sru */
36129240Sru		.set PAG_SIZ,0x1000		# Page size
37129240Sru		.set PAG_CNT,0x1000		# Pages to map
38128709Sru/*
39181433Sjhb * Fields in %eflags.
40181433Sjhb */
41189017Sjhb		.set PSL_RESERVED_DEFAULT,0x00000002
42181433Sjhb		.set PSL_T,0x00000100		# Trap flag
43181433Sjhb		.set PSL_I,0x00000200		# Interrupt enable flag
44256562Sjhb		.set PSL_D,0x00000400		# String instruction direction
45256562Sjhb		.set PSL_NT,0x00004000		# Nested task flag
46181433Sjhb		.set PSL_VM,0x00020000		# Virtual 8086 mode flag
47181433Sjhb		.set PSL_AC,0x00040000		# Alignment check flag
48181433Sjhb/*
49128709Sru * Segment selectors.
50128709Sru */
51129240Sru		.set SEL_SCODE,0x8		# Supervisor code
52129240Sru		.set SEL_SDATA,0x10		# Supervisor data
53129240Sru		.set SEL_RCODE,0x18		# Real mode code
54129240Sru		.set SEL_RDATA,0x20		# Real mode data
55129240Sru		.set SEL_UCODE,0x28|3		# User code
56129240Sru		.set SEL_UDATA,0x30|3		# User data
57129240Sru		.set SEL_TSS,0x38		# TSS
58128709Sru/*
59128709Sru * Task state segment fields.
60128709Sru */
61129240Sru		.set TSS_ESP0,0x4		# PL 0 ESP
62129240Sru		.set TSS_SS0,0x8		# PL 0 SS
63129240Sru		.set TSS_MAP,0x66		# I/O bit map base
64128709Sru/*
65128709Sru * System calls.
66128709Sru */
67129240Sru		.set SYS_EXIT,0x0		# Exit
68129240Sru		.set SYS_EXEC,0x1		# Exec
69128709Sru/*
70177039Sjhb * Fields in V86 interface structure.
71128709Sru */
72177039Sjhb		.set V86_CTL,0x0		# Control flags
73177039Sjhb		.set V86_ADDR,0x4		# Int number/address
74177039Sjhb		.set V86_ES,0x8			# V86 ES
75177039Sjhb		.set V86_DS,0xc			# V86 DS
76177039Sjhb		.set V86_FS,0x10		# V86 FS
77177039Sjhb		.set V86_GS,0x14		# V86 GS
78128709Sru/*
79177039Sjhb * V86 control flags.
80177039Sjhb */
81177039Sjhb		.set V86F_ADDR,0x10000		# Segment:offset address
82177039Sjhb		.set V86F_CALLF,0x20000		# Emulate far call
83177039Sjhb		.set V86F_FLAGS,0x40000		# Return flags
84177039Sjhb/*
85128709Sru * Dump format control bytes.
86128709Sru */
87129240Sru		.set DMP_X16,0x1		# Word
88129240Sru		.set DMP_X32,0x2		# Long
89129240Sru		.set DMP_MEM,0x4		# Memory
90129240Sru		.set DMP_EOL,0x8		# End of line
91128709Sru/*
92128709Sru * Screen defaults and assumptions.
93128709Sru */
94129240Sru		.set SCR_MAT,0x7		# Mode/attribute
95129240Sru		.set SCR_COL,0x50		# Columns per row
96129240Sru		.set SCR_ROW,0x19		# Rows per screen
97128709Sru/*
98128709Sru * BIOS Data Area locations.
99128709Sru */
100129240Sru		.set BDA_MEM,0x413		# Free memory
101129240Sru		.set BDA_SCR,0x449		# Video mode
102129240Sru		.set BDA_POS,0x450		# Cursor position
103129240Sru		.set BDA_BOOT,0x472		# Boot howto flag
104128709Sru/*
105128709Sru * Derivations, for brevity.
106128709Sru */
107129240Sru		.set _ESP0H,MEM_ESP0>>0x8	# Byte 1 of ESP0
108129240Sru		.set _TSSIO,MEM_MAP-MEM_TSS	# TSS I/O base
109176631Sjhb		.set _TSSLM,MEM_TSS_END-MEM_TSS	# TSS limit
110129240Sru		.set _IDTLM,MEM_TSS-MEM_IDT-1	# IDT limit
111128709Sru/*
112128709Sru * Code segment.
113128709Sru */
11439088Srnordier		.globl start
11560821Sjhb		.code16
116129240Srustart:						# Start of code
117128709Sru/*
118128709Sru * BTX header.
119128709Sru */
120129240Srubtx_hdr:	.byte 0xeb			# Machine ID
121129240Sru		.byte 0xe			# Header size
122129240Sru		.ascii "BTX"			# Magic
123129240Sru		.byte 0x1			# Major version
124177039Sjhb		.byte 0x2			# Minor version
125129240Sru		.byte BTX_FLAGS			# Flags
126129240Sru		.word PAG_CNT-MEM_ORG>>0xc	# Paging control
127129240Sru		.word break-start		# Text size
128129240Sru		.long 0x0			# Entry address
129128709Sru/*
130128709Sru * Initialization routine.
131128709Sru */
132129240Sruinit:		cli				# Disable interrupts
133129240Sru		xor %ax,%ax			# Zero/segment
134129240Sru		mov %ax,%ss			# Set up
135129240Sru		mov $MEM_ESP0,%sp		#  stack
136129240Sru		mov %ax,%es			# Address
137129240Sru		mov %ax,%ds			#  data
138129240Sru		pushl $0x2			# Clear
139129240Sru		popfl				#  flags
140128709Sru/*
141128709Sru * Initialize memory.
142128709Sru */
143129240Sru		mov $MEM_IDT,%di		# Memory to initialize
144129240Sru		mov $(MEM_ORG-MEM_IDT)/2,%cx	# Words to zero
145129240Sru		rep				# Zero-fill
146129240Sru		stosw				#  memory
147128709Sru/*
148177039Sjhb * Update real mode IDT for reflecting hardware interrupts.
149177039Sjhb */
150177039Sjhb		mov $intr20,%bx			# Address first handler
151177039Sjhb		mov $0x10,%cx			# Number of handlers
152177039Sjhb		mov $0x20*4,%di			# First real mode IDT entry
153177039Sjhbinit.0:		mov %bx,(%di)			# Store IP
154177039Sjhb		inc %di				# Address next
155177039Sjhb		inc %di				#  entry
156177039Sjhb		stosw				# Store CS
157177039Sjhb		add $4,%bx			# Next handler
158177039Sjhb		loop init.0			# Next IRQ
159177039Sjhb/*
160128709Sru * Create IDT.
161128709Sru */
162177039Sjhb		mov $MEM_IDT,%di
163129240Sru		mov $idtctl,%si			# Control string
164129240Sruinit.1: 	lodsb				# Get entry
165129240Sru		cbw				#  count
166129240Sru		xchg %ax,%cx			#  as word
167129240Sru		jcxz init.4			# If done
168129240Sru		lodsb				# Get segment
169129240Sru		xchg %ax,%dx	 		#  P:DPL:type
170129240Sru		lodsw				# Get control
171129240Sru		xchg %ax,%bx			#  set
172129240Sru		lodsw				# Get handler offset
173129240Sru		mov $SEL_SCODE,%dh		# Segment selector
174129240Sruinit.2: 	shr %bx				# Handle this int?
175129240Sru		jnc init.3			# No
176129240Sru		mov %ax,(%di)			# Set handler offset
177129240Sru		mov %dh,0x2(%di)		#  and selector
178129240Sru		mov %dl,0x5(%di)		# Set P:DPL:type
179129240Sru		add $0x4,%ax			# Next handler
180129240Sruinit.3: 	lea 0x8(%di),%di		# Next entry
181129240Sru		loop init.2			# Till set done
182129240Sru		jmp init.1			# Continue
183128709Sru/*
184128709Sru * Initialize TSS.
185128709Sru */
186129240Sruinit.4: 	movb $_ESP0H,TSS_ESP0+1(%di)	# Set ESP0
187129240Sru		movb $SEL_SDATA,TSS_SS0(%di)	# Set SS0
188129240Sru		movb $_TSSIO,TSS_MAP(%di)	# Set I/O bit map base
189128709Sru/*
190128709Sru * Bring up the system.
191128709Sru */
192129240Sru		mov $0x2820,%bx			# Set protected mode
193129240Sru		callw setpic			#  IRQ offsets
194129240Sru		lidt idtdesc	 		# Set IDT
195129240Sru		lgdt gdtdesc	 		# Set GDT
196129240Sru		mov %cr0,%eax			# Switch to protected
197162737Sjhb		inc %ax				#  mode
198129240Sru		mov %eax,%cr0			#
199129240Sru		ljmp $SEL_SCODE,$init.8		# To 32-bit code
20060821Sjhb		.code32
201129240Sruinit.8: 	xorl %ecx,%ecx			# Zero
202129240Sru		movb $SEL_SDATA,%cl		# To 32-bit
203129240Sru		movw %cx,%ss			#  stack
204128709Sru/*
205128709Sru * Launch user task.
206128709Sru */
207129240Sru		movb $SEL_TSS,%cl		# Set task
208129240Sru		ltr %cx				#  register
209129240Sru		movl $MEM_USR,%edx		# User base address
210129240Sru		movzwl %ss:BDA_MEM,%eax 	# Get free memory
211129240Sru		shll $0xa,%eax			# To bytes
212235154Savg		subl $ARGSPACE,%eax		# Less arg space
213129240Sru		subl %edx,%eax			# Less base
214129240Sru		movb $SEL_UDATA,%cl		# User data selector
215129240Sru		pushl %ecx			# Set SS
216129240Sru		pushl %eax			# Set ESP
217129240Sru		push $0x202			# Set flags (IF set)
218129240Sru		push $SEL_UCODE			# Set CS
219129240Sru		pushl btx_hdr+0xc		# Set EIP
220129240Sru		pushl %ecx			# Set GS
221129240Sru		pushl %ecx			# Set FS
222129240Sru		pushl %ecx			# Set DS
223129240Sru		pushl %ecx			# Set ES
224129240Sru		pushl %edx			# Set EAX
225129240Sru		movb $0x7,%cl			# Set remaining
226129240Sruinit.9:		push $0x0			#  general
227129240Sru		loop init.9			#  registers
228125693Sru#ifdef BTX_SERIAL
229129240Sru		call sio_init			# setup the serial console
230125693Sru#endif
231129240Sru		popa				#  and initialize
232129240Sru		popl %es			# Initialize
233129240Sru		popl %ds			#  user
234129240Sru		popl %fs			#  segment
235129240Sru		popl %gs			#  registers
236129240Sru		iret				# To user mode
237128709Sru/*
238128709Sru * Exit routine.
239128709Sru */
240129240Sruexit:		cli				# Disable interrupts
241129240Sru		movl $MEM_ESP0,%esp		# Clear stack
242128709Sru/*
243128709Sru * Turn off paging.
244128709Sru */
245129240Sru		movl %cr0,%eax			# Get CR0
246129240Sru		andl $~0x80000000,%eax		# Disable
247129240Sru		movl %eax,%cr0			#  paging
248129240Sru		xorl %ecx,%ecx			# Zero
249129240Sru		movl %ecx,%cr3			# Flush TLB
250128709Sru/*
251128709Sru * Restore the GDT in case we caught a kernel trap.
252128709Sru */
253249846Sdim		lgdt %cs:gdtdesc		# Set GDT
254128709Sru/*
255128709Sru * To 16 bits.
256128709Sru */
257129240Sru		ljmpw $SEL_RCODE,$exit.1	# Reload CS
25860821Sjhb		.code16
259129240Sruexit.1: 	mov $SEL_RDATA,%cl		# 16-bit selector
260129240Sru		mov %cx,%ss			# Reload SS
261129240Sru		mov %cx,%ds			# Load
262129240Sru		mov %cx,%es			#  remaining
263129240Sru		mov %cx,%fs			#  segment
264129240Sru		mov %cx,%gs			#  registers
265128709Sru/*
266128709Sru * To real-address mode.
267128709Sru */
268129240Sru		dec %ax				# Switch to
269129240Sru		mov %eax,%cr0			#  real mode
270129240Sru		ljmp $0x0,$exit.2		# Reload CS
271129240Sruexit.2: 	xor %ax,%ax			# Real mode segment
272129240Sru		mov %ax,%ss			# Reload SS
273129240Sru		mov %ax,%ds			# Address data
274129240Sru		mov $0x7008,%bx			# Set real mode
275129240Sru		callw setpic			#  IRQ offsets
276129240Sru		lidt ivtdesc	 		# Set IVT
277128709Sru/*
278128709Sru * Reboot or await reset.
279128709Sru */
280129240Sru		sti				# Enable interrupts
281129240Sru		testb $0x1,btx_hdr+0x7		# Reboot?
282129240Sruexit.3:		jz exit.3			# No
283129240Sru		movw $0x1234, BDA_BOOT		# Do a warm boot
284129240Sru		ljmp $0xf000,$0xfff0		# reboot the machine
285128709Sru/*
286128709Sru * Set IRQ offsets by reprogramming 8259A PICs.
287128709Sru */
288129240Srusetpic: 	in $0x21,%al			# Save master
289129240Sru		push %ax			#  IMR
290129240Sru		in $0xa1,%al			# Save slave
291129240Sru		push %ax			#  IMR
292129240Sru		movb $0x11,%al			# ICW1 to
293129240Sru		outb %al,$0x20			#  master,
294129240Sru		outb %al,$0xa0			#  slave
295129240Sru		movb %bl,%al			# ICW2 to
296129240Sru		outb %al,$0x21			#  master
297129240Sru		movb %bh,%al			# ICW2 to
298129240Sru		outb %al,$0xa1			#  slave
299129240Sru		movb $0x4,%al			# ICW3 to
300129240Sru		outb %al,$0x21			#  master
301129240Sru		movb $0x2,%al			# ICW3 to
302129240Sru		outb %al,$0xa1			#  slave
303129240Sru		movb $0x1,%al			# ICW4 to
304129240Sru		outb %al,$0x21			#  master,
305129240Sru		outb %al,$0xa1			#  slave
306129240Sru		pop %ax				# Restore slave
307129240Sru		outb %al,$0xa1			#  IMR
308129240Sru		pop %ax				# Restore master
309129240Sru		outb %al,$0x21			#  IMR
310129240Sru		retw				# To caller
31160821Sjhb		.code32
312128709Sru/*
313128709Sru * Exception jump table.
314128709Sru */
315129240Sruintx00: 	push $0x0			# Int 0x0: #DE
316129240Sru		jmp ex_noc			# Divide error
317129240Sru		push $0x1			# Int 0x1: #DB
318129240Sru		jmp ex_noc			# Debug
319129240Sru		push $0x3			# Int 0x3: #BP
320129240Sru		jmp ex_noc			# Breakpoint
321129240Sru		push $0x4			# Int 0x4: #OF
322129240Sru		jmp ex_noc			# Overflow
323129240Sru		push $0x5			# Int 0x5: #BR
324129240Sru		jmp ex_noc			# BOUND range exceeded
325129240Sru		push $0x6			# Int 0x6: #UD
326129240Sru		jmp ex_noc			# Invalid opcode
327129240Sru		push $0x7			# Int 0x7: #NM
328129240Sru		jmp ex_noc			# Device not available
329129240Sru		push $0x8			# Int 0x8: #DF
330129240Sru		jmp except			# Double fault
331129240Sru		push $0xa			# Int 0xa: #TS
332129240Sru		jmp except			# Invalid TSS
333129240Sru		push $0xb			# Int 0xb: #NP
334129240Sru		jmp except			# Segment not present
335129240Sru		push $0xc			# Int 0xc: #SS
336129240Sru		jmp except			# Stack segment fault
337129240Sru		push $0xd			# Int 0xd: #GP
338177039Sjhb		jmp except			# General protection
339129240Sru		push $0xe			# Int 0xe: #PF
340129240Sru		jmp except			# Page fault
341129240Sruintx10: 	push $0x10			# Int 0x10: #MF
342129240Sru		jmp ex_noc			# Floating-point error
343128709Sru/*
344128709Sru * Save a zero error code.
345128709Sru */
346129240Sruex_noc: 	pushl (%esp,1)			# Duplicate int no
347129240Sru		movb $0x0,0x4(%esp,1)		# Fake error code
348128709Sru/*
349128709Sru * Handle exception.
350128709Sru */
351129240Sruexcept: 	cld				# String ops inc
352129240Sru		pushl %ds			# Save
353129240Sru		pushl %es			#  most
354129240Sru		pusha				#  registers
355129240Sru		pushl %gs			# Set GS
356129240Sru		pushl %fs			# Set FS
357129240Sru		pushl %ds			# Set DS
358129240Sru		pushl %es			# Set ES
359129240Sru		cmpw $SEL_SCODE,0x44(%esp,1)	# Supervisor mode?
360129240Sru		jne except.1			# No
361129240Sru		pushl %ss			# Set SS
362129240Sru		jmp except.2			# Join common code
363177039Sjhbexcept.1:	pushl 0x50(%esp,1)		# Set SS
364177039Sjhbexcept.2:	pushl 0x50(%esp,1)		# Set ESP
365177039Sjhb		push $SEL_SDATA			# Set up
366129240Sru		popl %ds			#  to
367129240Sru		pushl %ds			#  address
368129240Sru		popl %es			#  data
369129240Sru		movl %esp,%ebx			# Stack frame
370129240Sru		movl $dmpfmt,%esi		# Dump format string
371129240Sru		movl $MEM_BUF,%edi		# Buffer
372129240Sru		pushl %edi			# Dump to
373129240Sru		call dump			#  buffer
374129240Sru		popl %esi			#  and
375129240Sru		call putstr			#  display
376129240Sru		leal 0x18(%esp,1),%esp		# Discard frame
377129240Sru		popa				# Restore
378129240Sru		popl %es			#  registers
379129240Sru		popl %ds			#  saved
380129240Sru		cmpb $0x3,(%esp,1)		# Breakpoint?
381129240Sru		je except.3			# Yes
382129240Sru		cmpb $0x1,(%esp,1)		# Debug?
383129240Sru		jne except.2a			# No
384181433Sjhb		testl $PSL_T,0x10(%esp,1)	# Trap flag set?
385129240Sru		jnz except.3			# Yes
386129240Sruexcept.2a:	jmp exit			# Exit
387129240Sruexcept.3:	leal 0x8(%esp,1),%esp		# Discard err, int no
388129240Sru		iret				# From interrupt
38952173Sjhb
390128709Sru/*
391128709Sru * Reboot the machine by setting the reboot flag and exiting
392128709Sru */
393129240Srureboot:		orb $0x1,btx_hdr+0x7		# Set the reboot flag
394129240Sru		jmp exit			# Terminate BTX and reboot
39557254Sjhb
396128709Sru/*
397177039Sjhb * Protected Mode Hardware interrupt jump table.
398128709Sru */
399129240Sruintx20: 	push $0x8			# Int 0x20: IRQ0
400129240Sru		jmp int_hw			# V86 int 0x8
401129240Sru		push $0x9			# Int 0x21: IRQ1
402129240Sru		jmp int_hw			# V86 int 0x9
403129240Sru		push $0xa			# Int 0x22: IRQ2
404129240Sru		jmp int_hw			# V86 int 0xa
405129240Sru		push $0xb			# Int 0x23: IRQ3
406129240Sru		jmp int_hw			# V86 int 0xb
407129240Sru		push $0xc			# Int 0x24: IRQ4
408129240Sru		jmp int_hw			# V86 int 0xc
409129240Sru		push $0xd			# Int 0x25: IRQ5
410129240Sru		jmp int_hw			# V86 int 0xd
411129240Sru		push $0xe			# Int 0x26: IRQ6
412129240Sru		jmp int_hw			# V86 int 0xe
413129240Sru		push $0xf			# Int 0x27: IRQ7
414129240Sru		jmp int_hw			# V86 int 0xf
415129240Sru		push $0x70			# Int 0x28: IRQ8
416129240Sru		jmp int_hw			# V86 int 0x70
417129240Sru		push $0x71			# Int 0x29: IRQ9
418129240Sru		jmp int_hw			# V86 int 0x71
419129240Sru		push $0x72			# Int 0x2a: IRQ10
420129240Sru		jmp int_hw			# V86 int 0x72
421129240Sru		push $0x73			# Int 0x2b: IRQ11
422129240Sru		jmp int_hw			# V86 int 0x73
423129240Sru		push $0x74			# Int 0x2c: IRQ12
424129240Sru		jmp int_hw			# V86 int 0x74
425129240Sru		push $0x75			# Int 0x2d: IRQ13
426129240Sru		jmp int_hw			# V86 int 0x75
427129240Sru		push $0x76			# Int 0x2e: IRQ14
428129240Sru		jmp int_hw			# V86 int 0x76
429129240Sru		push $0x77			# Int 0x2f: IRQ15
430129240Sru		jmp int_hw			# V86 int 0x77
431177039Sjhb
432128709Sru/*
433177039Sjhb * Invoke real mode interrupt/function call from user mode with arguments.
434128709Sru */
435177039Sjhbintx31: 	pushl $-1			# Dummy int no for btx_v86
436128709Sru/*
437177039Sjhb * Invoke real mode interrupt/function call from protected mode.
438177039Sjhb *
439177039Sjhb * We place a trampoline on the user stack that will return to rret_tramp
440177039Sjhb * which will reenter protected mode and then finally return to the user
441177039Sjhb * client.
442177039Sjhb *
443177039Sjhb * Kernel frame %esi points to:		Real mode stack frame at MEM_ESPR:
444177039Sjhb *
445177039Sjhb * -0x00 user %ss			-0x04 kernel %esp (with full frame)
446177039Sjhb * -0x04 user %esp			-0x08 btx_v86 pointer
447177039Sjhb * -0x08 user %eflags			-0x0c flags (only used if interrupt)
448177039Sjhb * -0x0c user %cs			-0x10 real mode CS:IP return trampoline
449177039Sjhb * -0x10 user %eip			-0x12 real mode flags
450177039Sjhb * -0x14 int no				-0x16 real mode CS:IP (target)
451177039Sjhb * -0x18 %eax
452177039Sjhb * -0x1c %ecx
453177039Sjhb * -0x20 %edx
454177039Sjhb * -0x24 %ebx
455177039Sjhb * -0x28 %esp
456177039Sjhb * -0x2c %ebp
457177039Sjhb * -0x30 %esi
458177039Sjhb * -0x34 %edi
459177039Sjhb * -0x38 %gs
460177039Sjhb * -0x3c %fs
461177039Sjhb * -0x40 %ds
462177039Sjhb * -0x44 %es
463189017Sjhb * -0x48 zero %eax (hardware int only)
464189017Sjhb * -0x4c zero %ecx (hardware int only)
465189017Sjhb * -0x50 zero %edx (hardware int only)
466189017Sjhb * -0x54 zero %ebx (hardware int only)
467189017Sjhb * -0x58 zero %esp (hardware int only)
468189017Sjhb * -0x5c zero %ebp (hardware int only)
469189017Sjhb * -0x60 zero %esi (hardware int only)
470189017Sjhb * -0x64 zero %edi (hardware int only)
471189017Sjhb * -0x68 zero %gs (hardware int only)
472189017Sjhb * -0x6c zero %fs (hardware int only)
473189017Sjhb * -0x70 zero %ds (hardware int only)
474189017Sjhb * -0x74 zero %es (hardware int only)
475128709Sru */
476177039Sjhbint_hw: 	cld				# String ops inc
477177039Sjhb		pusha				# Save gp regs
478129240Sru		pushl %gs			# Save
479177039Sjhb		pushl %fs			#  seg
480177039Sjhb		pushl %ds			#  regs
481177039Sjhb		pushl %es
482129240Sru		push $SEL_SDATA			# Set up
483129240Sru		popl %ds			#  to
484129240Sru		pushl %ds			#  address
485129240Sru		popl %es			#  data
486177039Sjhb		leal 0x44(%esp,1),%esi		# Base of frame
487189017Sjhb		movl %esp,MEM_ESPR-0x04		# Save kernel stack pointer
488177039Sjhb		movl -0x14(%esi),%eax		# Get Int no
489177039Sjhb		cmpl $-1,%eax			# Hardware interrupt?
490189017Sjhb		jne intusr.1			# Yes
491177039Sjhb/*
492189017Sjhb * v86 calls save the btx_v86 pointer on the real mode stack and read
493189017Sjhb * the address and flags from the btx_v86 structure.  For interrupt
494189017Sjhb * handler invocations (VM86 INTx requests), disable interrupts,
495189017Sjhb * tracing, and alignment checking while the handler runs.
496177039Sjhb */
497129240Sru		movl $MEM_USR,%ebx		# User base
498129240Sru		movl %ebx,%edx			#  address
499129240Sru		addl -0x4(%esi),%ebx		# User ESP
500129240Sru		movl (%ebx),%ebp		# btx_v86 pointer
501129240Sru		addl %ebp,%edx			# Flatten btx_v86 ptr
502177039Sjhb		movl %edx,MEM_ESPR-0x08		# Save btx_v86 ptr
503177039Sjhb		movl V86_ADDR(%edx),%eax	# Get int no/address
504177039Sjhb		movl V86_CTL(%edx),%edx		# Get control flags
505189017Sjhb		movl -0x08(%esi),%ebx		# Save user flags in %ebx
506189017Sjhb		testl $V86F_ADDR,%edx		# Segment:offset?
507189017Sjhb		jnz intusr.4			# Yes
508189017Sjhb		andl $~(PSL_I|PSL_T|PSL_AC),%ebx # Disable interrupts, tracing,
509189017Sjhb						#  and alignment checking for
510189017Sjhb						#  interrupt handler
511177039Sjhb		jmp intusr.3			# Skip hardware interrupt
512177039Sjhb/*
513189017Sjhb * Hardware interrupts store a NULL btx_v86 pointer and use the
514189017Sjhb * address (interrupt number) from the stack with empty flags.  Also,
515189017Sjhb * push a dummy frame of zeros onto the stack for all the general
516189017Sjhb * purpose and segment registers and clear %eflags.  This gives the
517189017Sjhb * hardware interrupt handler a clean slate.
518177039Sjhb */
519189017Sjhbintusr.1:	xorl %edx,%edx			# Control flags
520177039Sjhb		movl %edx,MEM_ESPR-0x08		# NULL btx_v86 ptr
521189017Sjhb		movl $12,%ecx			# Frame is 12 dwords
522189017Sjhbintusr.2:	pushl $0x0			# Fill frame
523189017Sjhb		loop intusr.2			#  with zeros
524189017Sjhb		movl $PSL_RESERVED_DEFAULT,%ebx # Set clean %eflags
525177039Sjhb/*
526189017Sjhb * Look up real mode IDT entry for hardware interrupts and VM86 INTx
527189017Sjhb * requests.
528177039Sjhb */
529189017Sjhbintusr.3:	shll $0x2,%eax			# Scale
530129240Sru		movl (%eax),%eax		# Load int vector
531177039Sjhb		jmp intusr.5			# Skip CALLF test
532189017Sjhb/*
533189017Sjhb * Panic if V86F_CALLF isn't set with V86F_ADDR.
534189017Sjhb */
535177039Sjhbintusr.4:	testl $V86F_CALLF,%edx		# Far call?
536177039Sjhb		jnz intusr.5			# Ok
537177039Sjhb		movl %edx,0x30(%esp,1)		# Place VM86 flags in int no
538177039Sjhb		movl $badvm86,%esi		# Display bad
539177039Sjhb		call putstr			#  VM86 call
540177039Sjhb		popl %es			# Restore
541177039Sjhb		popl %ds			#  seg
542177039Sjhb		popl %fs			#  regs
543177039Sjhb		popl %gs
544177039Sjhb		popal				# Restore gp regs
545177039Sjhb		jmp ex_noc			# Panic
546189017Sjhb/*
547189017Sjhb * %eax now holds the segment:offset of the function.
548189017Sjhb * %ebx now holds the %eflags to pass to real mode.
549189017Sjhb * %edx now holds the V86F_* flags.
550189017Sjhb */
551181433Sjhbintusr.5:	movw %bx,MEM_ESPR-0x12		# Pass user flags to real mode
552181433Sjhb						#  target
553128709Sru/*
554177039Sjhb * If this is a v86 call, copy the seg regs out of the btx_v86 structure.
555177039Sjhb */
556181433Sjhb		movl MEM_ESPR-0x08,%ecx		# Get btx_v86 ptr
557177039Sjhb		jecxz intusr.6			# Skip for hardware ints
558177039Sjhb		leal -0x44(%esi),%edi		# %edi => kernel stack seg regs
559177039Sjhb		pushl %esi			# Save
560177039Sjhb		leal V86_ES(%ecx),%esi		# %esi => btx_v86 seg regs
561177039Sjhb		movl $4,%ecx			# Copy seg regs
562177039Sjhb		rep				#  from btx_v86
563177039Sjhb		movsl				#  to kernel stack
564177039Sjhb		popl %esi			# Restore
565189017Sjhbintusr.6:	movl -0x08(%esi),%ebx		# Copy user flags to real
566177039Sjhb		movl %ebx,MEM_ESPR-0x0c		#  mode return trampoline
567177039Sjhb		movl $rret_tramp,%ebx		# Set return trampoline
568177039Sjhb		movl %ebx,MEM_ESPR-0x10		#  CS:IP
569177039Sjhb		movl %eax,MEM_ESPR-0x16		# Real mode target CS:IP
570177039Sjhb		ljmpw $SEL_RCODE,$intusr.7	# Change to 16-bit segment
571177039Sjhb		.code16
572177039Sjhbintusr.7:	movl %cr0,%eax			# Leave
573177039Sjhb		dec %al				#  protected
574177039Sjhb		movl %eax,%cr0			#  mode
575177039Sjhb		ljmpw $0x0,$intusr.8
576177039Sjhbintusr.8:	xorw %ax,%ax			# Reset %ds
577177039Sjhb		movw %ax,%ds			#  and
578177039Sjhb		movw %ax,%ss			#  %ss
579177039Sjhb		lidt ivtdesc	 		# Set IVT
580177039Sjhb		popl %es			# Restore
581177039Sjhb		popl %ds			#  seg
582177039Sjhb		popl %fs			#  regs
583177039Sjhb		popl %gs
584177039Sjhb		popal				# Restore gp regs
585177039Sjhb		movw $MEM_ESPR-0x16,%sp		# Switch to real mode stack
586177039Sjhb		iret				# Call target routine
587177039Sjhb/*
588177039Sjhb * For the return to real mode we setup a stack frame like this on the real
589177039Sjhb * mode stack.  Note that callf calls won't pop off the flags, but we just
590177039Sjhb * ignore that by repositioning %sp to be just above the btx_v86 pointer
591177039Sjhb * so it is aligned.  The stack is relative to MEM_ESPR.
592177039Sjhb *
593177039Sjhb * -0x04	kernel %esp
594177039Sjhb * -0x08	btx_v86
595177039Sjhb * -0x0c	%eax
596177039Sjhb * -0x10	%ecx
597177039Sjhb * -0x14	%edx
598177039Sjhb * -0x18	%ebx
599177039Sjhb * -0x1c	%esp
600177039Sjhb * -0x20	%ebp
601177039Sjhb * -0x24	%esi
602177039Sjhb * -0x28	%edi
603177039Sjhb * -0x2c	%gs
604177039Sjhb * -0x30	%fs
605177039Sjhb * -0x34	%ds
606177039Sjhb * -0x38	%es
607177039Sjhb * -0x3c	%eflags
608177039Sjhb */
609177039Sjhbrret_tramp:	movw $MEM_ESPR-0x08,%sp		# Reset stack pointer
610177039Sjhb		pushal				# Save gp regs
611177039Sjhb		pushl %gs			# Save
612177039Sjhb		pushl %fs			#  seg
613177039Sjhb		pushl %ds			#  regs
614177039Sjhb		pushl %es
615177039Sjhb		pushfl				# Save %eflags
616256562Sjhb		pushl $PSL_RESERVED_DEFAULT|PSL_D # Use clean %eflags with
617256562Sjhb		popfl				#  string ops dec
618177039Sjhb		xorw %ax,%ax			# Reset seg
619177039Sjhb		movw %ax,%ds			#  regs
620177039Sjhb		movw %ax,%es			#  (%ss is already 0)
621177039Sjhb		lidt idtdesc	 		# Set IDT
622177039Sjhb		lgdt gdtdesc	 		# Set GDT
623177039Sjhb		mov %cr0,%eax			# Switch to protected
624177039Sjhb		inc %ax				#  mode
625177039Sjhb		mov %eax,%cr0			#
626177039Sjhb		ljmp $SEL_SCODE,$rret_tramp.1	# To 32-bit code
627177039Sjhb		.code32
628177039Sjhbrret_tramp.1:	xorl %ecx,%ecx			# Zero
629177039Sjhb		movb $SEL_SDATA,%cl		# Setup
630177039Sjhb		movw %cx,%ss			#  32-bit
631177039Sjhb		movw %cx,%ds			#  seg
632177039Sjhb		movw %cx,%es			#  regs
633177039Sjhb		movl MEM_ESPR-0x04,%esp		# Switch to kernel stack
634177039Sjhb		leal 0x44(%esp,1),%esi		# Base of frame
635177039Sjhb		andb $~0x2,tss_desc+0x5		# Clear TSS busy
636177039Sjhb		movb $SEL_TSS,%cl		# Set task
637177039Sjhb		ltr %cx				#  register
638177039Sjhb/*
639189017Sjhb * Now we are back in protected mode.  The kernel stack frame set up
640189017Sjhb * before entering real mode is still intact. For hardware interrupts,
641189017Sjhb * leave the frame unchanged.
642189017Sjhb */
643189017Sjhb		cmpl $0,MEM_ESPR-0x08		# Leave saved regs unchanged
644189017Sjhb		jz rret_tramp.3			#  for hardware ints
645189017Sjhb/*
646189017Sjhb * For V86 calls, copy the registers off of the real mode stack onto
647189017Sjhb * the kernel stack as we want their updated values.  Also, initialize
648189017Sjhb * the segment registers on the kernel stack.
649177039Sjhb *
650177039Sjhb * Note that the %esp in the kernel stack after this is garbage, but popa
651177039Sjhb * ignores it, so we don't have to fix it up.
652177039Sjhb */
653177039Sjhb		leal -0x18(%esi),%edi		# Kernel stack GP regs
654177039Sjhb		pushl %esi			# Save
655177039Sjhb		movl $MEM_ESPR-0x0c,%esi	# Real mode stack GP regs
656177039Sjhb		movl $8,%ecx			# Copy GP regs from
657177039Sjhb		rep				#  real mode stack
658177039Sjhb		movsl				#  to kernel stack
659177039Sjhb		movl $SEL_UDATA,%eax		# Selector for data seg regs
660177039Sjhb		movl $4,%ecx			# Initialize %ds,
661177039Sjhb		rep				#  %es, %fs, and
662177039Sjhb		stosl				#  %gs
663177039Sjhb/*
664189017Sjhb * For V86 calls, copy the saved seg regs on the real mode stack back
665189017Sjhb * over to the btx_v86 structure.  Also, conditionally update the
666189017Sjhb * saved eflags on the kernel stack based on the flags from the user.
667177039Sjhb */
668177039Sjhb		movl MEM_ESPR-0x08,%ecx		# Get btx_v86 ptr
669177039Sjhb		leal V86_GS(%ecx),%edi		# %edi => btx_v86 seg regs
670177039Sjhb		leal MEM_ESPR-0x2c,%esi		# %esi => real mode seg regs
671177039Sjhb		xchgl %ecx,%edx			# Save btx_v86 ptr
672177039Sjhb		movl $4,%ecx			# Copy seg regs
673177039Sjhb		rep				#  from real mode stack
674177039Sjhb		movsl				#  to btx_v86
675177039Sjhb		popl %esi			# Restore
676177039Sjhb		movl V86_CTL(%edx),%edx		# Read V86 control flags
677177039Sjhb		testl $V86F_FLAGS,%edx		# User wants flags?
678177039Sjhb		jz rret_tramp.3			# No
679177039Sjhb		movl MEM_ESPR-0x3c,%eax		# Read real mode flags
680256562Sjhb		andl $~(PSL_T|PSL_NT),%eax	# Clear unsafe flags
681177039Sjhb		movw %ax,-0x08(%esi)		# Update user flags (low 16)
682177039Sjhb/*
683177039Sjhb * Return to the user task
684177039Sjhb */
685177039Sjhbrret_tramp.3:	popl %es			# Restore
686177039Sjhb		popl %ds			#  seg
687177039Sjhb		popl %fs			#  regs
688177039Sjhb		popl %gs
689177039Sjhb		popal				# Restore gp regs
690177039Sjhb		addl $4,%esp			# Discard int no
691177039Sjhb		iret				# Return to user mode
692177039Sjhb
693177039Sjhb/*
694128709Sru * System Call.
695128709Sru */
696129240Sruintx30: 	cmpl $SYS_EXEC,%eax		# Exec system call?
697129240Sru		jne intx30.1			# No
698129240Sru		pushl %ss			# Set up
699129240Sru		popl %es			#  all
700129240Sru		pushl %es			#  segment
701129240Sru		popl %ds			#  registers
702129240Sru		pushl %ds			#  for the
703129240Sru		popl %fs			#  program
704129240Sru		pushl %fs			#  we're
705129240Sru		popl %gs			#  invoking
706129240Sru		movl $MEM_USR,%eax		# User base address
707129240Sru		addl 0xc(%esp,1),%eax		# Change to user
708129240Sru		leal 0x4(%eax),%esp		#  stack
709129240Sru		popl %eax			# Call
710129240Sru		call *%eax			#  program
711129240Sruintx30.1:	orb $0x1,%ss:btx_hdr+0x7	# Flag reboot
712129240Sru		jmp exit			# Exit
713128709Sru/*
714128709Sru * Dump structure [EBX] to [EDI], using format string [ESI].
715128709Sru */
716129240Srudump.0: 	stosb				# Save char
717129240Srudump:		lodsb				# Load char
718129240Sru		testb %al,%al			# End of string?
719129240Sru		jz dump.10			# Yes
720129240Sru		testb $0x80,%al 		# Control?
721129240Sru		jz dump.0			# No
722129240Sru		movb %al,%ch			# Save control
723129240Sru		movb $'=',%al			# Append
724129240Sru		stosb				#  '='
725129240Sru		lodsb				# Get offset
726129240Sru		pushl %esi			# Save
727129240Sru		movsbl %al,%esi 		# To
728129240Sru		addl %ebx,%esi			#  pointer
729129240Sru		testb $DMP_X16,%ch		# Dump word?
730129240Sru		jz dump.1			# No
731129240Sru		lodsw				# Get and
732129240Sru		call hex16			#  dump it
733129240Srudump.1: 	testb $DMP_X32,%ch		# Dump long?
734129240Sru		jz dump.2			# No
735129240Sru		lodsl				# Get and
736129240Sru		call hex32			#  dump it
737129240Srudump.2: 	testb $DMP_MEM,%ch		# Dump memory?
738129240Sru		jz dump.8			# No
739129240Sru		pushl %ds			# Save
740181433Sjhb		testl $PSL_VM,0x50(%ebx)	# V86 mode?
741129240Sru		jnz dump.3			# Yes
742129240Sru		verr 0x4(%esi)	 		# Readable selector?
743129240Sru		jnz dump.3			# No
744129240Sru		ldsl (%esi),%esi		# Load pointer
745129240Sru		jmp dump.4			# Join common code
746129240Srudump.3: 	lodsl				# Set offset
747129240Sru		xchgl %eax,%edx 		# Save
748129240Sru		lodsl				# Get segment
749163032Sjhb		shll $0x4,%eax			#  * 0x10
750163032Sjhb		addl %edx,%eax			#  + offset
751129240Sru		xchgl %eax,%esi 		# Set pointer
752129240Srudump.4: 	movb $2,%dl			# Num lines
753129240Srudump.4a:	movb $0x10,%cl			# Bytes to dump
754129240Srudump.5: 	lodsb				# Get byte and
755129240Sru		call hex8			#  dump it
756129240Sru		decb %cl			# Keep count
757129240Sru		jz dump.6a			# If done
758129240Sru		movb $'-',%al			# Separator
759129240Sru		cmpb $0x8,%cl			# Half way?
760129240Sru		je dump.6			# Yes
761129240Sru		movb $' ',%al			# Use space
762129240Srudump.6: 	stosb				# Save separator
763129240Sru		jmp dump.5			# Continue
764129240Srudump.6a:	decb %dl			# Keep count
765129240Sru		jz dump.7			# If done
766129240Sru		movb $0xa,%al			# Line feed
767129240Sru		stosb				# Save one
768129240Sru		movb $7,%cl			# Leading
769129240Sru		movb $' ',%al			#  spaces
770129240Srudump.6b:	stosb				# Dump
771129240Sru		decb %cl			#  spaces
77285993Sjhb		jnz dump.6b
773129240Sru		jmp dump.4a			# Next line
774129240Srudump.7: 	popl %ds			# Restore
775129240Srudump.8: 	popl %esi			# Restore
776129240Sru		movb $0xa,%al			# Line feed
777129240Sru		testb $DMP_EOL,%ch		# End of line?
778129240Sru		jnz dump.9			# Yes
779129240Sru		movb $' ',%al			# Use spaces
780129240Sru		stosb				# Save one
781129240Srudump.9: 	jmp dump.0			# Continue
782129240Srudump.10:	stosb				# Terminate string
783129240Sru		ret				# To caller
784128709Sru/*
785128709Sru * Convert EAX, AX, or AL to hex, saving the result to [EDI].
786128709Sru */
787129240Sruhex32:		pushl %eax			# Save
788129240Sru		shrl $0x10,%eax 		# Do upper
789129240Sru		call hex16			#  16
790129240Sru		popl %eax			# Restore
791129240Sruhex16:		call hex16.1			# Do upper 8
792129240Sruhex16.1:	xchgb %ah,%al			# Save/restore
793129240Sruhex8:		pushl %eax			# Save
794129240Sru		shrb $0x4,%al			# Do upper
795129240Sru		call hex8.1			#  4
796129240Sru		popl %eax			# Restore
797129240Sruhex8.1: 	andb $0xf,%al			# Get lower 4
798129240Sru		cmpb $0xa,%al			# Convert
799129240Sru		sbbb $0x69,%al			#  to hex
800129240Sru		das				#  digit
801129240Sru		orb $0x20,%al			# To lower case
802129240Sru		stosb				# Save char
803129240Sru		ret				# (Recursive)
804128709Sru/*
805128709Sru * Output zero-terminated string [ESI] to the console.
806128709Sru */
807129240Sruputstr.0:	call putchr			# Output char
808129240Sruputstr: 	lodsb				# Load char
809129240Sru		testb %al,%al			# End of string?
810129240Sru		jnz putstr.0			# No
811129240Sru		ret				# To caller
812125693Sru#ifdef BTX_SERIAL
813129240Sru		.set SIO_PRT,SIOPRT		# Base port
814129240Sru		.set SIO_FMT,SIOFMT		# 8N1
815129240Sru		.set SIO_DIV,(115200/SIOSPD)	# 115200 / SPD
81685994Sjhb
817138046Sjhb/*
818241301Savg * int sio_init(void)
819138046Sjhb */
820129240Srusio_init:	movw $SIO_PRT+0x3,%dx		# Data format reg
821129240Sru		movb $SIO_FMT|0x80,%al		# Set format
822129240Sru		outb %al,(%dx)			#  and DLAB
823129240Sru		pushl %edx			# Save
824129240Sru		subb $0x3,%dl			# Divisor latch reg
825129240Sru		movw $SIO_DIV,%ax		# Set
826129240Sru		outw %ax,(%dx)			#  BPS
827129240Sru		popl %edx			# Restore
828129240Sru		movb $SIO_FMT,%al		# Clear
829129240Sru		outb %al,(%dx)			#  DLAB
830129240Sru		incl %edx			# Modem control reg
831129240Sru		movb $0x3,%al			# Set RTS,
832129240Sru		outb %al,(%dx)			#  DTR
833129240Sru		incl %edx			# Line status reg
834241301Savg		call sio_getc.1 		# Get character
83585994Sjhb
836138046Sjhb/*
837241301Savg * int sio_flush(void)
838138046Sjhb */
839241301Savgsio_flush:	xorl %eax,%eax			# Return value
840241301Savg		xorl %ecx,%ecx			# Timeout
841241301Savg		movb $0x80,%ch			#  counter
842241301Savgsio_flush.1:	call sio_ischar 		# Check for character
843241301Savg		jz sio_flush.2			# Till none
844241301Savg		loop sio_flush.1		#  or counter is zero
845241301Savg		movb $1, %al			# Exhausted all tries
846241301Savgsio_flush.2:	ret				# To caller
84785994Sjhb
848138046Sjhb/*
849128709Sru * void sio_putc(int c)
850138046Sjhb */
851129240Srusio_putc:	movw $SIO_PRT+0x5,%dx		# Line status reg
852129240Sru		xor %ecx,%ecx			# Timeout
853129240Sru		movb $0x40,%ch			#  counter
854129240Srusio_putc.1:	inb (%dx),%al			# Transmitter
855129240Sru		testb $0x20,%al 		#  buffer empty?
856129240Sru		loopz sio_putc.1		# No
857129240Sru		jz sio_putc.2			# If timeout
858129240Sru		movb 0x4(%esp,1),%al		# Get character
859129240Sru		subb $0x5,%dl			# Transmitter hold reg
860129240Sru		outb %al,(%dx)			# Write character
861129240Srusio_putc.2:	ret $0x4			# To caller
86285994Sjhb
863138046Sjhb/*
864128709Sru * int sio_getc(void)
865138046Sjhb */
866129240Srusio_getc:	call sio_ischar 		# Character available?
867129240Sru		jz sio_getc			# No
868129240Srusio_getc.1:	subb $0x5,%dl			# Receiver buffer reg
869129240Sru		inb (%dx),%al			# Read character
870129240Sru		ret				# To caller
87185994Sjhb
872138046Sjhb/*
873128709Sru * int sio_ischar(void)
874138046Sjhb */
875129240Srusio_ischar:	movw $SIO_PRT+0x5,%dx		# Line status register
876129240Sru		xorl %eax,%eax			# Zero
877129240Sru		inb (%dx),%al			# Received data
878129240Sru		andb $0x1,%al			#  ready?
879129240Sru		ret				# To caller
88085994Sjhb
881128709Sru/*
882128709Sru * Output character AL to the serial console.
883128709Sru */
884129240Sruputchr: 	pusha				# Save
885129240Sru		cmpb $10, %al			# is it a newline?
886129240Sru		jne putchr.1			#  no?, then leave
887129240Sru		push $13			# output a carriage
888129240Sru		call sio_putc			#  return first
889129240Sru		movb $10, %al			# restore %al
890129240Sruputchr.1:	pushl %eax			# Push the character
891129240Sru						#  onto the stack
892129240Sru		call sio_putc			# Output the character
893129240Sru		popa				# Restore
894129240Sru		ret				# To caller
895125693Sru#else
896128709Sru/*
897128709Sru * Output character AL to the console.
898128709Sru */
899129240Sruputchr: 	pusha				# Save
900129240Sru		xorl %ecx,%ecx			# Zero for loops
901129240Sru		movb $SCR_MAT,%ah		# Mode/attribute
902129240Sru		movl $BDA_POS,%ebx		# BDA pointer
903129240Sru		movw (%ebx),%dx 		# Cursor position
904129240Sru		movl $0xb8000,%edi		# Regen buffer (color)
905129240Sru		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
906129240Sru		jne putchr.1			# No
907129240Sru		xorw %di,%di			# Regen buffer (mono)
908129240Sruputchr.1:	cmpb $0xa,%al			# New line?
909129240Sru		je putchr.2			# Yes
910129240Sru		xchgl %eax,%ecx 		# Save char
911129240Sru		movb $SCR_COL,%al		# Columns per row
912129240Sru		mulb %dh			#  * row position
913129240Sru		addb %dl,%al			#  + column
914129240Sru		adcb $0x0,%ah			#  position
915129240Sru		shll %eax			#  * 2
916129240Sru		xchgl %eax,%ecx 		# Swap char, offset
917129240Sru		movw %ax,(%edi,%ecx,1)		# Write attr:char
918129240Sru		incl %edx			# Bump cursor
919129240Sru		cmpb $SCR_COL,%dl		# Beyond row?
920129240Sru		jb putchr.3			# No
921129240Sruputchr.2:	xorb %dl,%dl			# Zero column
922129240Sru		incb %dh			# Bump row
923129240Sruputchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
924129240Sru		jb putchr.4			# No
925129240Sru		leal 2*SCR_COL(%edi),%esi	# New top line
926129240Sru		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
927129240Sru		rep				# Scroll
928129240Sru		movsl				#  screen
929129240Sru		movb $0x20,%al			# Space
930129240Sru		movb $SCR_COL,%cl		# Columns to clear
931129240Sru		rep				# Clear
932129240Sru		stosw				#  line
933129240Sru		movb $SCR_ROW-1,%dh		# Bottom line
934129240Sruputchr.4:	movw %dx,(%ebx) 		# Update position
935129240Sru		popa				# Restore
936129240Sru		ret				# To caller
937125693Sru#endif
93839088Srnordier
939177039Sjhb		.code16
940177039Sjhb/*
941177039Sjhb * Real Mode Hardware interrupt jump table.
942177039Sjhb */
943177039Sjhbintr20: 	push $0x8			# Int 0x20: IRQ0
944177039Sjhb		jmp int_hwr			# V86 int 0x8
945177039Sjhb		push $0x9			# Int 0x21: IRQ1
946177039Sjhb		jmp int_hwr			# V86 int 0x9
947177039Sjhb		push $0xa			# Int 0x22: IRQ2
948177039Sjhb		jmp int_hwr			# V86 int 0xa
949177039Sjhb		push $0xb			# Int 0x23: IRQ3
950177039Sjhb		jmp int_hwr			# V86 int 0xb
951177039Sjhb		push $0xc			# Int 0x24: IRQ4
952177039Sjhb		jmp int_hwr			# V86 int 0xc
953177039Sjhb		push $0xd			# Int 0x25: IRQ5
954177039Sjhb		jmp int_hwr			# V86 int 0xd
955177039Sjhb		push $0xe			# Int 0x26: IRQ6
956177039Sjhb		jmp int_hwr			# V86 int 0xe
957177039Sjhb		push $0xf			# Int 0x27: IRQ7
958177039Sjhb		jmp int_hwr			# V86 int 0xf
959177039Sjhb		push $0x70			# Int 0x28: IRQ8
960177039Sjhb		jmp int_hwr			# V86 int 0x70
961177039Sjhb		push $0x71			# Int 0x29: IRQ9
962177039Sjhb		jmp int_hwr			# V86 int 0x71
963177039Sjhb		push $0x72			# Int 0x2a: IRQ10
964177039Sjhb		jmp int_hwr			# V86 int 0x72
965177039Sjhb		push $0x73			# Int 0x2b: IRQ11
966177039Sjhb		jmp int_hwr			# V86 int 0x73
967177039Sjhb		push $0x74			# Int 0x2c: IRQ12
968177039Sjhb		jmp int_hwr			# V86 int 0x74
969177039Sjhb		push $0x75			# Int 0x2d: IRQ13
970177039Sjhb		jmp int_hwr			# V86 int 0x75
971177039Sjhb		push $0x76			# Int 0x2e: IRQ14
972177039Sjhb		jmp int_hwr			# V86 int 0x76
973177039Sjhb		push $0x77			# Int 0x2f: IRQ15
974177039Sjhb		jmp int_hwr			# V86 int 0x77
975177039Sjhb/*
976177039Sjhb * Reflect hardware interrupts in real mode.
977177039Sjhb */
978177039Sjhbint_hwr: 	push %ax			# Save
979177039Sjhb		push %ds			# Save
980177039Sjhb		push %bp			# Save
981177039Sjhb		mov %sp,%bp			# Address stack frame
982177039Sjhb		xchg %bx,6(%bp)			# Swap BX, int no
983177039Sjhb		xor %ax,%ax			# Set %ds:%bx to
984177039Sjhb		shl $2,%bx			#  point to
985177039Sjhb		mov %ax,%ds			#  IDT entry
986177039Sjhb		mov (%bx),%ax			# Load IP
987177039Sjhb		mov 2(%bx),%bx			# Load CS
988177039Sjhb		xchg %ax,4(%bp)			# Swap saved %ax,%bx with
989177039Sjhb		xchg %bx,6(%bp)			#  CS:IP of handler
990177039Sjhb		pop %bp				# Restore
991177039Sjhb		pop %ds				# Restore
992177039Sjhb		lret				# Jump to handler
993177039Sjhb
99439088Srnordier		.p2align 4
995128709Sru/*
996128709Sru * Global descriptor table.
997128709Sru */
998129240Srugdt:		.word 0x0,0x0,0x0,0x0		# Null entry
999129240Sru		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
1000129240Sru		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
1001129240Sru		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
1002129240Sru		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
1003129240Sru		.word 0xffff,MEM_USR,0xfa00,0xcf# SEL_UCODE
1004129240Sru		.word 0xffff,MEM_USR,0xf200,0xcf# SEL_UDATA
1005177039Sjhbtss_desc:	.word _TSSLM,MEM_TSS,0x8900,0x0 # SEL_TSS
100639088Srnordiergdt.1:
1007128709Sru/*
1008128709Sru * Pseudo-descriptors.
1009128709Sru */
1010129240Srugdtdesc:	.word gdt.1-gdt-1,gdt,0x0	# GDT
1011129240Sruidtdesc:	.word _IDTLM,MEM_IDT,0x0	# IDT
1012129240Sruivtdesc:	.word 0x400-0x0-1,0x0,0x0	# IVT
1013128709Sru/*
1014128709Sru * IDT construction control string.
1015128709Sru */
1016129240Sruidtctl: 	.byte 0x10,  0x8e		# Int 0x0-0xf
1017129240Sru		.word 0x7dfb,intx00		#  (exceptions)
1018129240Sru		.byte 0x10,  0x8e		# Int 0x10
1019129240Sru		.word 0x1,   intx10		#  (exception)
1020129240Sru		.byte 0x10,  0x8e		# Int 0x20-0x2f
1021129240Sru		.word 0xffff,intx20		#  (hardware)
1022129240Sru		.byte 0x1,   0xee		# int 0x30
1023129240Sru		.word 0x1,   intx30		#  (system call)
1024129240Sru		.byte 0x2,   0xee		# Int 0x31-0x32
1025129240Sru		.word 0x1,   intx31		#  (V86, null)
1026129240Sru		.byte 0x0			# End of string
1027128709Sru/*
1028128709Sru * Dump format string.
1029128709Sru */
1030129240Srudmpfmt: 	.byte '\n'			# "\n"
1031129240Sru		.ascii "int"			# "int="
1032129240Sru		.byte 0x80|DMP_X32,	   0x40 # "00000000  "
1033129240Sru		.ascii "err"			# "err="
1034129240Sru		.byte 0x80|DMP_X32,	   0x44 # "00000000  "
1035129240Sru		.ascii "efl"			# "efl="
1036129240Sru		.byte 0x80|DMP_X32,	   0x50 # "00000000  "
1037129240Sru		.ascii "eip"			# "eip="
1038129240Sru		.byte 0x80|DMP_X32|DMP_EOL,0x48 # "00000000\n"
1039129240Sru		.ascii "eax"			# "eax="
1040129240Sru		.byte 0x80|DMP_X32,	   0x34 # "00000000  "
1041129240Sru		.ascii "ebx"			# "ebx="
1042129240Sru		.byte 0x80|DMP_X32,	   0x28 # "00000000  "
1043129240Sru		.ascii "ecx"			# "ecx="
1044129240Sru		.byte 0x80|DMP_X32,	   0x30 # "00000000  "
1045129240Sru		.ascii "edx"			# "edx="
1046129240Sru		.byte 0x80|DMP_X32|DMP_EOL,0x2c # "00000000\n"
1047129240Sru		.ascii "esi"			# "esi="
1048129240Sru		.byte 0x80|DMP_X32,	   0x1c # "00000000  "
1049129240Sru		.ascii "edi"			# "edi="
1050129240Sru		.byte 0x80|DMP_X32,	   0x18 # "00000000  "
1051129240Sru		.ascii "ebp"			# "ebp="
1052129240Sru		.byte 0x80|DMP_X32,	   0x20 # "00000000  "
1053129240Sru		.ascii "esp"			# "esp="
1054129240Sru		.byte 0x80|DMP_X32|DMP_EOL,0x0	# "00000000\n"
1055129240Sru		.ascii "cs"			# "cs="
1056129240Sru		.byte 0x80|DMP_X16,	   0x4c # "0000  "
1057129240Sru		.ascii "ds"			# "ds="
1058129240Sru		.byte 0x80|DMP_X16,	   0xc	# "0000  "
1059129240Sru		.ascii "es"			# "es="
1060129240Sru		.byte 0x80|DMP_X16,	   0x8	# "0000  "
1061129240Sru		.ascii "  "			# "  "
1062129240Sru		.ascii "fs"			# "fs="
1063129240Sru		.byte 0x80|DMP_X16,	   0x10 # "0000  "
1064129240Sru		.ascii "gs"			# "gs="
1065129240Sru		.byte 0x80|DMP_X16,	   0x14 # "0000  "
1066129240Sru		.ascii "ss"			# "ss="
1067129240Sru		.byte 0x80|DMP_X16|DMP_EOL,0x4	# "0000\n"
1068129240Sru		.ascii "cs:eip" 		# "cs:eip="
1069129240Sru		.byte 0x80|DMP_MEM|DMP_EOL,0x48 # "00 00 ... 00 00\n"
1070129240Sru		.ascii "ss:esp" 		# "ss:esp="
1071129240Sru		.byte 0x80|DMP_MEM|DMP_EOL,0x0	# "00 00 ... 00 00\n"
1072129240Sru		.asciz "BTX halted\n"		# End
1073128709Sru/*
1074177039Sjhb * Bad VM86 call panic
1075177039Sjhb */
1076177039Sjhbbadvm86:	.asciz "Invalid VM86 Request\n"
1077177039Sjhb
1078177039Sjhb/*
1079128709Sru * End of BTX memory.
1080128709Sru */
108139088Srnordier		.p2align 4
108239088Srnordierbreak:
1083