btxldr.S revision 43561
1#
2# Copyright (c) 1998 Robert Nordier
3# All rights reserved.
4#
5# Redistribution and use in source and binary forms are freely
6# permitted provided that the above copyright notice and this
7# paragraph and the following disclaimer are duplicated in all
8# such forms.
9#
10# This software is provided "AS IS" and without any express or
11# implied warranties, including, without limitation, the implied
12# warranties of merchantability and fitness for a particular
13# purpose.
14#
15
16#	$Id: btxldr.s,v 1.5 1999/01/22 13:07:17 rnordier Exp $
17
18#
19# Prototype BTX loader program, written in a couple of hours.  The
20# real thing should probably be more flexible, and in C.
21#
22
23#
24# Memory locations.
25#
26		.set MEM_STUB,0x600		# Real mode stub
27		.set MEM_ESP,0x1000		# New stack pointer
28		.set MEM_TBL,0x5000		# BTX page tables
29		.set MEM_ENTRY,0x9010		# BTX entry point
30		.set MEM_DATA,0x101000		# Data segment
31#
32# Segment selectors.
33#
34		.set SEL_SCODE,0x8		# 4GB code
35		.set SEL_SDATA,0x10		# 4GB data
36		.set SEL_RCODE,0x18		# 64K code
37		.set SEL_RDATA,0x20		# 64K data
38#
39# Paging constants.
40#
41		.set PAG_SIZ,0x1000		# Page size
42		.set PAG_ENT,0x4		# Page entry size
43#
44# Screen constants.
45#
46.ifdef PC98
47		.set SCR_MAT,0xe1		# Mode/attribute
48.else
49		.set SCR_MAT,0x7		# Mode/attribute
50.endif
51		.set SCR_COL,0x50		# Columns per row
52		.set SCR_ROW,0x19		# Rows per screen
53#
54# BIOS Data Area locations.
55#
56.ifdef PC98
57		.set BDA_MEM,0xa1501		# Free memory
58		.set BDA_POS,0xa153e		# Cursor position
59.else
60		.set BDA_MEM,0x413		# Free memory
61		.set BDA_SCR,0x449		# Video mode
62		.set BDA_POS,0x450		# Cursor position
63.endif
64#
65# Required by aout gas inadequacy.
66#
67		.set SIZ_STUB,0x1a		# Size of stub
68#
69# We expect to be loaded by boot2 at 0x100000.
70#
71		.globl start
72#
73# BTX program loader for ELF clients.
74#
75start:		cld				# String ops inc
76.ifdef PC98
77		cli
78gdcwait.1:	inb $0x60,%al
79		testb $0x04,%al
80		jz gdcwait.1
81		movb $0xe0,%al
82		outb %al,$0x62
83		nop
84gdcwait.2:	inb $0x60,%al
85		testb $0x01,%al
86		jz gdcwait.2
87		inb $0x62,%al
88		movb %al,%dl
89		inb $0x62,%al
90		movb %al,%dh
91		inb $0x62,%al
92		inb $0x62,%al
93		inb $0x62,%al
94		shlw $1,%dx
95		movl $BDA_POS,%ebx
96		movw %dx,(%ebx)
97.endif
98		movl $m_logo,%esi		# Identify
99		call putstr			#  ourselves
100		movzwl BDA_MEM,%eax		# Get base memory
101.ifdef PC98
102		andl $0x7,%eax
103		incl %eax
104		shll $0x11,%eax			#  in bytes
105.else
106		shll $0xa,%eax			#  in bytes
107.endif
108		movl %eax,%ebp			# Base of user stack
109		movl $m_mem,%esi		# Display
110		call dhexout			#  amount of
111		call dputstr			#  base memory
112		lgdt gdtdesc			# Load new GDT
113#
114# Relocate caller's arguments.
115#
116		movl $m_esp,%esi		# Display
117		movl %esp,%eax			#  caller's
118		call dhexout			#  stack
119		call dputstr			#  pointer
120		movl $m_args,%esi		# Format string
121		leal 0x4(%esp,1),%ebx		# First argument
122		movl $0x6,%ecx			# Count
123start.1:	movl (%ebx),%eax		# Get argument and
124		addl $0x4,%ebx			#  bump pointer
125		call dhexout			# Display it
126		loop start.1			# Till done
127		call dputstr			# End message
128		movl $0x48,%ecx 		# Allocate space
129		subl %ecx,%ebp			#  for bootinfo
130		movl 0x18(%esp,1),%esi		# Source
131		movl %ebp,%edi			# Destination
132		rep				# Copy
133		movsb				#  it
134		movl %ebp,0x18(%esp,1)		# Update pointer
135		movl $m_rel_bi,%esi		# Display
136		movl %ebp,%eax			#  bootinfo
137		call dhexout			#  relocation
138		call dputstr			#  message
139		movl $0x18,%ecx 		# Allocate space
140		subl %ecx,%ebp			#  for arguments
141		leal 0x4(%esp,1),%esi		# Source
142		movl %ebp,%edi			# Destination
143		rep				# Copy
144		movsb				#  them
145		movl $m_rel_args,%esi		# Display
146		movl %ebp,%eax			#  argument
147		call dhexout			#  relocation
148		call dputstr			#  message
149#
150# Set up BTX kernel.
151#
152		movl $MEM_ESP,%esp		# Set up new stack
153		movl $MEM_DATA,%ebx		# Data segment
154		movl $m_vers,%esi		# Display BTX
155		call putstr			#  version message
156		movb 0x5(%ebx),%al		# Get major version
157		addb $'0',%al			# Display
158		call putchr			#  it
159		movb $'.',%al			# And a
160		call putchr			#  dot
161		movb 0x6(%ebx),%al		# Get minor
162		xorb %ah,%ah			#  version
163		movb $0xa,%dl			# Divide
164		divb %dl,%al			#  by 10
165		addb $'0',%al			# Display
166		call putchr			#  tens
167		movb %ah,%al			# Get units
168		addb $'0',%al			# Display
169		call putchr			#  units
170		call putstr			# End message
171		movl %ebx,%esi			# BTX image
172		movzwl 0x8(%ebx),%edi		# Compute
173		orl $PAG_SIZ/PAG_ENT-1,%edi	#  the
174		incl %edi			#  BTX
175		shll $0x2,%edi			#  load
176		addl $MEM_TBL,%edi		#  address
177		pushl %edi			# Save
178		movzwl 0xa(%ebx),%ecx		# Image size
179		pushl %ecx			# Save
180		rep				# Relocate
181		movsb				#  BTX
182		movl %esi,%ebx			# Keep place
183		movl $m_rel_btx,%esi		# Restore
184		popl %eax			#  parameters
185		call dhexout			#  and
186		popl %ebp			#  display
187		movl %ebp,%eax			#  the
188		call dhexout			#  relocation
189		call dputstr			#  message
190		addl $PAG_SIZ,%ebp		# Display
191		movl $m_base,%esi		#  the
192		movl %ebp,%eax			#  user
193		call dhexout			#  base
194		call dputstr			#  address
195#
196# Set up ELF-format client program.
197#
198		cmpl $0x464c457f,(%ebx) 	# ELF magic number?
199		je start.3			# Yes
200		movl $e_fmt,%esi		# Display error
201		call putstr			#  message
202start.2:	jmp start.2			# Hang
203start.3:	movl $m_elf,%esi		# Display ELF
204		call dputstr			#  message
205		movl $m_segs,%esi		# Format string
206		movl $0x2,%edi			# Segment count
207		movl 0x1c(%ebx),%edx		# Get e_phoff
208		addl %ebx,%edx			# To pointer
209		movzwl 0x2c(%ebx),%ecx		# Get e_phnum
210start.4:	cmpl $0x1,(%edx)		# Is p_type PT_LOAD?
211		jne start.6			# No
212		movl 0x4(%edx),%eax		# Display
213		call dhexout			#  p_offset
214		movl 0x8(%edx),%eax		# Display
215		call dhexout			#  p_vaddr
216		movl 0x10(%edx),%eax		# Display
217		call dhexout			#  p_filesz
218		movl 0x14(%edx),%eax		# Display
219		call dhexout			#  p_memsz
220		call dputstr			# End message
221		pushl %esi			# Save
222		pushl %edi			#  working
223		pushl %ecx			#  registers
224		movl 0x4(%edx),%esi		# Get p_offset
225		addl %ebx,%esi			#  as pointer
226		movl 0x8(%edx),%edi		# Get p_vaddr
227		addl %ebp,%edi			#  as pointer
228		movl 0x10(%edx),%ecx		# Get p_filesz
229		rep				# Set up
230		movsb				#  segment
231		movl 0x14(%edx),%ecx		# Any bytes
232		subl 0x10(%edx),%ecx		#  to zero?
233		jz start.5			# No
234		xorb %al,%al			# Then
235		rep				#  zero
236		stosb				#  them
237start.5:	popl %ecx			# Restore
238		popl %edi			#  working
239		popl %esi			#  registers
240		decl %edi			# Segments to do
241		je start.7			# If none
242start.6:	addl $0x20,%edx 		# To next entry
243		loop start.4			# Till done
244start.7:	movl $m_done,%esi		# Display done
245		call dputstr			#  message
246		movl $start.8,%esi		# Real mode stub
247		movl $MEM_STUB,%edi		# Destination
248		movl $SIZ_STUB,%ecx		# Size
249		rep				# Relocate
250		movsb				#  it
251		ljmp $SEL_RCODE,$MEM_STUB	# To 16-bit code
252start.8:	xorl %eax,%eax			# Data
253		movb $SEL_RDATA,%al		#  selector
254		movl %eax,%ss			# Reload SS
255		movl %eax,%ds			# Reset
256		movl %eax,%es			#  other
257		movl %eax,%fs			#  segment
258		movl %eax,%gs			#  limits
259		movl %cr0,%eax			# Switch to
260		decl %eax			#  real
261		movl %eax,%cr0			#  mode
262		.byte 0xea			# Jump to
263		.word MEM_ENTRY 		# BTX entry
264		.word 0x0			#  point
265start.9:
266#
267# Output message [ESI] followed by EAX in hex.
268#
269dhexout:
270.ifndef BTXLDR_VERBOSE
271		ret
272.endif
273hexout: 	pushl %eax			# Save
274		call putstr			# Display message
275		popl %eax			# Restore
276		pushl %esi			# Save
277		pushl %edi			#  caller's
278		movl $buf,%edi			# Buffer
279		pushl %edi			# Save
280		call hex32			# To hex
281		xorb %al,%al			# Terminate
282		stosb				#  string
283		popl %esi			# Restore
284hexout.1:	lodsb				# Get a char
285		cmpb $'0',%al			# Leading zero?
286		je hexout.1			# Yes
287		testb %al,%al			# End of string?
288		jne hexout.2			# No
289		decl %esi			# Undo
290hexout.2:	decl %esi			# Adjust for inc
291		call putstr			# Display hex
292		popl %edi			# Restore
293		popl %esi			#  caller's
294		ret				# To caller
295#
296# Output zero-terminated string [ESI] to the console.
297#
298dputstr:
299.ifndef BTXLDR_VERBOSE
300		ret
301.else
302		jmp putstr
303.endif
304putstr.0:	call putchr			# Output char
305putstr: 	lodsb				# Load char
306		testb %al,%al			# End of string?
307		jne putstr.0			# No
308		ret				# To caller
309#
310# Output character AL to the console.
311#
312dputchr:
313.ifndef BTXLDR_VERBOSE
314		ret
315.endif
316putchr: 	pusha				# Save
317		xorl %ecx,%ecx			# Zero for loops
318		movb $SCR_MAT,%ah		# Mode/attribute
319		movl $BDA_POS,%ebx		# BDA pointer
320		movw (%ebx),%dx 		# Cursor position
321.ifdef PC98
322		movl $0xa0000,%edi		# Regen buffer (color)
323.else
324		movl $0xb8000,%edi		# Regen buffer (color)
325		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
326		jne putchr.1			# No
327		xorw %di,%di			# Regen buffer (mono)
328.endif
329putchr.1:	cmpb $0xa,%al			# New line?
330		je putchr.2			# Yes
331.ifdef PC98
332		movw %dx,%cx
333		movb %al,(%edi,%ecx,1)		# Write char
334		addl $0x2000,%ecx
335		movb %ah,(%edi,%ecx,1)		# Write attr
336		addw $0x2,%dx
337		jmp putchr.3
338putchr.2:	movw %dx,%ax
339		movb $SCR_COL*2,%dl
340		div %dl
341		incb %al
342		mul %dl
343		movw %ax,%dx
344putchr.3:	cmpw $SCR_COL*SCR_ROW*2,%dx
345.else
346		xchgl %eax,%ecx 		# Save char
347		movb $SCR_COL,%al		# Columns per row
348		mulb %dh			#  * row position
349		addb %dl,%al			#  + column
350		adcb $0x0,%ah			#  position
351		shll %eax			#  * 2
352		xchgl %eax,%ecx 		# Swap char, offset
353		movw %ax,(%edi,%ecx,1)		# Write attr:char
354		incl %edx			# Bump cursor
355		cmpb $SCR_COL,%dl		# Beyond row?
356		jb putchr.3			# No
357putchr.2:	xorb %dl,%dl			# Zero column
358		incb %dh			# Bump row
359putchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
360.endif
361		jb putchr.4			# No
362		leal 2*SCR_COL(%edi),%esi	# New top line
363		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
364		rep				# Scroll
365		movsl				#  screen
366		movb $' ',%al			# Space
367.ifdef PC98
368		xorb %ah,%ah
369.endif
370		movb $SCR_COL,%cl		# Columns to clear
371		rep				# Clear
372		stosw				#  line
373.ifdef PC98
374		movw $(SCR_ROW-1)*SCR_COL*2,%dx
375putchr.4:	movw %dx,(%ebx) 		# Update position
376		shrw $1,%dx
377gdcwait.3:	inb $0x60,%al
378		testb $0x04,%al
379		jz gdcwait.3
380		movb $0x49,%al
381		outb %al,$0x62
382		movb %dl,%al
383		outb %al,$0x60
384		movb %dh,%al
385		outb %al,$0x60
386.else
387		movb $SCR_ROW-1,%dh		# Bottom line
388putchr.4:	movw %dx,(%ebx) 		# Update position
389.endif
390		popa				# Restore
391		ret				# To caller
392#
393# Convert EAX, AX, or AL to hex, saving the result to [EDI].
394#
395hex32:		pushl %eax			# Save
396		shrl $0x10,%eax 		# Do upper
397		call hex16			#  16
398		popl %eax			# Restore
399hex16:		call hex16.1			# Do upper 8
400hex16.1:	xchgb %ah,%al			# Save/restore
401hex8:		pushl %eax			# Save
402		shrb $0x4,%al			# Do upper
403		call hex8.1			#  4
404		popl %eax			# Restore
405hex8.1: 	andb $0xf,%al			# Get lower 4
406		cmpb $0xa,%al			# Convert
407		sbbb $0x69,%al			#  to hex
408		das				#  digit
409		orb $0x20,%al			# To lower case
410		stosb				# Save char
411		ret				# (Recursive)
412
413		.data
414		.p2align 4
415#
416# Global descriptor table.
417#
418gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
419		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
420		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
421		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
422		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
423gdt.1:
424gdtdesc:	.word gdt.1-gdt-1		# Limit
425		.long gdt			# Base
426#
427# Messages.
428#
429m_logo: 	.asciz "\nBTX loader 1.00  "
430m_vers: 	.asciz "BTX version is \0\n"
431e_fmt:		.asciz "Error: Client format not supported\n"
432#.ifdef BTXLDR_VERBOSE
433m_mem:		.asciz "Starting in protected mode (base mem=\0)\n"
434m_esp:		.asciz "Arguments passed (esp=\0):\n"
435m_args: 	.asciz"<howto="
436		.asciz" bootdev="
437		.asciz" junk="
438		.asciz" "
439		.asciz" "
440		.asciz" bootinfo=\0>\n"
441m_rel_bi:	.asciz "Relocated bootinfo (size=48) to \0\n"
442m_rel_args:	.asciz "Relocated arguments (size=18) to \0\n"
443m_rel_btx:	.asciz "Relocated kernel (size=\0) to \0\n"
444m_base: 	.asciz "Client base address is \0\n"
445m_elf:		.asciz "Client format is ELF\n"
446m_segs: 	.asciz "text segment: offset="
447		.asciz " vaddr="
448		.asciz " filesz="
449		.asciz " memsz=\0\n"
450		.asciz "data segment: offset="
451		.asciz " vaddr="
452		.asciz " filesz="
453		.asciz " memsz=\0\n"
454m_done: 	.asciz "Loading complete\n"
455#.endif
456#
457# Uninitialized data area.
458#
459buf:						# Scratch buffer
460