btxldr.S revision 56693
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# $FreeBSD: head/sys/boot/i386/btx/btxldr/btxldr.S 56693 2000-01-27 21:21:01Z jhb $
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		.set SCR_MAT,0x7		# Mode/attribute
47		.set SCR_COL,0x50		# Columns per row
48		.set SCR_ROW,0x19		# Rows per screen
49#
50# BIOS Data Area locations.
51#
52		.set BDA_MEM,0x413		# Free memory
53		.set BDA_SCR,0x449		# Video mode
54		.set BDA_POS,0x450		# Cursor position
55#
56# Required by aout gas inadequacy.
57#
58		.set SIZ_STUB,0x1a		# Size of stub
59#
60# We expect to be loaded by boot2 at 0x100000.
61#
62		.globl start
63#
64# BTX program loader for ELF clients.
65#
66start:		cld				# String ops inc
67		movl $m_logo,%esi		# Identify
68		call putstr			#  ourselves
69		movzwl BDA_MEM,%eax		# Get base memory
70		shll $0xa,%eax			#  in bytes
71		movl %eax,%ebp			# Base of user stack
72		movl $m_mem,%esi		# Display
73		call dhexout			#  amount of
74		call dputstr			#  base memory
75		lgdt gdtdesc			# Load new GDT
76#
77# Relocate caller's arguments.
78#
79		movl $m_esp,%esi		# Display
80		movl %esp,%eax			#  caller's
81		call dhexout			#  stack
82		call dputstr			#  pointer
83		movl $m_args,%esi		# Format string
84		leal 0x4(%esp,1),%ebx		# First argument
85		movl $0x6,%ecx			# Count
86start.1:	movl (%ebx),%eax		# Get argument and
87		addl $0x4,%ebx			#  bump pointer
88		call dhexout			# Display it
89		loop start.1			# Till done
90		call dputstr			# End message
91		movl $0x48,%ecx 		# Allocate space
92		subl %ecx,%ebp			#  for bootinfo
93		movl 0x18(%esp,1),%esi		# Source: bootinfo
94		cmpl $0x0, %esi			# If the bootinfo pointer
95		je start_null_bi		#  is null, don't copy it
96		movl %ebp,%edi			# Destination
97		rep				# Copy
98		movsb				#  it
99		movl %ebp,0x18(%esp,1)		# Update pointer
100		movl $m_rel_bi,%esi		# Display
101		movl %ebp,%eax			#  bootinfo
102		call dhexout			#  relocation
103		call dputstr			#  message
104start_null_bi:	movl $0x18,%ecx 		# Allocate space
105		subl %ecx,%ebp			#  for arguments
106		leal 0x4(%esp,1),%esi		# Source
107		movl %ebp,%edi			# Destination
108		rep				# Copy
109		movsb				#  them
110		movl $m_rel_args,%esi		# Display
111		movl %ebp,%eax			#  argument
112		call dhexout			#  relocation
113		call dputstr			#  message
114#
115# Set up BTX kernel.
116#
117		movl $MEM_ESP,%esp		# Set up new stack
118		movl $MEM_DATA,%ebx		# Data segment
119		movl $m_vers,%esi		# Display BTX
120		call putstr			#  version message
121		movb 0x5(%ebx),%al		# Get major version
122		addb $'0',%al			# Display
123		call putchr			#  it
124		movb $'.',%al			# And a
125		call putchr			#  dot
126		movb 0x6(%ebx),%al		# Get minor
127		xorb %ah,%ah			#  version
128		movb $0xa,%dl			# Divide
129		divb %dl,%al			#  by 10
130		addb $'0',%al			# Display
131		call putchr			#  tens
132		movb %ah,%al			# Get units
133		addb $'0',%al			# Display
134		call putchr			#  units
135		call putstr			# End message
136		movl %ebx,%esi			# BTX image
137		movzwl 0x8(%ebx),%edi		# Compute
138		orl $PAG_SIZ/PAG_ENT-1,%edi	#  the
139		incl %edi			#  BTX
140		shll $0x2,%edi			#  load
141		addl $MEM_TBL,%edi		#  address
142		pushl %edi			# Save
143		movzwl 0xa(%ebx),%ecx		# Image size
144		pushl %ecx			# Save
145		rep				# Relocate
146		movsb				#  BTX
147		movl %esi,%ebx			# Keep place
148		movl $m_rel_btx,%esi		# Restore
149		popl %eax			#  parameters
150		call dhexout			#  and
151		popl %ebp			#  display
152		movl %ebp,%eax			#  the
153		call dhexout			#  relocation
154		call dputstr			#  message
155		addl $PAG_SIZ,%ebp		# Display
156		movl $m_base,%esi		#  the
157		movl %ebp,%eax			#  user
158		call dhexout			#  base
159		call dputstr			#  address
160#
161# Set up ELF-format client program.
162#
163		cmpl $0x464c457f,(%ebx) 	# ELF magic number?
164		je start.3			# Yes
165		movl $e_fmt,%esi		# Display error
166		call putstr			#  message
167start.2:	jmp start.2			# Hang
168start.3:	movl $m_elf,%esi		# Display ELF
169		call dputstr			#  message
170		movl $m_segs,%esi		# Format string
171		movl $0x2,%edi			# Segment count
172		movl 0x1c(%ebx),%edx		# Get e_phoff
173		addl %ebx,%edx			# To pointer
174		movzwl 0x2c(%ebx),%ecx		# Get e_phnum
175start.4:	cmpl $0x1,(%edx)		# Is p_type PT_LOAD?
176		jne start.6			# No
177		movl 0x4(%edx),%eax		# Display
178		call dhexout			#  p_offset
179		movl 0x8(%edx),%eax		# Display
180		call dhexout			#  p_vaddr
181		movl 0x10(%edx),%eax		# Display
182		call dhexout			#  p_filesz
183		movl 0x14(%edx),%eax		# Display
184		call dhexout			#  p_memsz
185		call dputstr			# End message
186		pushl %esi			# Save
187		pushl %edi			#  working
188		pushl %ecx			#  registers
189		movl 0x4(%edx),%esi		# Get p_offset
190		addl %ebx,%esi			#  as pointer
191		movl 0x8(%edx),%edi		# Get p_vaddr
192		addl %ebp,%edi			#  as pointer
193		movl 0x10(%edx),%ecx		# Get p_filesz
194		rep				# Set up
195		movsb				#  segment
196		movl 0x14(%edx),%ecx		# Any bytes
197		subl 0x10(%edx),%ecx		#  to zero?
198		jz start.5			# No
199		xorb %al,%al			# Then
200		rep				#  zero
201		stosb				#  them
202start.5:	popl %ecx			# Restore
203		popl %edi			#  working
204		popl %esi			#  registers
205		decl %edi			# Segments to do
206		je start.7			# If none
207start.6:	addl $0x20,%edx 		# To next entry
208		loop start.4			# Till done
209start.7:	movl $m_done,%esi		# Display done
210		call dputstr			#  message
211		movl $start.8,%esi		# Real mode stub
212		movl $MEM_STUB,%edi		# Destination
213		movl $SIZ_STUB,%ecx		# Size
214		rep				# Relocate
215		movsb				#  it
216		ljmp $SEL_RCODE,$MEM_STUB	# To 16-bit code
217start.8:	xorl %eax,%eax			# Data
218		movb $SEL_RDATA,%al		#  selector
219		movl %eax,%ss			# Reload SS
220		movl %eax,%ds			# Reset
221		movl %eax,%es			#  other
222		movl %eax,%fs			#  segment
223		movl %eax,%gs			#  limits
224		movl %cr0,%eax			# Switch to
225		decl %eax			#  real
226		movl %eax,%cr0			#  mode
227		.byte 0xea			# Jump to
228		.word MEM_ENTRY 		# BTX entry
229		.word 0x0			#  point
230start.9:
231#
232# Output message [ESI] followed by EAX in hex.
233#
234dhexout:
235#ifndef BTXLDR_VERBOSE
236		ret
237#endif
238hexout: 	pushl %eax			# Save
239		call putstr			# Display message
240		popl %eax			# Restore
241		pushl %esi			# Save
242		pushl %edi			#  caller's
243		movl $buf,%edi			# Buffer
244		pushl %edi			# Save
245		call hex32			# To hex
246		xorb %al,%al			# Terminate
247		stosb				#  string
248		popl %esi			# Restore
249hexout.1:	lodsb				# Get a char
250		cmpb $'0',%al			# Leading zero?
251		je hexout.1			# Yes
252		testb %al,%al			# End of string?
253		jne hexout.2			# No
254		decl %esi			# Undo
255hexout.2:	decl %esi			# Adjust for inc
256		call putstr			# Display hex
257		popl %edi			# Restore
258		popl %esi			#  caller's
259		ret				# To caller
260#
261# Output zero-terminated string [ESI] to the console.
262#
263dputstr:
264#ifndef BTXLDR_VERBOSE
265		ret
266#else
267		jmp putstr
268#endif
269putstr.0:	call putchr			# Output char
270putstr: 	lodsb				# Load char
271		testb %al,%al			# End of string?
272		jne putstr.0			# No
273		ret				# To caller
274#
275# Output character AL to the console.
276#
277dputchr:
278#ifndef BTXLDR_VERBOSE
279		ret
280#endif
281putchr: 	pusha				# Save
282		xorl %ecx,%ecx			# Zero for loops
283		movb $SCR_MAT,%ah		# Mode/attribute
284		movl $BDA_POS,%ebx		# BDA pointer
285		movw (%ebx),%dx 		# Cursor position
286		movl $0xb8000,%edi		# Regen buffer (color)
287		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
288		jne putchr.1			# No
289		xorw %di,%di			# Regen buffer (mono)
290putchr.1:	cmpb $0xa,%al			# New line?
291		je putchr.2			# Yes
292		xchgl %eax,%ecx 		# Save char
293		movb $SCR_COL,%al		# Columns per row
294		mulb %dh			#  * row position
295		addb %dl,%al			#  + column
296		adcb $0x0,%ah			#  position
297		shll %eax			#  * 2
298		xchgl %eax,%ecx 		# Swap char, offset
299		movw %ax,(%edi,%ecx,1)		# Write attr:char
300		incl %edx			# Bump cursor
301		cmpb $SCR_COL,%dl		# Beyond row?
302		jb putchr.3			# No
303putchr.2:	xorb %dl,%dl			# Zero column
304		incb %dh			# Bump row
305putchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
306		jb putchr.4			# No
307		leal 2*SCR_COL(%edi),%esi	# New top line
308		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
309		rep				# Scroll
310		movsl				#  screen
311		movb $' ',%al			# Space
312		movb $SCR_COL,%cl		# Columns to clear
313		rep				# Clear
314		stosw				#  line
315		movb $SCR_ROW-1,%dh		# Bottom line
316putchr.4:	movw %dx,(%ebx) 		# Update position
317		popa				# Restore
318		ret				# To caller
319#
320# Convert EAX, AX, or AL to hex, saving the result to [EDI].
321#
322hex32:		pushl %eax			# Save
323		shrl $0x10,%eax 		# Do upper
324		call hex16			#  16
325		popl %eax			# Restore
326hex16:		call hex16.1			# Do upper 8
327hex16.1:	xchgb %ah,%al			# Save/restore
328hex8:		pushl %eax			# Save
329		shrb $0x4,%al			# Do upper
330		call hex8.1			#  4
331		popl %eax			# Restore
332hex8.1: 	andb $0xf,%al			# Get lower 4
333		cmpb $0xa,%al			# Convert
334		sbbb $0x69,%al			#  to hex
335		das				#  digit
336		orb $0x20,%al			# To lower case
337		stosb				# Save char
338		ret				# (Recursive)
339
340		.data
341		.p2align 4
342#
343# Global descriptor table.
344#
345gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
346		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
347		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
348		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
349		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
350gdt.1:
351gdtdesc:	.word gdt.1-gdt-1		# Limit
352		.long gdt			# Base
353#
354# Messages.
355#
356m_logo: 	.asciz " \nBTX loader 1.00  "
357m_vers: 	.asciz "BTX version is \0\n"
358e_fmt:		.asciz "Error: Client format not supported\n"
359#ifdef BTXLDR_VERBOSE
360m_mem:		.asciz "Starting in protected mode (base mem=\0)\n"
361m_esp:		.asciz "Arguments passed (esp=\0):\n"
362m_args: 	.asciz"<howto="
363		.asciz" bootdev="
364		.asciz" junk="
365		.asciz" "
366		.asciz" "
367		.asciz" bootinfo=\0>\n"
368m_rel_bi:	.asciz "Relocated bootinfo (size=48) to \0\n"
369m_rel_args:	.asciz "Relocated arguments (size=18) to \0\n"
370m_rel_btx:	.asciz "Relocated kernel (size=\0) to \0\n"
371m_base: 	.asciz "Client base address is \0\n"
372m_elf:		.asciz "Client format is ELF\n"
373m_segs: 	.asciz "text segment: offset="
374		.asciz " vaddr="
375		.asciz " filesz="
376		.asciz " memsz=\0\n"
377		.asciz "data segment: offset="
378		.asciz " vaddr="
379		.asciz " filesz="
380		.asciz " memsz=\0\n"
381m_done: 	.asciz "Loading complete\n"
382#endif
383#
384# Uninitialized data area.
385#
386buf:						# Scratch buffer
387