btxldr.S revision 129514
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 128710 2004-04-28 10:15:31Z ru $
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#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 the origin defined in ./Makefile.
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#ifdef BTXLDR_VERBOSE
110		movl $m_mem,%esi		# Display
111		call hexout			#  amount of
112		call putstr			#  base memory
113#endif
114		lgdt gdtdesc			# Load new GDT
115/*
116 * Relocate caller's arguments.
117 */
118#ifdef BTXLDR_VERBOSE
119		movl $m_esp,%esi		# Display
120		movl %esp,%eax			#  caller
121		call hexout			#  stack
122		call putstr			#  pointer
123		movl $m_args,%esi		# Format string
124		leal 0x4(%esp,1),%ebx		# First argument
125		movl $0x6,%ecx			# Count
126start.1:	movl (%ebx),%eax		# Get argument and
127		addl $0x4,%ebx			#  bump pointer
128		call hexout			# Display it
129		loop start.1			# Till done
130		call putstr			# End message
131#endif
132		movl $0x48,%ecx 		# Allocate space
133		subl %ecx,%ebp			#  for bootinfo
134		movl 0x18(%esp,1),%esi		# Source: bootinfo
135		cmpl $0x0, %esi			# If the bootinfo pointer
136		je start_null_bi		#  is null, don't copy it
137		movl %ebp,%edi			# Destination
138		rep				# Copy
139		movsb				#  it
140		movl %ebp,0x18(%esp,1)		# Update pointer
141#ifdef BTXLDR_VERBOSE
142		movl $m_rel_bi,%esi		# Display
143		movl %ebp,%eax			#  bootinfo
144		call hexout			#  relocation
145		call putstr			#  message
146#endif
147start_null_bi:	movl $0x18,%ecx 		# Allocate space
148		subl %ecx,%ebp			#  for arguments
149		leal 0x4(%esp,1),%esi		# Source
150		movl %ebp,%edi			# Destination
151		rep				# Copy
152		movsb				#  them
153#ifdef BTXLDR_VERBOSE
154		movl $m_rel_args,%esi		# Display
155		movl %ebp,%eax			#  argument
156		call hexout			#  relocation
157		call putstr			#  message
158#endif
159/*
160 * Set up BTX kernel.
161 */
162		movl $MEM_ESP,%esp		# Set up new stack
163		movl $MEM_DATA,%ebx		# Data segment
164		movl $m_vers,%esi		# Display BTX
165		call putstr			#  version message
166		movb 0x5(%ebx),%al		# Get major version
167		addb $'0',%al			# Display
168		call putchr			#  it
169		movb $'.',%al			# And a
170		call putchr			#  dot
171		movb 0x6(%ebx),%al		# Get minor
172		xorb %ah,%ah			#  version
173		movb $0xa,%dl			# Divide
174		divb %dl,%al			#  by 10
175		addb $'0',%al			# Display
176		call putchr			#  tens
177		movb %ah,%al			# Get units
178		addb $'0',%al			# Display
179		call putchr			#  units
180		call putstr			# End message
181		movl %ebx,%esi			# BTX image
182		movzwl 0x8(%ebx),%edi		# Compute
183		orl $PAG_SIZ/PAG_ENT-1,%edi	#  the
184		incl %edi			#  BTX
185		shll $0x2,%edi			#  load
186		addl $MEM_TBL,%edi		#  address
187		pushl %edi			# Save load address
188		movzwl 0xa(%ebx),%ecx		# Image size
189#ifdef BTXLDR_VERBOSE
190		pushl %ecx			# Save image size
191#endif
192		rep				# Relocate
193		movsb				#  BTX
194		movl %esi,%ebx			# Keep place
195#ifdef BTXLDR_VERBOSE
196		movl $m_rel_btx,%esi		# Restore
197		popl %eax			#  parameters
198		call hexout			#  and
199#endif
200		popl %ebp			#  display
201#ifdef BTXLDR_VERBOSE
202		movl %ebp,%eax			#  the
203		call hexout			#  relocation
204		call putstr			#  message
205#endif
206		addl $PAG_SIZ,%ebp		# Display
207#ifdef BTXLDR_VERBOSE
208		movl $m_base,%esi		#  the
209		movl %ebp,%eax			#  user
210		call hexout			#  base
211		call putstr			#  address
212#endif
213/*
214 * Set up ELF-format client program.
215 */
216		cmpl $0x464c457f,(%ebx) 	# ELF magic number?
217		je start.3			# Yes
218		movl $e_fmt,%esi		# Display error
219		call putstr			#  message
220start.2:	jmp start.2			# Hang
221start.3:
222#ifdef BTXLDR_VERBOSE
223		movl $m_elf,%esi		# Display ELF
224		call putstr			#  message
225		movl $m_segs,%esi		# Format string
226#endif
227		movl $0x2,%edi			# Segment count
228		movl 0x1c(%ebx),%edx		# Get e_phoff
229		addl %ebx,%edx			# To pointer
230		movzwl 0x2c(%ebx),%ecx		# Get e_phnum
231start.4:	cmpl $0x1,(%edx)		# Is p_type PT_LOAD?
232		jne start.6			# No
233#ifdef BTXLDR_VERBOSE
234		movl 0x4(%edx),%eax		# Display
235		call hexout			#  p_offset
236		movl 0x8(%edx),%eax		# Display
237		call hexout			#  p_vaddr
238		movl 0x10(%edx),%eax		# Display
239		call hexout			#  p_filesz
240		movl 0x14(%edx),%eax		# Display
241		call hexout			#  p_memsz
242		call putstr			# End message
243#endif
244		pushl %esi			# Save
245		pushl %edi			#  working
246		pushl %ecx			#  registers
247		movl 0x4(%edx),%esi		# Get p_offset
248		addl %ebx,%esi			#  as pointer
249		movl 0x8(%edx),%edi		# Get p_vaddr
250		addl %ebp,%edi			#  as pointer
251		movl 0x10(%edx),%ecx		# Get p_filesz
252		rep				# Set up
253		movsb				#  segment
254		movl 0x14(%edx),%ecx		# Any bytes
255		subl 0x10(%edx),%ecx		#  to zero?
256		jz start.5			# No
257		xorb %al,%al			# Then
258		rep				#  zero
259		stosb				#  them
260start.5:	popl %ecx			# Restore
261		popl %edi			#  working
262		popl %esi			#  registers
263		decl %edi			# Segments to do
264		je start.7			# If none
265start.6:	addl $0x20,%edx 		# To next entry
266		loop start.4			# Till done
267start.7:
268#ifdef BTXLDR_VERBOSE
269		movl $m_done,%esi		# Display done
270		call putstr			#  message
271#endif
272		movl $start.8,%esi		# Real mode stub
273		movl $MEM_STUB,%edi		# Destination
274		movl $start.9-start.8,%ecx	# Size
275		rep				# Relocate
276		movsb				#  it
277		ljmp $SEL_RCODE,$MEM_STUB	# To 16-bit code
278		.code16
279start.8:	xorw %ax,%ax			# Data
280		movb $SEL_RDATA,%al		#  selector
281		movw %ax,%ss			# Reload SS
282		movw %ax,%ds			# Reset
283		movw %ax,%es			#  other
284		movw %ax,%fs			#  segment
285		movw %ax,%gs			#  limits
286		movl %cr0,%eax			# Switch to
287		decw %ax			#  real
288		movl %eax,%cr0			#  mode
289		ljmp $0,$MEM_ENTRY		# Jump to BTX entry point
290start.9:
291		.code32
292/*
293 * Output message [ESI] followed by EAX in hex.
294 */
295hexout: 	pushl %eax			# Save
296		call putstr			# Display message
297		popl %eax			# Restore
298		pushl %esi			# Save
299		pushl %edi			#  caller's
300		movl $buf,%edi			# Buffer
301		pushl %edi			# Save
302		call hex32			# To hex
303		xorb %al,%al			# Terminate
304		stosb				#  string
305		popl %esi			# Restore
306hexout.1:	lodsb				# Get a char
307		cmpb $'0',%al			# Leading zero?
308		je hexout.1			# Yes
309		testb %al,%al			# End of string?
310		jne hexout.2			# No
311		decl %esi			# Undo
312hexout.2:	decl %esi			# Adjust for inc
313		call putstr			# Display hex
314		popl %edi			# Restore
315		popl %esi			#  caller's
316		ret				# To caller
317/*
318 * Output zero-terminated string [ESI] to the console.
319 */
320putstr.0:	call putchr			# Output char
321putstr: 	lodsb				# Load char
322		testb %al,%al			# End of string?
323		jne putstr.0			# No
324		ret				# To caller
325/*
326 * Output character AL to the console.
327 */
328putchr: 	pusha				# Save
329		xorl %ecx,%ecx			# Zero for loops
330		movb $SCR_MAT,%ah		# Mode/attribute
331		movl $BDA_POS,%ebx		# BDA pointer
332		movw (%ebx),%dx 		# Cursor position
333#ifdef PC98
334		movl $0xa0000,%edi		# Regen buffer (color)
335#else
336		movl $0xb8000,%edi		# Regen buffer (color)
337		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
338		jne putchr.1			# No
339		xorw %di,%di			# Regen buffer (mono)
340#endif
341putchr.1:	cmpb $0xa,%al			# New line?
342		je putchr.2			# Yes
343#ifdef PC98
344		movw %dx,%cx
345		movb %al,(%edi,%ecx,1)		# Write char
346		addl $0x2000,%ecx
347		movb %ah,(%edi,%ecx,1)		# Write attr
348		addw $0x2,%dx
349		jmp putchr.3
350putchr.2:	movw %dx,%ax
351		movb $SCR_COL*2,%dl
352		div %dl
353		incb %al
354		mul %dl
355		movw %ax,%dx
356putchr.3:	cmpw $SCR_COL*SCR_ROW*2,%dx
357#else
358		xchgl %eax,%ecx 		# Save char
359		movb $SCR_COL,%al		# Columns per row
360		mulb %dh			#  * row position
361		addb %dl,%al			#  + column
362		adcb $0x0,%ah			#  position
363		shll %eax			#  * 2
364		xchgl %eax,%ecx 		# Swap char, offset
365		movw %ax,(%edi,%ecx,1)		# Write attr:char
366		incl %edx			# Bump cursor
367		cmpb $SCR_COL,%dl		# Beyond row?
368		jb putchr.3			# No
369putchr.2:	xorb %dl,%dl			# Zero column
370		incb %dh			# Bump row
371putchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
372#endif
373		jb putchr.4			# No
374		leal 2*SCR_COL(%edi),%esi	# New top line
375		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
376		rep				# Scroll
377		movsl				#  screen
378		movb $' ',%al			# Space
379#ifdef PC98
380		xorb %ah,%ah
381#endif
382		movb $SCR_COL,%cl		# Columns to clear
383		rep				# Clear
384		stosw				#  line
385#ifdef PC98
386		movw $(SCR_ROW-1)*SCR_COL*2,%dx
387putchr.4:	movw %dx,(%ebx) 		# Update position
388		shrw $1,%dx
389gdcwait.3:	inb $0x60,%al
390		testb $0x04,%al
391		jz gdcwait.3
392		movb $0x49,%al
393		outb %al,$0x62
394		movb %dl,%al
395		outb %al,$0x60
396		movb %dh,%al
397		outb %al,$0x60
398#else
399		movb $SCR_ROW-1,%dh		# Bottom line
400putchr.4:	movw %dx,(%ebx) 		# Update position
401#endif
402		popa				# Restore
403		ret				# To caller
404/*
405 * Convert EAX, AX, or AL to hex, saving the result to [EDI].
406 */
407hex32:		pushl %eax			# Save
408		shrl $0x10,%eax 		# Do upper
409		call hex16			#  16
410		popl %eax			# Restore
411hex16:		call hex16.1			# Do upper 8
412hex16.1:	xchgb %ah,%al			# Save/restore
413hex8:		pushl %eax			# Save
414		shrb $0x4,%al			# Do upper
415		call hex8.1			#  4
416		popl %eax			# Restore
417hex8.1: 	andb $0xf,%al			# Get lower 4
418		cmpb $0xa,%al			# Convert
419		sbbb $0x69,%al			#  to hex
420		das				#  digit
421		orb $0x20,%al			# To lower case
422		stosb				# Save char
423		ret				# (Recursive)
424
425		.data
426		.p2align 4
427/*
428 * Global descriptor table.
429 */
430gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
431		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
432		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
433		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
434		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
435gdt.1:
436gdtdesc:	.word gdt.1-gdt-1		# Limit
437		.long gdt			# Base
438/*
439 * Messages.
440 */
441m_logo: 	.asciz " \nBTX loader 1.00  "
442m_vers: 	.asciz "BTX version is \0\n"
443e_fmt:		.asciz "Error: Client format not supported\n"
444#ifdef BTXLDR_VERBOSE
445m_mem:		.asciz "Starting in protected mode (base mem=\0)\n"
446m_esp:		.asciz "Arguments passed (esp=\0):\n"
447m_args: 	.asciz"<howto="
448		.asciz" bootdev="
449		.asciz" junk="
450		.asciz" "
451		.asciz" "
452		.asciz" bootinfo=\0>\n"
453m_rel_bi:	.asciz "Relocated bootinfo (size=48) to \0\n"
454m_rel_args:	.asciz "Relocated arguments (size=18) to \0\n"
455m_rel_btx:	.asciz "Relocated kernel (size=\0) to \0\n"
456m_base: 	.asciz "Client base address is \0\n"
457m_elf:		.asciz "Client format is ELF\n"
458m_segs: 	.asciz "text segment: offset="
459		.asciz " vaddr="
460		.asciz " filesz="
461		.asciz " memsz=\0\n"
462		.asciz "data segment: offset="
463		.asciz " vaddr="
464		.asciz " filesz="
465		.asciz " memsz=\0\n"
466m_done: 	.asciz "Loading complete\n"
467#endif
468/*
469 * Uninitialized data area.
470 */
471buf:						# Scratch buffer
472