cdboot.S revision 167191
1158559Snyan#
2158559Snyan# Copyright (c) 2006 TAKAHASHI Yoshihiro <nyan@FreeBSD.org>
3158559Snyan# Copyright (c) 2001 John Baldwin <jhb@FreeBSD.org>
4158559Snyan# All rights reserved.
5158559Snyan#
6158559Snyan# Redistribution and use in source and binary forms, with or without
7158559Snyan# modification, are permitted provided that the following conditions
8158559Snyan# are met:
9158559Snyan# 1. Redistributions of source code must retain the above copyright
10158559Snyan#    notice, this list of conditions and the following disclaimer.
11158559Snyan# 2. Redistributions in binary form must reproduce the above copyright
12158559Snyan#    notice, this list of conditions and the following disclaimer in the
13158559Snyan#    documentation and/or other materials provided with the distribution.
14158559Snyan# 3. Neither the name of the author nor the names of any co-contributors
15158559Snyan#    may be used to endorse or promote products derived from this software
16158559Snyan#    without specific prior written permission.
17158559Snyan#
18158559Snyan# THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
19158559Snyan# ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
20158559Snyan# IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
21158559Snyan# ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
22158559Snyan# FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
23158559Snyan# DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
24158559Snyan# OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
25158559Snyan# HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
26158559Snyan# LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
27158559Snyan# OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
28158559Snyan# SUCH DAMAGE.
29158559Snyan#
30158559Snyan
31158559Snyan# $FreeBSD: head/sys/boot/pc98/cdboot/cdboot.s 167191 2007-03-04 04:53:17Z nyan $
32158559Snyan
33158559Snyan#
34158559Snyan# Basically, we first create a set of boot arguments to pass to the loaded
35158559Snyan# binary.  Then we attempt to load /boot/loader from the CD we were booted
36158559Snyan# off of.
37158559Snyan#
38158559Snyan
39158559Snyan#
40158559Snyan# Memory locations.
41158559Snyan#
42158559Snyan		.set STACK_OFF,0x6000		# Stack offset
43158559Snyan		.set LOAD_SEG,0x0700		# Load segment
44158559Snyan		.set LOAD_SIZE,2048		# Load size
45158559Snyan		.set DAUA,0x0584		# DA/UA
46158559Snyan
47158559Snyan		.set MEM_PAGE_SIZE,0x1000	# memory page size, 4k
48158559Snyan		.set MEM_ARG,0x900		# Arguments at start
49158559Snyan		.set MEM_ARG_BTX,0xa100		# Where we move them to so the
50158559Snyan						#  BTX client can see them
51158559Snyan		.set MEM_ARG_SIZE,0x18		# Size of the arguments
52158559Snyan		.set MEM_BTX_ADDRESS,0x9000	# where BTX lives
53158559Snyan		.set MEM_BTX_ENTRY,0x9010	# where BTX starts to execute
54158559Snyan		.set MEM_BTX_OFFSET,MEM_PAGE_SIZE # offset of BTX in the loader
55158559Snyan		.set MEM_BTX_CLIENT,0xa000	# where BTX clients live
56158559Snyan#
57158559Snyan# PC98 machine type from sys/pc98/pc98/pc98_machdep.h
58158559Snyan#
59158559Snyan		.set MEM_SYS,		0xa100	# System common area segment
60158559Snyan		.set PC98_MACHINE_TYPE,	0x0620	# PC98 machine type
61158559Snyan		.set EPSON_ID,		0x0624	# EPSON machine id
62158559Snyan
63158559Snyan		.set M_NEC_PC98,	0x0001
64158559Snyan		.set M_EPSON_PC98,	0x0002
65158559Snyan		.set M_NOT_H98,		0x0010
66158559Snyan		.set M_H98,		0x0020
67158559Snyan		.set M_NOTE,		0x0040
68158559Snyan		.set M_NORMAL,		0x1000
69158559Snyan		.set M_8M,		0x8000
70158559Snyan#
71158559Snyan# Signature Constants
72158559Snyan#
73158559Snyan		.set SIG1_OFF,0x1fe		# Signature offset
74158559Snyan		.set SIG2_OFF,0x7fe		# Signature offset
75158559Snyan#
76158559Snyan# a.out header fields
77158559Snyan#
78158559Snyan		.set AOUT_TEXT,0x04		# text segment size
79158559Snyan		.set AOUT_DATA,0x08		# data segment size
80158559Snyan		.set AOUT_BSS,0x0c		# zero'd BSS size
81158559Snyan		.set AOUT_SYMBOLS,0x10		# symbol table
82158559Snyan		.set AOUT_ENTRY,0x14		# entry point
83158559Snyan		.set AOUT_HEADER,MEM_PAGE_SIZE	# size of the a.out header
84158559Snyan#
85158559Snyan# Flags for kargs->bootflags
86158559Snyan#
87158559Snyan		.set KARGS_FLAGS_CD,0x1		# flag to indicate booting from
88158559Snyan						#  CD loader
89158559Snyan#
90158559Snyan# Segment selectors.
91158559Snyan#
92158559Snyan		.set SEL_SDATA,0x8		# Supervisor data
93158559Snyan		.set SEL_RDATA,0x10		# Real mode data
94158559Snyan		.set SEL_SCODE,0x18		# PM-32 code
95158559Snyan		.set SEL_SCODE16,0x20		# PM-16 code
96158559Snyan#
97158559Snyan# BTX constants
98158559Snyan#
99158559Snyan		.set INT_SYS,0x30		# BTX syscall interrupt
100158559Snyan#
101158559Snyan# Constants for reading from the CD.
102158559Snyan#
103158559Snyan		.set ERROR_TIMEOUT,0x90		# BIOS timeout on read
104158559Snyan		.set NUM_RETRIES,3		# Num times to retry
105158559Snyan		.set SECTOR_SIZE,0x800		# size of a sector
106158559Snyan		.set SECTOR_SHIFT,11		# number of place to shift
107158559Snyan		.set BUFFER_LEN,0x100		# number of sectors in buffer
108158559Snyan		.set MAX_READ,0xf800		# max we can read at a time
109158559Snyan		.set MAX_READ_SEC,MAX_READ >> SECTOR_SHIFT
110158559Snyan		.set MEM_READ_BUFFER,0x9000	# buffer to read from CD
111158559Snyan		.set MEM_VOLDESC,MEM_READ_BUFFER # volume descriptor
112158559Snyan		.set MEM_DIR,MEM_VOLDESC+SECTOR_SIZE # Lookup buffer
113158559Snyan		.set VOLDESC_LBA,0x10		# LBA of vol descriptor
114158559Snyan		.set VD_PRIMARY,1		# Primary VD
115158559Snyan		.set VD_END,255			# VD Terminator
116158559Snyan		.set VD_ROOTDIR,156		# Offset of Root Dir Record
117158559Snyan		.set DIR_LEN,0			# Offset of Dir Record length
118158559Snyan		.set DIR_EA_LEN,1		# Offset of EA length
119158559Snyan		.set DIR_EXTENT,2		# Offset of 64-bit LBA
120158559Snyan		.set DIR_SIZE,10		# Offset of 64-bit length
121158559Snyan		.set DIR_NAMELEN,32		# Offset of 8-bit name len
122158559Snyan		.set DIR_NAME,33		# Offset of dir name
123158559Snyan
124158559Snyan#
125158559Snyan# Program start.
126158559Snyan#
127158559Snyan		.code16
128158559Snyan		.globl start
129158559Snyan
130158559Snyanstart:		jmp main
131158559Snyan
132158559Snyan		.org 4
133158559Snyan		.ascii "IPL1   "
134158559Snyan
135158559Snyanmain:		cld
136158559Snyan
137158559Snyan		/* Setup the stack */
138158559Snyan		xor %ax,%ax
139158559Snyan		mov %ax,%ss
140158559Snyan		mov $STACK_OFF,%sp
141158559Snyan
142158559Snyan		push %ecx
143158559Snyan
144158559Snyan		/* Setup graphic screen */
145158559Snyan		mov $0x42,%ah			# 640x400
146158559Snyan		mov $0xc0,%ch
147158559Snyan		int $0x18
148158559Snyan		mov $0x40,%ah			# graph on
149158559Snyan		int $0x18
150158559Snyan
151158559Snyan		/* Setup text screen */
152158559Snyan		mov $0x0a00,%ax			# 80x25
153158559Snyan		int $0x18
154158559Snyan		mov $0x0c,%ah			# text on
155158559Snyan		int $0x18
156158559Snyan		mov $0x13,%ah			# cursor home
157158559Snyan		xor %dx,%dx
158158559Snyan		int $0x18
159158559Snyan		mov $0x11,%ah			# cursor on
160158559Snyan		int $0x18
161158559Snyan
162158559Snyan		/* Setup keyboard */
163158559Snyan		mov $0x03,%ah
164158559Snyan		int $0x18
165158559Snyan
166158559Snyan		/* Transfer PC-9801 system common area */
167158559Snyan		xor %ax,%ax
168158559Snyan		mov %ax,%si
169158559Snyan		mov %ax,%ds
170158559Snyan		mov %ax,%di
171158559Snyan		mov $MEM_SYS,%ax
172158559Snyan		mov %ax,%es
173158559Snyan		mov $0x0600,%cx
174158559Snyan		rep
175158559Snyan		movsb
176158559Snyan
177158559Snyan		/* Transfer EPSON machine type */
178158559Snyan		mov $0xfd00,%ax
179158559Snyan		mov %ax,%ds
180158559Snyan		mov (0x804),%eax
181158559Snyan		and $0x00ffffff,%eax
182158559Snyan		mov %eax,%es:(EPSON_ID)
183158559Snyan
184158559Snyan		/* Set machine type to PC98_SYSTEM_PARAMETER */
185158559Snyan		call machine_check
186158559Snyan
187158559Snyan		/* Load cdboot */
188158559Snyan		xor %ax,%ax
189158559Snyan		mov %ax,%ds
190158559Snyan		mov $0x06,%ah		/* Read data */
191158559Snyan		mov (DAUA),%al		/* Read drive */
192158559Snyan		pop %ecx		/* cylinder */
193158559Snyan		xor %dx,%dx		/* head / sector */
194158559Snyan		mov $LOAD_SEG,%bx	/* Load address */
195158559Snyan		mov %bx,%es
196158559Snyan		xor %bp,%bp
197158559Snyan		mov $LOAD_SIZE,%bx	/* Load size */
198158559Snyan		int $0x1b
199158559Snyan		mov $msg_readerr,%si
200158559Snyan		jc error
201158559Snyan
202158559Snyan		/* Jump to cdboot */
203158559Snyan		ljmp $LOAD_SEG,$cdboot
204158559Snyan
205158559Snyan#
206158559Snyan# Set machine type to PC98_SYSTEM_PARAMETER.
207158559Snyan#
208158559Snyanmachine_check:	xor %edx,%edx
209158559Snyan		mov %dx,%ds
210158559Snyan		mov $MEM_SYS,%ax
211158559Snyan		mov %ax,%es
212158559Snyan
213158559Snyan		/* Wait V-SYNC */
214158559Snyanvsync.1:	inb $0x60,%al
215158559Snyan		test $0x20,%al
216158559Snyan		jnz vsync.1
217158559Snyanvsync.2:	inb $0x60,%al
218158559Snyan		test $0x20,%al
219158559Snyan		jz vsync.2
220158559Snyan
221158559Snyan		/* ANK 'A' font */
222158559Snyan		xor %al,%al
223158559Snyan		outb %al,$0xa1
224158559Snyan		mov $0x41,%al
225158559Snyan		outb %al,$0xa3
226158559Snyan
227158559Snyan		/* Get 'A' font from CG window */
228158559Snyan		push %ds
229158559Snyan		mov $0xa400,%ax
230158559Snyan		mov %ax,%ds
231158559Snyan		xor %eax,%eax
232158559Snyan		xor %bx,%bx
233158559Snyan		mov $4,%cx
234158559Snyanfont.1:		add (%bx),%eax
235158559Snyan		add $4,%bx
236158559Snyan		loop font.1
237158559Snyan		pop %ds
238158559Snyan		cmp $0x6efc58fc,%eax
239158559Snyan		jnz m_epson
240158559Snyan
241158559Snyanm_pc98:		or $M_NEC_PC98,%edx
242158559Snyan		mov $0x0458,%bx
243158559Snyan		mov (%bx),%al
244158559Snyan		test $0x80,%al
245158559Snyan		jz m_not_h98
246158559Snyan		or $M_H98,%edx
247158559Snyan		jmp 1f
248158559Snyanm_epson:	or $M_EPSON_PC98,%edx
249158559Snyanm_not_h98:	or $M_NOT_H98,%edx
250158559Snyan
251158559Snyan1:		inb $0x42,%al
252158559Snyan		test $0x20,%al
253158559Snyan		jz 1f
254158559Snyan		or $M_8M,%edx
255158559Snyan
256158559Snyan1:		mov $0x0400,%bx
257158559Snyan		mov (%bx),%al
258158559Snyan		test $0x80,%al
259158559Snyan		jz 1f
260158559Snyan		or $M_NOTE,%edx
261158559Snyan
262158559Snyan1:		mov $PC98_MACHINE_TYPE,%bx
263158559Snyan		mov %edx,%es:(%bx)
264158559Snyan		ret
265158559Snyan
266158559Snyan#
267158559Snyan# Print out the error message at [SI], wait for a keypress, and then
268158559Snyan# reboot the machine.
269158559Snyan#
270158559Snyanerror:		call putstr
271158559Snyan		mov $msg_keypress,%si
272158559Snyan		call putstr
273158559Snyan		xor %ax,%ax			# Get keypress
274158559Snyan		int $0x18
275158559Snyan		xor %ax,%ax			# CPU reset
276158559Snyan		outb %al,$0xf0
277158559Snyanhalt:		hlt
278158559Snyan		jmp halt			# Spin
279158559Snyan
280158559Snyan#
281158559Snyan# Display a null-terminated string at [SI].
282158559Snyan#
283158559Snyan# Trashes: AX, BX, CX, DX, SI, DI
284158559Snyan#
285158559Snyanputstr:		push %ds
286158559Snyan		push %es
287158559Snyan		mov %cs,%ax
288158559Snyan		mov %ax,%ds
289158559Snyan		mov $0xa000,%ax
290158559Snyan		mov %ax,%es
291158559Snyan		mov cursor,%di
292158559Snyan		mov $0x00e1,%bx			# Attribute
293158559Snyan		mov $160,%cx
294158559Snyanputstr.0:	lodsb
295158559Snyan		testb %al,%al
296158559Snyan		jz putstr.done
297158559Snyan		cmp $0x0d,%al
298158559Snyan		jz putstr.cr
299158559Snyan		cmp $0x0a,%al
300158559Snyan		jz putstr.lf
301158559Snyan		mov %bl,%es:0x2000(%di)
302158559Snyan		stosb
303158559Snyan		inc %di
304158559Snyan		jmp putstr.move
305158559Snyanputstr.cr:	xor %dx,%dx
306158559Snyan		mov %di,%ax
307158559Snyan		div %cx
308158559Snyan		sub %dx,%di
309158559Snyan		jmp putstr.move
310158559Snyanputstr.lf:	add %cx,%di
311158559Snyanputstr.move:	mov %di,%dx
312158559Snyan		mov $0x13,%ah			# Move cursor
313158559Snyan		int $0x18
314158559Snyan		jmp putstr.0
315158559Snyanputstr.done:	mov %di,cursor
316158559Snyan		pop %es
317158559Snyan		pop %ds
318158559Snyan		ret
319158559Snyan
320158559Snyan#
321158559Snyan# Display a single char at [AL], but don't move a cursor.
322158559Snyan#
323158559Snyanputc:		push %es
324158559Snyan		push %di
325158559Snyan		push %bx
326158559Snyan		mov $0xa000,%bx
327158559Snyan		mov %bx,%es
328158559Snyan		mov cursor,%di
329158559Snyan		mov $0xe1,%bl			# Attribute
330158559Snyan		mov %bl,%es:0x2000(%di)
331158559Snyan		stosb
332158559Snyan		pop %bx
333158559Snyan		pop %di
334158559Snyan		pop %es
335158559Snyan		ret
336158559Snyan
337158559Snyanmsg_readerr:	.asciz "Read Error\r\n"
338158559Snyanmsg_keypress:	.asciz "\r\nPress any key to reboot\r\n"
339158559Snyan
340158559Snyan/* Boot signature */
341158559Snyan
342158559Snyan		.org SIG1_OFF,0x90
343158559Snyan
344158559Snyan		.word 0xaa55			# Magic number
345158559Snyan
346158559Snyan#
347158559Snyan# cdboot
348158559Snyan#
349158559Snyancdboot:		mov %cs,%ax
350158559Snyan		mov %ax,%ds
351158559Snyan		xor %ax,%ax
352158559Snyan		mov %ax,%es
353158559Snyan		mov %es:(DAUA),%al		# Save BIOS boot device
354158559Snyan		mov %al,drive
355158559Snyan		mov %cx,cylinder		# Save BIOS boot cylinder
356158559Snyan
357158559Snyan		mov $msg_welcome,%si		# %ds:(%si) -> welcome message
358158559Snyan		call putstr			# display the welcome message
359158559Snyan#
360158559Snyan# Setup the arguments that the loader is expecting from boot[12]
361158559Snyan#
362158559Snyan		mov $msg_bootinfo,%si		# %ds:(%si) -> boot args message
363158559Snyan		call putstr			# display the message
364158559Snyan		mov $MEM_ARG,%bx		# %ds:(%bx) -> boot args
365158559Snyan		mov %bx,%di			# %es:(%di) -> boot args
366158559Snyan		xor %eax,%eax			# zero %eax
367158559Snyan		mov $(MEM_ARG_SIZE/4),%cx	# Size of arguments in 32-bit
368158559Snyan						#  dwords
369158559Snyan		rep				# Clear the arguments
370158559Snyan		stosl				#  to zero
371158559Snyan		mov drive,%dl			# Store BIOS boot device
372158559Snyan		mov %dl,%es:0x4(%bx)		#  in kargs->bootdev
373158559Snyan		or $KARGS_FLAGS_CD,%es:0x8(%bx)	# kargs->bootflags |=
374158559Snyan						#  KARGS_FLAGS_CD
375158559Snyan#
376158559Snyan# Load Volume Descriptor
377158559Snyan#
378158559Snyan		mov $VOLDESC_LBA,%eax		# Set LBA of first VD
379158559Snyanload_vd:	push %eax			# Save %eax
380158559Snyan		mov $1,%dh			# One sector
381158559Snyan		mov $MEM_VOLDESC,%ebx		# Destination
382158559Snyan		call read			# Read it in
383158559Snyan		cmpb $VD_PRIMARY,%es:(%bx)	# Primary VD?
384158559Snyan		je have_vd			# Yes
385158559Snyan		pop %eax			# Prepare to
386158559Snyan		inc %eax			#  try next
387158559Snyan		cmpb $VD_END,%es:(%bx)		# Last VD?
388158559Snyan		jne load_vd			# No, read next
389158559Snyan		mov $msg_novd,%si		# No VD
390158559Snyan		jmp error			# Halt
391158559Snyanhave_vd:					# Have Primary VD
392158559Snyan#
393158559Snyan# Try to look up the loader binary using the paths in the loader_paths
394158559Snyan# array.
395158559Snyan#
396158559Snyan		mov $loader_paths,%si		# Point to start of array
397158559Snyanlookup_path:	push %si			# Save file name pointer
398158559Snyan		call lookup			# Try to find file
399158559Snyan		pop %di				# Restore file name pointer
400158559Snyan		jnc lookup_found		# Found this file
401158559Snyan		push %es
402158559Snyan		mov %cs,%ax
403158559Snyan		mov %ax,%es
404158559Snyan		xor %al,%al			# Look for next
405158559Snyan		mov $0xffff,%cx			#  path name by
406158559Snyan		repnz				#  scanning for
407158559Snyan		scasb				#  nul char
408158559Snyan		pop %es
409158559Snyan		mov %di,%si			# Point %si at next path
410158559Snyan		mov (%si),%al			# Get first char of next path
411158559Snyan		or %al,%al			# Is it double nul?
412158559Snyan		jnz lookup_path			# No, try it.
413158559Snyan		mov $msg_failed,%si		# Failed message
414158559Snyan		jmp error			# Halt
415158559Snyanlookup_found:					# Found a loader file
416158559Snyan#
417158559Snyan# Load the binary into the buffer.  Due to real mode addressing limitations
418158559Snyan# we have to read it in in 64k chunks.
419158559Snyan#
420158559Snyan		mov %es:DIR_SIZE(%bx),%eax	# Read file length
421158559Snyan		add $SECTOR_SIZE-1,%eax		# Convert length to sectors
422158559Snyan		shr $SECTOR_SHIFT,%eax
423158559Snyan		cmp $BUFFER_LEN,%eax
424158559Snyan		jbe load_sizeok
425158559Snyan		mov $msg_load2big,%si		# Error message
426158559Snyan		jmp error
427158559Snyanload_sizeok:	movzbw %al,%cx			# Num sectors to read
428158559Snyan		mov %es:DIR_EXTENT(%bx),%eax	# Load extent
429158559Snyan		xor %edx,%edx
430158559Snyan		mov %es:DIR_EA_LEN(%bx),%dl
431158559Snyan		add %edx,%eax			# Skip extended
432158559Snyan		mov $MEM_READ_BUFFER,%ebx	# Read into the buffer
433158559Snyanload_loop:	mov %cl,%dh
434158559Snyan		cmp $MAX_READ_SEC,%cl		# Truncate to max read size
435158559Snyan		jbe load_notrunc
436158559Snyan		mov $MAX_READ_SEC,%dh
437158559Snyanload_notrunc:	sub %dh,%cl			# Update count
438158559Snyan		push %eax			# Save
439158559Snyan		call read			# Read it in
440158559Snyan		pop %eax			# Restore
441158559Snyan		add $MAX_READ_SEC,%eax		# Update LBA
442158559Snyan		add $MAX_READ,%ebx		# Update dest addr
443158559Snyan		jcxz load_done			# Done?
444158559Snyan		jmp load_loop			# Keep going
445158559Snyanload_done:
446158559Snyan#
447158559Snyan# Turn on the A20 address line
448158559Snyan#
449158559Snyan		xor %ax,%ax			# Turn A20 on
450158559Snyan		outb %al,$0xf2
451158559Snyan		mov $0x02,%al
452158559Snyan		outb %al,$0xf6
453158559Snyan#
454158559Snyan# Relocate the loader and BTX using a very lazy protected mode
455158559Snyan#
456158559Snyan		mov $msg_relocate,%si		# Display the
457158559Snyan		call putstr			#  relocation message
458158559Snyan		mov %es:(MEM_READ_BUFFER+AOUT_ENTRY),%edi # %edi is the destination
459158559Snyan		mov $(MEM_READ_BUFFER+AOUT_HEADER),%esi	# %esi is
460158559Snyan						#  the start of the text
461158559Snyan						#  segment
462158559Snyan		mov %es:(MEM_READ_BUFFER+AOUT_TEXT),%ecx # %ecx = length of the text
463158559Snyan						#  segment
464158559Snyan		push %edi			# Save entry point for later
465158559Snyan		lgdt gdtdesc			# setup our own gdt
466158559Snyan		cli				# turn off interrupts
467158559Snyan		mov %cr0,%eax			# Turn on
468158559Snyan		or $0x1,%al			#  protected
469158559Snyan		mov %eax,%cr0			#  mode
470158559Snyan		ljmp $SEL_SCODE,$pm_start	# long jump to clear the
471158559Snyan						#  instruction pre-fetch queue
472158559Snyan		.code32
473158559Snyanpm_start:	mov $SEL_SDATA,%ax		# Initialize
474158559Snyan		mov %ax,%ds			#  %ds and
475158559Snyan		mov %ax,%es			#  %es to a flat selector
476158559Snyan		rep				# Relocate the
477158559Snyan		movsb				#  text segment
478158559Snyan		add $(MEM_PAGE_SIZE - 1),%edi	# pad %edi out to a new page
479158559Snyan		and $~(MEM_PAGE_SIZE - 1),%edi #  for the data segment
480158559Snyan		mov MEM_READ_BUFFER+AOUT_DATA,%ecx # size of the data segment
481158559Snyan		rep				# Relocate the
482158559Snyan		movsb				#  data segment
483158559Snyan		mov MEM_READ_BUFFER+AOUT_BSS,%ecx # size of the bss
484158559Snyan		xor %eax,%eax			# zero %eax
485158559Snyan		add $3,%cl			# round %ecx up to
486158559Snyan		shr $2,%ecx			#  a multiple of 4
487158559Snyan		rep				# zero the
488158559Snyan		stosl				#  bss
489158559Snyan		mov MEM_READ_BUFFER+AOUT_ENTRY,%esi # %esi -> relocated loader
490158559Snyan		add $MEM_BTX_OFFSET,%esi	# %esi -> BTX in the loader
491158559Snyan		mov $MEM_BTX_ADDRESS,%edi	# %edi -> where BTX needs to go
492158559Snyan		movzwl 0xa(%esi),%ecx		# %ecx -> length of BTX
493158559Snyan		rep				# Relocate
494158559Snyan		movsb				#  BTX
495158559Snyan		ljmp $SEL_SCODE16,$pm_16	# Jump to 16-bit PM
496158559Snyan		.code16
497158559Snyanpm_16:		mov $SEL_RDATA,%ax		# Initialize
498158559Snyan		mov %ax,%ds			#  %ds and
499158559Snyan		mov %ax,%es			#  %es to a real mode selector
500158559Snyan		mov %cr0,%eax			# Turn off
501158559Snyan		and $~0x1,%al			#  protected
502158559Snyan		mov %eax,%cr0			#  mode
503158559Snyan		ljmp $LOAD_SEG,$pm_end		# Long jump to clear the
504158559Snyan						#  instruction pre-fetch queue
505158559Snyanpm_end:		sti				# Turn interrupts back on now
506158559Snyan#
507158559Snyan# Copy the BTX client to MEM_BTX_CLIENT
508158559Snyan#
509158559Snyan		mov %cs,%ax
510158559Snyan		mov %ax,%ds
511158559Snyan		xor %ax,%ax
512158559Snyan		mov %ax,%es
513158559Snyan		mov $MEM_BTX_CLIENT,%di		# Prepare to relocate
514158559Snyan		mov $btx_client,%si		#  the simple btx client
515158559Snyan		mov $(btx_client_end-btx_client),%cx # length of btx client
516158559Snyan		rep				# Relocate the
517158559Snyan		movsb				#  simple BTX client
518158559Snyan#
519158559Snyan# Copy the boot[12] args to where the BTX client can see them
520158559Snyan#
521158559Snyan		xor %ax,%ax
522158559Snyan		mov %ax,%ds
523158559Snyan		mov $MEM_ARG,%si		# where the args are at now
524158559Snyan		mov $MEM_ARG_BTX,%di		# where the args are moving to
525158559Snyan		mov $(MEM_ARG_SIZE/4),%cx	# size of the arguments in longs
526158559Snyan		rep				# Relocate
527158559Snyan		movsl				#  the words
528158559Snyan#
529158559Snyan# Save the entry point so the client can get to it later on
530158559Snyan#
531158559Snyan		pop %eax			# Restore saved entry point
532158559Snyan		stosl				#  and add it to the end of
533158559Snyan						#  the arguments
534158559Snyan#
535158559Snyan# Now we just start up BTX and let it do the rest
536158559Snyan#
537158559Snyan		mov $msg_jump,%si		# Display the
538158559Snyan		call putstr			#  jump message
539158559Snyan		ljmp $0,$MEM_BTX_ENTRY		# Jump to the BTX entry point
540158559Snyan
541158559Snyan#
542158559Snyan# Lookup the file in the path at [SI] from the root directory.
543158559Snyan#
544158559Snyan# Trashes: All but BX
545158559Snyan# Returns: CF = 0 (success), BX = pointer to record
546158559Snyan#          CF = 1 (not found)
547158559Snyan#
548158559Snyanlookup:		mov $VD_ROOTDIR+MEM_VOLDESC,%bx	# Root directory record
549158559Snyan		push %bx
550158559Snyan		push %si
551158559Snyan		mov $msg_lookup,%si		# Display lookup message
552158559Snyan		call putstr
553158559Snyan		pop %si
554158559Snyan		push %si
555158559Snyan		call putstr
556158559Snyan		mov $msg_lookup2,%si
557158559Snyan		call putstr
558158559Snyan		pop %si
559158559Snyan		pop %bx
560158559Snyanlookup_dir:	lodsb				# Get first char of path
561158559Snyan		cmp $0,%al			# Are we done?
562158559Snyan		je lookup_done			# Yes
563158559Snyan		cmp $'/',%al			# Skip path separator.
564158559Snyan		je lookup_dir
565158559Snyan		dec %si				# Undo lodsb side effect
566158559Snyan		call find_file			# Lookup first path item
567158559Snyan		jnc lookup_dir			# Try next component
568158559Snyan		mov $msg_lookupfail,%si		# Not found message
569158559Snyan		push %bx
570158559Snyan		call putstr
571158559Snyan		pop %bx
572158559Snyan		stc				# Set carry
573158559Snyan		ret
574158559Snyanlookup_done:	mov $msg_lookupok,%si		# Success message
575158559Snyan		push %bx
576158559Snyan		call putstr
577158559Snyan		pop %bx
578158559Snyan		clc				# Clear carry
579158559Snyan		ret
580158559Snyan
581158559Snyan#
582158559Snyan# Lookup file at [SI] in directory whose record is at [BX].
583158559Snyan#
584158559Snyan# Trashes: All but returns
585158559Snyan# Returns: CF = 0 (success), BX = pointer to record, SI = next path item
586158559Snyan#          CF = 1 (not found), SI = preserved
587158559Snyan#
588158559Snyanfind_file:	mov %es:DIR_EXTENT(%bx),%eax	# Load extent
589158559Snyan		xor %edx,%edx
590158559Snyan		mov %es:DIR_EA_LEN(%bx),%dl
591158559Snyan		add %edx,%eax			# Skip extended attributes
592158559Snyan		mov %eax,rec_lba		# Save LBA
593158559Snyan		mov %es:DIR_SIZE(%bx),%eax	# Save size
594158559Snyan		mov %eax,rec_size
595158559Snyan		xor %cl,%cl			# Zero length
596158559Snyan		push %si			# Save
597158559Snyanff.namelen:	inc %cl				# Update length
598158559Snyan		lodsb				# Read char
599158559Snyan		cmp $0,%al			# Nul?
600158559Snyan		je ff.namedone			# Yes
601158559Snyan		cmp $'/',%al			# Path separator?
602158559Snyan		jnz ff.namelen			# No, keep going
603158559Snyanff.namedone:	dec %cl				# Adjust length and save
604158559Snyan		mov %cl,name_len
605158559Snyan		pop %si				# Restore
606158559Snyanff.load:	mov rec_lba,%eax		# Load LBA
607158559Snyan		mov $MEM_DIR,%ebx		# Address buffer
608158559Snyan		mov $1,%dh			# One sector
609158559Snyan		call read			# Read directory block
610158559Snyan		incl rec_lba			# Update LBA to next block
611158559Snyanff.scan:	mov %ebx,%edx			# Check for EOF
612158559Snyan		sub $MEM_DIR,%edx
613158559Snyan		cmp %edx,rec_size
614158559Snyan		ja ff.scan.1
615158559Snyan		stc				# EOF reached
616158559Snyan		ret
617158559Snyanff.scan.1:	cmpb $0,%es:DIR_LEN(%bx)	# Last record in block?
618158559Snyan		je ff.nextblock
619158559Snyan		push %si			# Save
620158559Snyan		movzbw %es:DIR_NAMELEN(%bx),%si	# Find end of string
621158559Snyanff.checkver:	cmpb $'0',%es:DIR_NAME-1(%bx,%si)	# Less than '0'?
622158559Snyan		jb ff.checkver.1
623158559Snyan		cmpb $'9',%es:DIR_NAME-1(%bx,%si)	# Greater than '9'?
624158559Snyan		ja ff.checkver.1
625158559Snyan		dec %si				# Next char
626158559Snyan		jnz ff.checkver
627158559Snyan		jmp ff.checklen			# All numbers in name, so
628158559Snyan						#  no version
629158559Snyanff.checkver.1:	movzbw %es:DIR_NAMELEN(%bx),%cx
630158559Snyan		cmp %cx,%si			# Did we find any digits?
631158559Snyan		je ff.checkdot			# No
632158559Snyan		cmpb $';',%es:DIR_NAME-1(%bx,%si)	# Check for semicolon
633158559Snyan		jne ff.checkver.2
634158559Snyan		dec %si				# Skip semicolon
635158559Snyan		mov %si,%cx
636158559Snyan		mov %cl,%es:DIR_NAMELEN(%bx)	# Adjust length
637158559Snyan		jmp ff.checkdot
638158559Snyanff.checkver.2:	mov %cx,%si			# Restore %si to end of string
639158559Snyanff.checkdot:	cmpb $'.',%es:DIR_NAME-1(%bx,%si)	# Trailing dot?
640158559Snyan		jne ff.checklen			# No
641158559Snyan		decb %es:DIR_NAMELEN(%bx)	# Adjust length
642158559Snyanff.checklen:	pop %si				# Restore
643158559Snyan		movzbw name_len,%cx		# Load length of name
644158559Snyan		cmp %cl,%es:DIR_NAMELEN(%bx)	# Does length match?
645158559Snyan		je ff.checkname			# Yes, check name
646158559Snyanff.nextrec:	add %es:DIR_LEN(%bx),%bl	# Next record
647158559Snyan		adc $0,%bh
648158559Snyan		jmp ff.scan
649158559Snyanff.nextblock:	subl $SECTOR_SIZE,rec_size	# Adjust size
650158559Snyan		jnc ff.load			# If subtract ok, keep going
651158559Snyan		ret				# End of file, so not found
652158559Snyanff.checkname:	lea DIR_NAME(%bx),%di		# Address name in record
653158559Snyan		push %si			# Save
654158559Snyan		repe cmpsb			# Compare name
655158559Snyan		je ff.match			# We have a winner!
656158559Snyan		pop %si				# Restore
657158559Snyan		jmp ff.nextrec			# Keep looking.
658158559Snyanff.match:	add $2,%sp			# Discard saved %si
659158559Snyan		clc				# Clear carry
660158559Snyan		ret
661158559Snyan
662158559Snyan#
663158559Snyan# Load DH sectors starting at LBA EAX into [EBX].
664158559Snyan#
665158559Snyan# Trashes: EAX
666158559Snyan#
667158559Snyanread:		push %es			# Save
668158559Snyan		push %bp
669158559Snyan		push %dx
670158559Snyan		push %cx
671158559Snyan		push %ebx
672158559Snyan		mov %bx,%bp			# Set destination address
673158559Snyan		and $0x000f,%bp
674158559Snyan		shr $4,%ebx
675158559Snyan		mov %bx,%es
676158559Snyan		xor %bx,%bx			# Set read bytes
677158559Snyan		mov %dh,%bl
678158559Snyan		shl $SECTOR_SHIFT,%bx		# 2048 bytes/sec
679158559Snyan		mov %ax,%cx			# Set LBA
680158559Snyan		shr $16,%eax
681158559Snyan		mov %ax,%dx
682158559Snyanread.retry:	mov $0x06,%ah			# BIOS device read
683158559Snyan		mov drive,%al
684158559Snyan		and $0x7f,%al
685158559Snyan		call twiddle			# Entertain the user
686158559Snyan		int $0x1b			# Call BIOS
687158559Snyan		jc read.fail			# Worked?
688158559Snyan		pop %ebx			# Restore
689158559Snyan		pop %cx
690158559Snyan		pop %dx
691158559Snyan		pop %bp
692158559Snyan		pop %es
693158559Snyan		ret				# Return
694158559Snyanread.fail:	cmp $ERROR_TIMEOUT,%ah		# Timeout?
695158559Snyan		je read.retry			# Yes, Retry.
696158559Snyanread.error:	mov %ah,%al			# Save error
697158559Snyan		mov $hex_error,%di		# Format it
698158559Snyan		call hex8			#  as hex
699158559Snyan		mov $msg_badread,%si		# Display Read error message
700158559Snyan		jmp error
701158559Snyan
702158559Snyan#
703158559Snyan# Output the "twiddle"
704158559Snyan#
705158559Snyantwiddle:	push %ax			# Save
706158559Snyan		push %bx			# Save
707158559Snyan		mov twiddle_index,%al		# Load index
708167191Snyan		mov $twiddle_chars,%bx		# Address table
709158559Snyan		inc %al				# Next
710158559Snyan		and $3,%al			#  char
711158559Snyan		mov %al,twiddle_index		# Save index for next call
712158559Snyan		xlat				# Get char
713158559Snyan		call putc			# Output it
714158559Snyan		pop %bx				# Restore
715158559Snyan		pop %ax				# Restore
716158559Snyan		ret
717158559Snyan
718158559Snyan#
719158559Snyan# Convert AL to hex, saving the result to [EDI].
720158559Snyan#
721158559Snyanhex8:		pushl %eax			# Save
722158559Snyan		shrb $0x4,%al			# Do upper
723158559Snyan		call hex8.1			#  4
724158559Snyan		popl %eax			# Restore
725158559Snyanhex8.1: 	andb $0xf,%al			# Get lower 4
726158559Snyan		cmpb $0xa,%al			# Convert
727158559Snyan		sbbb $0x69,%al			#  to hex
728158559Snyan		das				#  digit
729158559Snyan		orb $0x20,%al			# To lower case
730158559Snyan		mov %al,(%di)			# Save char
731158559Snyan		inc %di
732158559Snyan		ret				# (Recursive)
733158559Snyan
734158559Snyan#
735158559Snyan# BTX client to start btxldr
736158559Snyan#
737158559Snyan		.code32
738158559Snyanbtx_client:	mov $(MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE-4), %esi
739158559Snyan						# %ds:(%esi) -> end
740158559Snyan						#  of boot[12] args
741158559Snyan		mov $(MEM_ARG_SIZE/4),%ecx	# Number of words to push
742158559Snyan		std				# Go backwards
743158559Snyanpush_arg:	lodsl				# Read argument
744158559Snyan		push %eax			# Push it onto the stack
745158559Snyan		loop push_arg			# Push all of the arguments
746158559Snyan		cld				# In case anyone depends on this
747158559Snyan		pushl MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE # Entry point of
748158559Snyan						#  the loader
749158559Snyan		push %eax			# Emulate a near call
750158559Snyan		mov $0x1,%eax			# 'exec' system call
751158559Snyan		int $INT_SYS			# BTX system call
752158559Snyanbtx_client_end:
753158559Snyan		.code16
754158559Snyan
755158559Snyan		.p2align 4
756158559Snyan#
757158559Snyan# Global descriptor table.
758158559Snyan#
759158559Snyangdt:		.word 0x0,0x0,0x0,0x0			# Null entry
760158559Snyan		.word 0xffff,0x0000,0x9200,0x00cf	# SEL_SDATA
761158559Snyan		.word 0xffff,0x0000,0x9200,0x0000	# SEL_RDATA
762158559Snyan		.word 0xffff,LOAD_SEG<<4,0x9a00,0x00cf	# SEL_SCODE (32-bit)
763158559Snyan		.word 0xffff,LOAD_SEG<<4,0x9a00,0x008f	# SEL_SCODE16 (16-bit)
764158559Snyangdt.1:
765158559Snyan#
766158559Snyan# Pseudo-descriptors.
767158559Snyan#
768158559Snyangdtdesc:	.word gdt.1-gdt-1		# Limit
769158559Snyan		.long LOAD_SEG<<4 + gdt		# Base
770158559Snyan
771158559Snyan#
772158559Snyan# BOOT device
773158559Snyan#
774158559Snyandrive:		.byte 0
775158559Snyancylinder:	.word 0
776158559Snyan
777158559Snyan#
778158559Snyan# State for searching dir
779158559Snyan#
780158559Snyanrec_lba:	.long 0x0			# LBA (adjusted for EA)
781158559Snyanrec_size:	.long 0x0			# File size
782158559Snyanname_len:	.byte 0x0			# Length of current name
783158559Snyan
784158559Snyancursor:		.word 0
785158559Snyantwiddle_index:	.byte 0x0
786158559Snyan
787158559Snyanmsg_welcome:	.asciz	"CD Loader 1.2\r\n\n"
788158559Snyanmsg_bootinfo:	.asciz	"Building the boot loader arguments\r\n"
789158559Snyanmsg_relocate:	.asciz	"Relocating the loader and the BTX\r\n"
790158559Snyanmsg_jump:	.asciz	"Starting the BTX loader\r\n"
791158559Snyanmsg_badread:	.ascii  "Read Error: 0x"
792158559Snyanhex_error:	.ascii	"00\r\n"
793158559Snyanmsg_novd:	.asciz  "Could not find Primary Volume Descriptor\r\n"
794158559Snyanmsg_lookup:	.asciz  "Looking up "
795158559Snyanmsg_lookup2:	.asciz  "... "
796158559Snyanmsg_lookupok:	.asciz  "Found\r\n"
797158559Snyanmsg_lookupfail:	.asciz  "File not found\r\n"
798158559Snyanmsg_load2big:	.asciz  "File too big\r\n"
799158559Snyanmsg_failed:	.asciz	"Boot failed\r\n"
800158559Snyantwiddle_chars:	.ascii	"|/-\\"
801158559Snyanloader_paths:	.asciz  "/BOOT.PC98/LOADER"
802158559Snyan		.asciz	"/boot.pc98/loader"
803158559Snyan		.asciz  "/BOOT/LOADER"
804158559Snyan		.asciz	"/boot/loader"
805158559Snyan		.byte 0
806158559Snyan
807158559Snyan/* Boot signature */
808158559Snyan
809158559Snyan		.org SIG2_OFF,0x90
810158559Snyan
811158559Snyan		.word 0xaa55			# Magic number
812