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