btxldr.S revision 43561
1128765Spjd#
2128765Spjd# Copyright (c) 1998 Robert Nordier
3128765Spjd# All rights reserved.
4128765Spjd#
5128765Spjd# Redistribution and use in source and binary forms are freely
6128765Spjd# permitted provided that the above copyright notice and this
7128765Spjd# paragraph and the following disclaimer are duplicated in all
8128765Spjd# such forms.
9128765Spjd#
10128765Spjd# This software is provided "AS IS" and without any express or
11128765Spjd# implied warranties, including, without limitation, the implied
12128765Spjd# warranties of merchantability and fitness for a particular
13128765Spjd# purpose.
14128765Spjd#
15128765Spjd
16128765Spjd#	$Id: btxldr.s,v 1.5 1999/01/22 13:07:17 rnordier Exp $
17128765Spjd
18128765Spjd#
19128765Spjd# Prototype BTX loader program, written in a couple of hours.  The
20128765Spjd# real thing should probably be more flexible, and in C.
21128765Spjd#
22128765Spjd
23128765Spjd#
24128765Spjd# Memory locations.
25128765Spjd#
26128765Spjd		.set MEM_STUB,0x600		# Real mode stub
27128765Spjd		.set MEM_ESP,0x1000		# New stack pointer
28128765Spjd		.set MEM_TBL,0x5000		# BTX page tables
29128765Spjd		.set MEM_ENTRY,0x9010		# BTX entry point
30128765Spjd		.set MEM_DATA,0x101000		# Data segment
31128765Spjd#
32128765Spjd# Segment selectors.
33128765Spjd#
34128765Spjd		.set SEL_SCODE,0x8		# 4GB code
35128765Spjd		.set SEL_SDATA,0x10		# 4GB data
36128765Spjd		.set SEL_RCODE,0x18		# 64K code
37147844Spjd		.set SEL_RDATA,0x20		# 64K data
38147844Spjd#
39128765Spjd# Paging constants.
40128765Spjd#
41147844Spjd		.set PAG_SIZ,0x1000		# Page size
42147844Spjd		.set PAG_ENT,0x4		# Page entry size
43128765Spjd#
44128765Spjd# Screen constants.
45128765Spjd#
46128765Spjd.ifdef PC98
47128765Spjd		.set SCR_MAT,0xe1		# Mode/attribute
48128765Spjd.else
49128765Spjd		.set SCR_MAT,0x7		# Mode/attribute
50128765Spjd.endif
51128765Spjd		.set SCR_COL,0x50		# Columns per row
52128765Spjd		.set SCR_ROW,0x19		# Rows per screen
53128765Spjd#
54128765Spjd# BIOS Data Area locations.
55128765Spjd#
56128765Spjd.ifdef PC98
57128765Spjd		.set BDA_MEM,0xa1501		# Free memory
58147844Spjd		.set BDA_POS,0xa153e		# Cursor position
59128765Spjd.else
60128765Spjd		.set BDA_MEM,0x413		# Free memory
61128765Spjd		.set BDA_SCR,0x449		# Video mode
62204076Spjd		.set BDA_POS,0x450		# Cursor position
63128765Spjd.endif
64128765Spjd#
65128765Spjd# Required by aout gas inadequacy.
66128765Spjd#
67128765Spjd		.set SIZ_STUB,0x1a		# Size of stub
68128765Spjd#
69128765Spjd# We expect to be loaded by boot2 at 0x100000.
70147844Spjd#
71147844Spjd		.globl start
72147844Spjd#
73147844Spjd# BTX program loader for ELF clients.
74128765Spjd#
75128765Spjdstart:		cld				# String ops inc
76128765Spjd.ifdef PC98
77128765Spjd		cli
78128765Spjdgdcwait.1:	inb $0x60,%al
79128765Spjd		testb $0x04,%al
80128765Spjd		jz gdcwait.1
81128765Spjd		movb $0xe0,%al
82147844Spjd		outb %al,$0x62
83128765Spjd		nop
84128765Spjdgdcwait.2:	inb $0x60,%al
85128765Spjd		testb $0x01,%al
86128765Spjd		jz gdcwait.2
87128765Spjd		inb $0x62,%al
88128765Spjd		movb %al,%dl
89147844Spjd		inb $0x62,%al
90147844Spjd		movb %al,%dh
91128765Spjd		inb $0x62,%al
92128765Spjd		inb $0x62,%al
93147844Spjd		inb $0x62,%al
94147844Spjd		shlw $1,%dx
95147844Spjd		movl $BDA_POS,%ebx
96147844Spjd		movw %dx,(%ebx)
97128765Spjd.endif
98147844Spjd		movl $m_logo,%esi		# Identify
99128765Spjd		call putstr			#  ourselves
100128765Spjd		movzwl BDA_MEM,%eax		# Get base memory
101128765Spjd.ifdef PC98
102147844Spjd		andl $0x7,%eax
103147844Spjd		incl %eax
104128765Spjd		shll $0x11,%eax			#  in bytes
105147844Spjd.else
106128765Spjd		shll $0xa,%eax			#  in bytes
107128765Spjd.endif
108128765Spjd		movl %eax,%ebp			# Base of user stack
109128765Spjd		movl $m_mem,%esi		# Display
110128765Spjd		call dhexout			#  amount of
111128765Spjd		call dputstr			#  base memory
112128765Spjd		lgdt gdtdesc			# Load new GDT
113147844Spjd#
114147844Spjd# Relocate caller's arguments.
115128765Spjd#
116128765Spjd		movl $m_esp,%esi		# Display
117128765Spjd		movl %esp,%eax			#  caller's
118147844Spjd		call dhexout			#  stack
119128765Spjd		call dputstr			#  pointer
120128765Spjd		movl $m_args,%esi		# Format string
121128765Spjd		leal 0x4(%esp,1),%ebx		# First argument
122128765Spjd		movl $0x6,%ecx			# Count
123128765Spjdstart.1:	movl (%ebx),%eax		# Get argument and
124128765Spjd		addl $0x4,%ebx			#  bump pointer
125128765Spjd		call dhexout			# Display it
126128765Spjd		loop start.1			# Till done
127128765Spjd		call dputstr			# End message
128147844Spjd		movl $0x48,%ecx 		# Allocate space
129128765Spjd		subl %ecx,%ebp			#  for bootinfo
130128765Spjd		movl 0x18(%esp,1),%esi		# Source
131128765Spjd		movl %ebp,%edi			# Destination
132128765Spjd		rep				# Copy
133128765Spjd		movsb				#  it
134128765Spjd		movl %ebp,0x18(%esp,1)		# Update pointer
135147844Spjd		movl $m_rel_bi,%esi		# Display
136147844Spjd		movl %ebp,%eax			#  bootinfo
137147844Spjd		call dhexout			#  relocation
138147844Spjd		call dputstr			#  message
139147844Spjd		movl $0x18,%ecx 		# Allocate space
140147844Spjd		subl %ecx,%ebp			#  for arguments
141147844Spjd		leal 0x4(%esp,1),%esi		# Source
142147844Spjd		movl %ebp,%edi			# Destination
143147844Spjd		rep				# Copy
144147844Spjd		movsb				#  them
145147844Spjd		movl $m_rel_args,%esi		# Display
146147844Spjd		movl %ebp,%eax			#  argument
147128765Spjd		call dhexout			#  relocation
148128765Spjd		call dputstr			#  message
149128765Spjd#
150128765Spjd# Set up BTX kernel.
151147844Spjd#
152147844Spjd		movl $MEM_ESP,%esp		# Set up new stack
153128765Spjd		movl $MEM_DATA,%ebx		# Data segment
154128765Spjd		movl $m_vers,%esi		# Display BTX
155147844Spjd		call putstr			#  version message
156147844Spjd		movb 0x5(%ebx),%al		# Get major version
157128765Spjd		addb $'0',%al			# Display
158147844Spjd		call putchr			#  it
159147844Spjd		movb $'.',%al			# And a
160147844Spjd		call putchr			#  dot
161147844Spjd		movb 0x6(%ebx),%al		# Get minor
162128765Spjd		xorb %ah,%ah			#  version
163147844Spjd		movb $0xa,%dl			# Divide
164147844Spjd		divb %dl,%al			#  by 10
165147844Spjd		addb $'0',%al			# Display
166147844Spjd		call putchr			#  tens
167147844Spjd		movb %ah,%al			# Get units
168147844Spjd		addb $'0',%al			# Display
169128765Spjd		call putchr			#  units
170147844Spjd		call putstr			# End message
171147844Spjd		movl %ebx,%esi			# BTX image
172147844Spjd		movzwl 0x8(%ebx),%edi		# Compute
173147844Spjd		orl $PAG_SIZ/PAG_ENT-1,%edi	#  the
174128765Spjd		incl %edi			#  BTX
175147844Spjd		shll $0x2,%edi			#  load
176128765Spjd		addl $MEM_TBL,%edi		#  address
177128765Spjd		pushl %edi			# Save
178147844Spjd		movzwl 0xa(%ebx),%ecx		# Image size
179147844Spjd		pushl %ecx			# Save
180147844Spjd		rep				# Relocate
181147844Spjd		movsb				#  BTX
182147844Spjd		movl %esi,%ebx			# Keep place
183147844Spjd		movl $m_rel_btx,%esi		# Restore
184147844Spjd		popl %eax			#  parameters
185147844Spjd		call dhexout			#  and
186147844Spjd		popl %ebp			#  display
187147844Spjd		movl %ebp,%eax			#  the
188147844Spjd		call dhexout			#  relocation
189147844Spjd		call dputstr			#  message
190147844Spjd		addl $PAG_SIZ,%ebp		# Display
191147844Spjd		movl $m_base,%esi		#  the
192147844Spjd		movl %ebp,%eax			#  user
193147844Spjd		call dhexout			#  base
194147844Spjd		call dputstr			#  address
195147844Spjd#
196147844Spjd# Set up ELF-format client program.
197147844Spjd#
198147844Spjd		cmpl $0x464c457f,(%ebx) 	# ELF magic number?
199147844Spjd		je start.3			# Yes
200147844Spjd		movl $e_fmt,%esi		# Display error
201128765Spjd		call putstr			#  message
202128765Spjdstart.2:	jmp start.2			# Hang
203147844Spjdstart.3:	movl $m_elf,%esi		# Display ELF
204147844Spjd		call dputstr			#  message
205147844Spjd		movl $m_segs,%esi		# Format string
206147844Spjd		movl $0x2,%edi			# Segment count
207147844Spjd		movl 0x1c(%ebx),%edx		# Get e_phoff
208147844Spjd		addl %ebx,%edx			# To pointer
209128765Spjd		movzwl 0x2c(%ebx),%ecx		# Get e_phnum
210147844Spjdstart.4:	cmpl $0x1,(%edx)		# Is p_type PT_LOAD?
211147844Spjd		jne start.6			# No
212147844Spjd		movl 0x4(%edx),%eax		# Display
213147844Spjd		call dhexout			#  p_offset
214147844Spjd		movl 0x8(%edx),%eax		# Display
215147844Spjd		call dhexout			#  p_vaddr
216147844Spjd		movl 0x10(%edx),%eax		# Display
217147844Spjd		call dhexout			#  p_filesz
218147844Spjd		movl 0x14(%edx),%eax		# Display
219147844Spjd		call dhexout			#  p_memsz
220147844Spjd		call dputstr			# End message
221147844Spjd		pushl %esi			# Save
222147844Spjd		pushl %edi			#  working
223128765Spjd		pushl %ecx			#  registers
224128765Spjd		movl 0x4(%edx),%esi		# Get p_offset
225147844Spjd		addl %ebx,%esi			#  as pointer
226147844Spjd		movl 0x8(%edx),%edi		# Get p_vaddr
227147844Spjd		addl %ebp,%edi			#  as pointer
228147844Spjd		movl 0x10(%edx),%ecx		# Get p_filesz
229128765Spjd		rep				# Set up
230128765Spjd		movsb				#  segment
231128765Spjd		movl 0x14(%edx),%ecx		# Any bytes
232128765Spjd		subl 0x10(%edx),%ecx		#  to zero?
233128765Spjd		jz start.5			# No
234147844Spjd		xorb %al,%al			# Then
235128765Spjd		rep				#  zero
236128765Spjd		stosb				#  them
237147844Spjdstart.5:	popl %ecx			# Restore
238147844Spjd		popl %edi			#  working
239128765Spjd		popl %esi			#  registers
240128765Spjd		decl %edi			# Segments to do
241147844Spjd		je start.7			# If none
242147844Spjdstart.6:	addl $0x20,%edx 		# To next entry
243128765Spjd		loop start.4			# Till done
244147844Spjdstart.7:	movl $m_done,%esi		# Display done
245147844Spjd		call dputstr			#  message
246147844Spjd		movl $start.8,%esi		# Real mode stub
247147844Spjd		movl $MEM_STUB,%edi		# Destination
248147844Spjd		movl $SIZ_STUB,%ecx		# Size
249128765Spjd		rep				# Relocate
250147844Spjd		movsb				#  it
251147844Spjd		ljmp $SEL_RCODE,$MEM_STUB	# To 16-bit code
252147844Spjdstart.8:	xorl %eax,%eax			# Data
253147844Spjd		movb $SEL_RDATA,%al		#  selector
254147844Spjd		movl %eax,%ss			# Reload SS
255147844Spjd		movl %eax,%ds			# Reset
256147844Spjd		movl %eax,%es			#  other
257147844Spjd		movl %eax,%fs			#  segment
258147844Spjd		movl %eax,%gs			#  limits
259147844Spjd		movl %cr0,%eax			# Switch to
260147844Spjd		decl %eax			#  real
261147844Spjd		movl %eax,%cr0			#  mode
262147844Spjd		.byte 0xea			# Jump to
263147844Spjd		.word MEM_ENTRY 		# BTX entry
264147844Spjd		.word 0x0			#  point
265147844Spjdstart.9:
266147844Spjd#
267128765Spjd# Output message [ESI] followed by EAX in hex.
268147844Spjd#
269147844Spjddhexout:
270147844Spjd.ifndef BTXLDR_VERBOSE
271147844Spjd		ret
272147844Spjd.endif
273128882Spjdhexout: 	pushl %eax			# Save
274147844Spjd		call putstr			# Display message
275128765Spjd		popl %eax			# Restore
276147844Spjd		pushl %esi			# Save
277147844Spjd		pushl %edi			#  caller's
278147844Spjd		movl $buf,%edi			# Buffer
279147844Spjd		pushl %edi			# Save
280147844Spjd		call hex32			# To hex
281147844Spjd		xorb %al,%al			# Terminate
282147844Spjd		stosb				#  string
283147844Spjd		popl %esi			# Restore
284147844Spjdhexout.1:	lodsb				# Get a char
285147844Spjd		cmpb $'0',%al			# Leading zero?
286147844Spjd		je hexout.1			# Yes
287147844Spjd		testb %al,%al			# End of string?
288147844Spjd		jne hexout.2			# No
289147844Spjd		decl %esi			# Undo
290147844Spjdhexout.2:	decl %esi			# Adjust for inc
291147844Spjd		call putstr			# Display hex
292147844Spjd		popl %edi			# Restore
293147844Spjd		popl %esi			#  caller's
294147844Spjd		ret				# To caller
295147844Spjd#
296147844Spjd# Output zero-terminated string [ESI] to the console.
297147844Spjd#
298147844Spjddputstr:
299147844Spjd.ifndef BTXLDR_VERBOSE
300147844Spjd		ret
301147844Spjd.else
302147844Spjd		jmp putstr
303147844Spjd.endif
304147844Spjdputstr.0:	call putchr			# Output char
305147844Spjdputstr: 	lodsb				# Load char
306147844Spjd		testb %al,%al			# End of string?
307147844Spjd		jne putstr.0			# No
308147844Spjd		ret				# To caller
309147844Spjd#
310147844Spjd# Output character AL to the console.
311147844Spjd#
312147844Spjddputchr:
313147844Spjd.ifndef BTXLDR_VERBOSE
314147844Spjd		ret
315147844Spjd.endif
316147844Spjdputchr: 	pusha				# Save
317147844Spjd		xorl %ecx,%ecx			# Zero for loops
318147844Spjd		movb $SCR_MAT,%ah		# Mode/attribute
319147844Spjd		movl $BDA_POS,%ebx		# BDA pointer
320147844Spjd		movw (%ebx),%dx 		# Cursor position
321147844Spjd.ifdef PC98
322147844Spjd		movl $0xa0000,%edi		# Regen buffer (color)
323147844Spjd.else
324147844Spjd		movl $0xb8000,%edi		# Regen buffer (color)
325147844Spjd		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
326147844Spjd		jne putchr.1			# No
327147844Spjd		xorw %di,%di			# Regen buffer (mono)
328147844Spjd.endif
329147844Spjdputchr.1:	cmpb $0xa,%al			# New line?
330147844Spjd		je putchr.2			# Yes
331147844Spjd.ifdef PC98
332147844Spjd		movw %dx,%cx
333147844Spjd		movb %al,(%edi,%ecx,1)		# Write char
334147844Spjd		addl $0x2000,%ecx
335147844Spjd		movb %ah,(%edi,%ecx,1)		# Write attr
336147844Spjd		addw $0x2,%dx
337147844Spjd		jmp putchr.3
338147844Spjdputchr.2:	movw %dx,%ax
339147844Spjd		movb $SCR_COL*2,%dl
340147844Spjd		div %dl
341147844Spjd		incb %al
342147844Spjd		mul %dl
343147844Spjd		movw %ax,%dx
344147844Spjdputchr.3:	cmpw $SCR_COL*SCR_ROW*2,%dx
345147844Spjd.else
346147844Spjd		xchgl %eax,%ecx 		# Save char
347147844Spjd		movb $SCR_COL,%al		# Columns per row
348147844Spjd		mulb %dh			#  * row position
349147844Spjd		addb %dl,%al			#  + column
350147844Spjd		adcb $0x0,%ah			#  position
351147844Spjd		shll %eax			#  * 2
352147844Spjd		xchgl %eax,%ecx 		# Swap char, offset
353147844Spjd		movw %ax,(%edi,%ecx,1)		# Write attr:char
354128765Spjd		incl %edx			# Bump cursor
355128765Spjd		cmpb $SCR_COL,%dl		# Beyond row?
356128765Spjd		jb putchr.3			# No
357128765Spjdputchr.2:	xorb %dl,%dl			# Zero column
358128765Spjd		incb %dh			# Bump row
359128765Spjdputchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
360128765Spjd.endif
361128765Spjd		jb putchr.4			# No
362128765Spjd		leal 2*SCR_COL(%edi),%esi	# New top line
363128765Spjd		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
364128765Spjd		rep				# Scroll
365128765Spjd		movsl				#  screen
366128765Spjd		movb $' ',%al			# Space
367128765Spjd.ifdef PC98
368128765Spjd		xorb %ah,%ah
369147844Spjd.endif
370147844Spjd		movb $SCR_COL,%cl		# Columns to clear
371147844Spjd		rep				# Clear
372147844Spjd		stosw				#  line
373147844Spjd.ifdef PC98
374147844Spjd		movw $(SCR_ROW-1)*SCR_COL*2,%dx
375147844Spjdputchr.4:	movw %dx,(%ebx) 		# Update position
376147844Spjd		shrw $1,%dx
377147844Spjdgdcwait.3:	inb $0x60,%al
378147844Spjd		testb $0x04,%al
379147844Spjd		jz gdcwait.3
380147844Spjd		movb $0x49,%al
381147844Spjd		outb %al,$0x62
382147844Spjd		movb %dl,%al
383147844Spjd		outb %al,$0x60
384147844Spjd		movb %dh,%al
385147844Spjd		outb %al,$0x60
386147844Spjd.else
387147844Spjd		movb $SCR_ROW-1,%dh		# Bottom line
388147844Spjdputchr.4:	movw %dx,(%ebx) 		# Update position
389147844Spjd.endif
390147844Spjd		popa				# Restore
391128765Spjd		ret				# To caller
392147844Spjd#
393128765Spjd# Convert EAX, AX, or AL to hex, saving the result to [EDI].
394147844Spjd#
395128765Spjdhex32:		pushl %eax			# Save
396147844Spjd		shrl $0x10,%eax 		# Do upper
397147844Spjd		call hex16			#  16
398147844Spjd		popl %eax			# Restore
399147844Spjdhex16:		call hex16.1			# Do upper 8
400147844Spjdhex16.1:	xchgb %ah,%al			# Save/restore
401147844Spjdhex8:		pushl %eax			# Save
402147844Spjd		shrb $0x4,%al			# Do upper
403147844Spjd		call hex8.1			#  4
404147844Spjd		popl %eax			# Restore
405147844Spjdhex8.1: 	andb $0xf,%al			# Get lower 4
406147844Spjd		cmpb $0xa,%al			# Convert
407147844Spjd		sbbb $0x69,%al			#  to hex
408128765Spjd		das				#  digit
409128765Spjd		orb $0x20,%al			# To lower case
410128765Spjd		stosb				# Save char
411147844Spjd		ret				# (Recursive)
412147844Spjd
413147844Spjd		.data
414147844Spjd		.p2align 4
415147844Spjd#
416147844Spjd# Global descriptor table.
417147844Spjd#
418147844Spjdgdt:		.word 0x0,0x0,0x0,0x0		# Null entry
419147844Spjd		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
420147844Spjd		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
421147844Spjd		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
422147844Spjd		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
423147844Spjdgdt.1:
424147844Spjdgdtdesc:	.word gdt.1-gdt-1		# Limit
425147844Spjd		.long gdt			# Base
426147844Spjd#
427147844Spjd# Messages.
428147844Spjd#
429147844Spjdm_logo: 	.asciz "\nBTX loader 1.00  "
430147844Spjdm_vers: 	.asciz "BTX version is \0\n"
431147844Spjde_fmt:		.asciz "Error: Client format not supported\n"
432147844Spjd#.ifdef BTXLDR_VERBOSE
433147844Spjdm_mem:		.asciz "Starting in protected mode (base mem=\0)\n"
434147844Spjdm_esp:		.asciz "Arguments passed (esp=\0):\n"
435147844Spjdm_args: 	.asciz"<howto="
436147844Spjd		.asciz" bootdev="
437147844Spjd		.asciz" junk="
438147844Spjd		.asciz" "
439147844Spjd		.asciz" "
440128765Spjd		.asciz" bootinfo=\0>\n"
441128765Spjdm_rel_bi:	.asciz "Relocated bootinfo (size=48) to \0\n"
442128765Spjdm_rel_args:	.asciz "Relocated arguments (size=18) to \0\n"
443128765Spjdm_rel_btx:	.asciz "Relocated kernel (size=\0) to \0\n"
444147844Spjdm_base: 	.asciz "Client base address is \0\n"
445147844Spjdm_elf:		.asciz "Client format is ELF\n"
446147844Spjdm_segs: 	.asciz "text segment: offset="
447147844Spjd		.asciz " vaddr="
448147844Spjd		.asciz " filesz="
449147844Spjd		.asciz " memsz=\0\n"
450128765Spjd		.asciz "data segment: offset="
451128765Spjd		.asciz " vaddr="
452128765Spjd		.asciz " filesz="
453128765Spjd		.asciz " memsz=\0\n"
454128765Spjdm_done: 	.asciz "Loading complete\n"
455128765Spjd#.endif
456128765Spjd#
457128765Spjd# Uninitialized data area.
458128765Spjd#
459128765Spjdbuf:						# Scratch buffer
460156590Spjd