cdboot.S revision 243448
1215991Sdelphij#
2215991Sdelphij# Copyright (c) 2006 TAKAHASHI Yoshihiro <nyan@FreeBSD.org>
3215991Sdelphij# Copyright (c) 2001 John Baldwin <jhb@FreeBSD.org>
4215991Sdelphij# All rights reserved.
5215991Sdelphij#
6215991Sdelphij# Redistribution and use in source and binary forms, with or without
7215991Sdelphij# modification, are permitted provided that the following conditions
8215991Sdelphij# are met:
9215991Sdelphij# 1. Redistributions of source code must retain the above copyright
10215991Sdelphij#    notice, this list of conditions and the following disclaimer.
11215991Sdelphij# 2. Redistributions in binary form must reproduce the above copyright
12215991Sdelphij#    notice, this list of conditions and the following disclaimer in the
13215991Sdelphij#    documentation and/or other materials provided with the distribution.
14215991Sdelphij# 3. Neither the name of the author nor the names of any co-contributors
15215991Sdelphij#    may be used to endorse or promote products derived from this software
16215991Sdelphij#    without specific prior written permission.
17215991Sdelphij#
18215991Sdelphij# THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
19215991Sdelphij# ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
20215991Sdelphij# IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
21215991Sdelphij# ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
22215991Sdelphij# FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
23215991Sdelphij# DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
24215991Sdelphij# OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
25215991Sdelphij# HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
26215991Sdelphij# LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
27215991Sdelphij# OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
28215991Sdelphij# SUCH DAMAGE.
29215991Sdelphij#
30215991Sdelphij
31215991Sdelphij# $FreeBSD: stable/9/sys/boot/pc98/cdboot/cdboot.S 243448 2012-11-23 13:35:17Z nyan $
32215991Sdelphij
33215991Sdelphij#
34215991Sdelphij# Basically, we first create a set of boot arguments to pass to the loaded
35215991Sdelphij# binary.  Then we attempt to load /boot/loader from the CD we were booted
36215991Sdelphij# off of.
37215991Sdelphij#
38215991Sdelphij
39215991Sdelphij#include <bootargs.h>
40215991Sdelphij
41215991Sdelphij#
42215991Sdelphij# Memory locations.
43215991Sdelphij#
44215991Sdelphij		.set STACK_OFF,0x6000		# Stack offset
45215991Sdelphij		.set LOAD_SEG,0x0700		# Load segment
46215991Sdelphij		.set LOAD_SIZE,2048		# Load size
47215991Sdelphij		.set DAUA,0x0584		# DA/UA
48215991Sdelphij
49215991Sdelphij		.set MEM_PAGE_SIZE,0x1000	# memory page size, 4k
50215991Sdelphij		.set MEM_ARG,0x900		# Arguments at start
51215991Sdelphij		.set MEM_ARG_BTX,0xa100		# Where we move them to so the
52215991Sdelphij						#  BTX client can see them
53215991Sdelphij		.set MEM_ARG_SIZE,0x18		# Size of the arguments
54215991Sdelphij		.set MEM_BTX_ADDRESS,0x9000	# where BTX lives
55215991Sdelphij		.set MEM_BTX_ENTRY,0x9010	# where BTX starts to execute
56215991Sdelphij		.set MEM_BTX_OFFSET,MEM_PAGE_SIZE # offset of BTX in the loader
57215991Sdelphij		.set MEM_BTX_CLIENT,0xa000	# where BTX clients live
58215991Sdelphij#
59215991Sdelphij# PC98 machine type from sys/pc98/pc98/pc98_machdep.h
60215991Sdelphij#
61215991Sdelphij		.set MEM_SYS,		0xa100	# System common area segment
62215991Sdelphij		.set PC98_MACHINE_TYPE,	0x0620	# PC98 machine type
63215991Sdelphij		.set EPSON_ID,		0x0624	# EPSON machine id
64215991Sdelphij
65215991Sdelphij		.set M_NEC_PC98,	0x0001
66215991Sdelphij		.set M_EPSON_PC98,	0x0002
67215991Sdelphij		.set M_NOT_H98,		0x0010
68215991Sdelphij		.set M_H98,		0x0020
69215991Sdelphij		.set M_NOTE,		0x0040
70215991Sdelphij		.set M_NORMAL,		0x1000
71215991Sdelphij		.set M_8M,		0x8000
72215991Sdelphij#
73215991Sdelphij# Signature Constants
74215991Sdelphij#
75215991Sdelphij		.set SIG1_OFF,0x1fe		# Signature offset
76215991Sdelphij		.set SIG2_OFF,0x7fe		# Signature offset
77215991Sdelphij#
78215991Sdelphij# a.out header fields
79215991Sdelphij#
80215991Sdelphij		.set AOUT_TEXT,0x04		# text segment size
81215991Sdelphij		.set AOUT_DATA,0x08		# data segment size
82215991Sdelphij		.set AOUT_BSS,0x0c		# zero'd BSS size
83215991Sdelphij		.set AOUT_SYMBOLS,0x10		# symbol table
84215991Sdelphij		.set AOUT_ENTRY,0x14		# entry point
85		.set AOUT_HEADER,MEM_PAGE_SIZE	# size of the a.out header
86#
87# Segment selectors.
88#
89		.set SEL_SDATA,0x8		# Supervisor data
90		.set SEL_RDATA,0x10		# Real mode data
91		.set SEL_SCODE,0x18		# PM-32 code
92		.set SEL_SCODE16,0x20		# PM-16 code
93#
94# BTX constants
95#
96		.set INT_SYS,0x30		# BTX syscall interrupt
97#
98# Constants for reading from the CD.
99#
100		.set ERROR_TIMEOUT,0x90		# BIOS timeout on read
101		.set NUM_RETRIES,3		# Num times to retry
102		.set SECTOR_SIZE,0x800		# size of a sector
103		.set SECTOR_SHIFT,11		# number of place to shift
104		.set BUFFER_LEN,0x100		# number of sectors in buffer
105		.set MAX_READ,0xf800		# max we can read at a time
106		.set MAX_READ_SEC,MAX_READ >> SECTOR_SHIFT
107		.set MEM_READ_BUFFER,0x9000	# buffer to read from CD
108		.set MEM_VOLDESC,MEM_READ_BUFFER # volume descriptor
109		.set MEM_DIR,MEM_VOLDESC+SECTOR_SIZE # Lookup buffer
110		.set VOLDESC_LBA,0x10		# LBA of vol descriptor
111		.set VD_PRIMARY,1		# Primary VD
112		.set VD_END,255			# VD Terminator
113		.set VD_ROOTDIR,156		# Offset of Root Dir Record
114		.set DIR_LEN,0			# Offset of Dir Record length
115		.set DIR_EA_LEN,1		# Offset of EA length
116		.set DIR_EXTENT,2		# Offset of 64-bit LBA
117		.set DIR_SIZE,10		# Offset of 64-bit length
118		.set DIR_NAMELEN,32		# Offset of 8-bit name len
119		.set DIR_NAME,33		# Offset of dir name
120
121#
122# Program start.
123#
124		.code16
125		.globl start
126
127start:		jmp main
128
129		.org 4
130		.ascii "IPL1   "
131
132main:		cld
133
134		/* Setup the stack */
135		xor %ax,%ax
136		mov %ax,%ss
137		mov $STACK_OFF,%sp
138
139		push %ecx
140
141		/* Setup graphic screen */
142		mov $0x42,%ah			# 640x400
143		mov $0xc0,%ch
144		int $0x18
145		mov $0x40,%ah			# graph on
146		int $0x18
147
148		/* Setup text screen */
149		mov $0x0a00,%ax			# 80x25
150		int $0x18
151		mov $0x0c,%ah			# text on
152		int $0x18
153		mov $0x13,%ah			# cursor home
154		xor %dx,%dx
155		int $0x18
156		mov $0x11,%ah			# cursor on
157		int $0x18
158
159		/* Setup keyboard */
160		mov $0x03,%ah
161		int $0x18
162
163		/* Transfer PC-9801 system common area */
164		xor %ax,%ax
165		mov %ax,%si
166		mov %ax,%ds
167		mov %ax,%di
168		mov $MEM_SYS,%ax
169		mov %ax,%es
170		mov $0x0600,%cx
171		rep
172		movsb
173
174		/* Transfer EPSON machine type */
175		mov $0xfd00,%ax
176		mov %ax,%ds
177		mov (0x804),%eax
178		and $0x00ffffff,%eax
179		mov %eax,%es:(EPSON_ID)
180
181		/* Set machine type to PC98_SYSTEM_PARAMETER */
182		call machine_check
183
184		/* Load cdboot */
185		xor %ax,%ax
186		mov %ax,%ds
187		mov $0x06,%ah		/* Read data */
188		mov (DAUA),%al		/* Read drive */
189		pop %ecx		/* cylinder */
190		xor %dx,%dx		/* head / sector */
191		mov $LOAD_SEG,%bx	/* Load address */
192		mov %bx,%es
193		xor %bp,%bp
194		mov $LOAD_SIZE,%bx	/* Load size */
195		int $0x1b
196		mov $msg_readerr,%si
197		jc error
198
199		/* Jump to cdboot */
200		ljmp $LOAD_SEG,$cdboot
201
202#
203# Set machine type to PC98_SYSTEM_PARAMETER.
204#
205machine_check:	xor %edx,%edx
206		mov %dx,%ds
207		mov $MEM_SYS,%ax
208		mov %ax,%es
209
210		/* Wait V-SYNC */
211vsync.1:	inb $0x60,%al
212		test $0x20,%al
213		jnz vsync.1
214vsync.2:	inb $0x60,%al
215		test $0x20,%al
216		jz vsync.2
217
218		/* ANK 'A' font */
219		xor %al,%al
220		outb %al,$0xa1
221		mov $0x41,%al
222		outb %al,$0xa3
223
224		/* Get 'A' font from CG window */
225		push %ds
226		mov $0xa400,%ax
227		mov %ax,%ds
228		xor %eax,%eax
229		xor %bx,%bx
230		mov $4,%cx
231font.1:		add (%bx),%eax
232		add $4,%bx
233		loop font.1
234		pop %ds
235		cmp $0x6efc58fc,%eax
236		jnz m_epson
237
238m_pc98:		or $M_NEC_PC98,%edx
239		mov $0x0458,%bx
240		mov (%bx),%al
241		test $0x80,%al
242		jz m_not_h98
243		or $M_H98,%edx
244		jmp 1f
245m_epson:	or $M_EPSON_PC98,%edx
246m_not_h98:	or $M_NOT_H98,%edx
247
2481:		inb $0x42,%al
249		test $0x20,%al
250		jz 1f
251		or $M_8M,%edx
252
2531:		mov $0x0400,%bx
254		mov (%bx),%al
255		test $0x80,%al
256		jz 1f
257		or $M_NOTE,%edx
258
2591:		mov $PC98_MACHINE_TYPE,%bx
260		mov %edx,%es:(%bx)
261		ret
262
263#
264# Print out the error message at [SI], wait for a keypress, and then
265# reboot the machine.
266#
267error:		call putstr
268		mov $msg_keypress,%si
269		call putstr
270		xor %ax,%ax			# Get keypress
271		int $0x18
272		xor %ax,%ax			# CPU reset
273		outb %al,$0xf0
274halt:		hlt
275		jmp halt			# Spin
276
277#
278# Display a null-terminated string at [SI].
279#
280# Trashes: AX, BX, CX, DX, SI, DI
281#
282putstr:		push %ds
283		push %es
284		mov %cs,%ax
285		mov %ax,%ds
286		mov $0xa000,%ax
287		mov %ax,%es
288		mov cursor,%di
289		mov $0x00e1,%bx			# Attribute
290		mov $160,%cx
291putstr.0:	lodsb
292		testb %al,%al
293		jz putstr.done
294		cmp $0x0d,%al
295		jz putstr.cr
296		cmp $0x0a,%al
297		jz putstr.lf
298		mov %bl,%es:0x2000(%di)
299		stosb
300		inc %di
301		jmp putstr.move
302putstr.cr:	xor %dx,%dx
303		mov %di,%ax
304		div %cx
305		sub %dx,%di
306		jmp putstr.move
307putstr.lf:	add %cx,%di
308putstr.move:	mov %di,%dx
309		mov $0x13,%ah			# Move cursor
310		int $0x18
311		jmp putstr.0
312putstr.done:	mov %di,cursor
313		pop %es
314		pop %ds
315		ret
316
317#
318# Display a single char at [AL], but don't move a cursor.
319#
320putc:		push %es
321		push %di
322		push %bx
323		mov $0xa000,%bx
324		mov %bx,%es
325		mov cursor,%di
326		mov $0xe1,%bl			# Attribute
327		mov %bl,%es:0x2000(%di)
328		stosb
329		pop %bx
330		pop %di
331		pop %es
332		ret
333
334msg_readerr:	.asciz "Read Error\r\n"
335msg_keypress:	.asciz "\r\nPress any key to reboot\r\n"
336
337/* Boot signature */
338
339		.org SIG1_OFF,0x90
340
341		.word 0xaa55			# Magic number
342
343#
344# cdboot
345#
346cdboot:		mov %cs,%ax
347		mov %ax,%ds
348		xor %ax,%ax
349		mov %ax,%es
350		mov %es:(DAUA),%al		# Save BIOS boot device
351		mov %al,drive
352		mov %cx,cylinder		# Save BIOS boot cylinder
353
354		mov $msg_welcome,%si		# %ds:(%si) -> welcome message
355		call putstr			# display the welcome message
356#
357# Setup the arguments that the loader is expecting from boot[12]
358#
359		mov $msg_bootinfo,%si		# %ds:(%si) -> boot args message
360		call putstr			# display the message
361		mov $MEM_ARG,%bx		# %ds:(%bx) -> boot args
362		mov %bx,%di			# %es:(%di) -> boot args
363		xor %eax,%eax			# zero %eax
364		mov $(MEM_ARG_SIZE/4),%cx	# Size of arguments in 32-bit
365						#  dwords
366		rep				# Clear the arguments
367		stosl				#  to zero
368		mov drive,%dl			# Store BIOS boot device
369		mov %dl,%es:0x4(%bx)		#  in kargs->bootdev
370		or $KARGS_FLAGS_CD,%es:0x8(%bx)	# kargs->bootflags |=
371						#  KARGS_FLAGS_CD
372#
373# Load Volume Descriptor
374#
375		mov $VOLDESC_LBA,%eax		# Set LBA of first VD
376load_vd:	push %eax			# Save %eax
377		mov $1,%dh			# One sector
378		mov $MEM_VOLDESC,%ebx		# Destination
379		call read			# Read it in
380		cmpb $VD_PRIMARY,%es:(%bx)	# Primary VD?
381		je have_vd			# Yes
382		pop %eax			# Prepare to
383		inc %eax			#  try next
384		cmpb $VD_END,%es:(%bx)		# Last VD?
385		jne load_vd			# No, read next
386		mov $msg_novd,%si		# No VD
387		jmp error			# Halt
388have_vd:					# Have Primary VD
389#
390# Try to look up the loader binary using the paths in the loader_paths
391# array.
392#
393		mov $loader_paths,%si		# Point to start of array
394lookup_path:	push %si			# Save file name pointer
395		call lookup			# Try to find file
396		pop %di				# Restore file name pointer
397		jnc lookup_found		# Found this file
398		push %es
399		mov %cs,%ax
400		mov %ax,%es
401		xor %al,%al			# Look for next
402		mov $0xffff,%cx			#  path name by
403		repnz				#  scanning for
404		scasb				#  nul char
405		pop %es
406		mov %di,%si			# Point %si at next path
407		mov (%si),%al			# Get first char of next path
408		or %al,%al			# Is it double nul?
409		jnz lookup_path			# No, try it.
410		mov $msg_failed,%si		# Failed message
411		jmp error			# Halt
412lookup_found:					# Found a loader file
413#
414# Load the binary into the buffer.  Due to real mode addressing limitations
415# we have to read it in 64k chunks.
416#
417		mov %es:DIR_SIZE(%bx),%eax	# Read file length
418		add $SECTOR_SIZE-1,%eax		# Convert length to sectors
419		shr $SECTOR_SHIFT,%eax
420		cmp $BUFFER_LEN,%eax
421		jbe load_sizeok
422		mov $msg_load2big,%si		# Error message
423		jmp error
424load_sizeok:	movzbw %al,%cx			# Num sectors to read
425		mov %es:DIR_EXTENT(%bx),%eax	# Load extent
426		xor %edx,%edx
427		mov %es:DIR_EA_LEN(%bx),%dl
428		add %edx,%eax			# Skip extended
429		mov $MEM_READ_BUFFER,%ebx	# Read into the buffer
430load_loop:	mov %cl,%dh
431		cmp $MAX_READ_SEC,%cl		# Truncate to max read size
432		jbe load_notrunc
433		mov $MAX_READ_SEC,%dh
434load_notrunc:	sub %dh,%cl			# Update count
435		push %eax			# Save
436		call read			# Read it in
437		pop %eax			# Restore
438		add $MAX_READ_SEC,%eax		# Update LBA
439		add $MAX_READ,%ebx		# Update dest addr
440		jcxz load_done			# Done?
441		jmp load_loop			# Keep going
442load_done:
443#
444# Turn on the A20 address line
445#
446		xor %ax,%ax			# Turn A20 on
447		outb %al,$0xf2
448		mov $0x02,%al
449		outb %al,$0xf6
450#
451# Relocate the loader and BTX using a very lazy protected mode
452#
453		mov $msg_relocate,%si		# Display the
454		call putstr			#  relocation message
455		mov %es:(MEM_READ_BUFFER+AOUT_ENTRY),%edi # %edi is the destination
456		mov $(MEM_READ_BUFFER+AOUT_HEADER),%esi	# %esi is
457						#  the start of the text
458						#  segment
459		mov %es:(MEM_READ_BUFFER+AOUT_TEXT),%ecx # %ecx = length of the text
460						#  segment
461		push %edi			# Save entry point for later
462		lgdt gdtdesc			# setup our own gdt
463		cli				# turn off interrupts
464		mov %cr0,%eax			# Turn on
465		or $0x1,%al			#  protected
466		mov %eax,%cr0			#  mode
467		ljmp $SEL_SCODE,$pm_start	# long jump to clear the
468						#  instruction pre-fetch queue
469		.code32
470pm_start:	mov $SEL_SDATA,%ax		# Initialize
471		mov %ax,%ds			#  %ds and
472		mov %ax,%es			#  %es to a flat selector
473		rep				# Relocate the
474		movsb				#  text segment
475		add $(MEM_PAGE_SIZE - 1),%edi	# pad %edi out to a new page
476		and $~(MEM_PAGE_SIZE - 1),%edi #  for the data segment
477		mov MEM_READ_BUFFER+AOUT_DATA,%ecx # size of the data segment
478		rep				# Relocate the
479		movsb				#  data segment
480		mov MEM_READ_BUFFER+AOUT_BSS,%ecx # size of the bss
481		xor %eax,%eax			# zero %eax
482		add $3,%cl			# round %ecx up to
483		shr $2,%ecx			#  a multiple of 4
484		rep				# zero the
485		stosl				#  bss
486		mov MEM_READ_BUFFER+AOUT_ENTRY,%esi # %esi -> relocated loader
487		add $MEM_BTX_OFFSET,%esi	# %esi -> BTX in the loader
488		mov $MEM_BTX_ADDRESS,%edi	# %edi -> where BTX needs to go
489		movzwl 0xa(%esi),%ecx		# %ecx -> length of BTX
490		rep				# Relocate
491		movsb				#  BTX
492		ljmp $SEL_SCODE16,$pm_16	# Jump to 16-bit PM
493		.code16
494pm_16:		mov $SEL_RDATA,%ax		# Initialize
495		mov %ax,%ds			#  %ds and
496		mov %ax,%es			#  %es to a real mode selector
497		mov %cr0,%eax			# Turn off
498		and $~0x1,%al			#  protected
499		mov %eax,%cr0			#  mode
500		ljmp $LOAD_SEG,$pm_end		# Long jump to clear the
501						#  instruction pre-fetch queue
502pm_end:		sti				# Turn interrupts back on now
503#
504# Copy the BTX client to MEM_BTX_CLIENT
505#
506		mov %cs,%ax
507		mov %ax,%ds
508		xor %ax,%ax
509		mov %ax,%es
510		mov $MEM_BTX_CLIENT,%di		# Prepare to relocate
511		mov $btx_client,%si		#  the simple btx client
512		mov $(btx_client_end-btx_client),%cx # length of btx client
513		rep				# Relocate the
514		movsb				#  simple BTX client
515#
516# Copy the boot[12] args to where the BTX client can see them
517#
518		xor %ax,%ax
519		mov %ax,%ds
520		mov $MEM_ARG,%si		# where the args are at now
521		mov $MEM_ARG_BTX,%di		# where the args are moving to
522		mov $(MEM_ARG_SIZE/4),%cx	# size of the arguments in longs
523		rep				# Relocate
524		movsl				#  the words
525#
526# Save the entry point so the client can get to it later on
527#
528		pop %eax			# Restore saved entry point
529		stosl				#  and add it to the end of
530						#  the arguments
531#
532# Now we just start up BTX and let it do the rest
533#
534		mov $msg_jump,%si		# Display the
535		call putstr			#  jump message
536		ljmp $0,$MEM_BTX_ENTRY		# Jump to the BTX entry point
537
538#
539# Lookup the file in the path at [SI] from the root directory.
540#
541# Trashes: All but BX
542# Returns: CF = 0 (success), BX = pointer to record
543#          CF = 1 (not found)
544#
545lookup:		mov $VD_ROOTDIR+MEM_VOLDESC,%bx	# Root directory record
546		push %bx
547		push %si
548		mov $msg_lookup,%si		# Display lookup message
549		call putstr
550		pop %si
551		push %si
552		call putstr
553		mov $msg_lookup2,%si
554		call putstr
555		pop %si
556		pop %bx
557lookup_dir:	lodsb				# Get first char of path
558		cmp $0,%al			# Are we done?
559		je lookup_done			# Yes
560		cmp $'/',%al			# Skip path separator.
561		je lookup_dir
562		dec %si				# Undo lodsb side effect
563		call find_file			# Lookup first path item
564		jnc lookup_dir			# Try next component
565		mov $msg_lookupfail,%si		# Not found message
566		push %bx
567		call putstr
568		pop %bx
569		stc				# Set carry
570		ret
571lookup_done:	mov $msg_lookupok,%si		# Success message
572		push %bx
573		call putstr
574		pop %bx
575		clc				# Clear carry
576		ret
577
578#
579# Lookup file at [SI] in directory whose record is at [BX].
580#
581# Trashes: All but returns
582# Returns: CF = 0 (success), BX = pointer to record, SI = next path item
583#          CF = 1 (not found), SI = preserved
584#
585find_file:	mov %es:DIR_EXTENT(%bx),%eax	# Load extent
586		xor %edx,%edx
587		mov %es:DIR_EA_LEN(%bx),%dl
588		add %edx,%eax			# Skip extended attributes
589		mov %eax,rec_lba		# Save LBA
590		mov %es:DIR_SIZE(%bx),%eax	# Save size
591		mov %eax,rec_size
592		xor %cl,%cl			# Zero length
593		push %si			# Save
594ff.namelen:	inc %cl				# Update length
595		lodsb				# Read char
596		cmp $0,%al			# Nul?
597		je ff.namedone			# Yes
598		cmp $'/',%al			# Path separator?
599		jnz ff.namelen			# No, keep going
600ff.namedone:	dec %cl				# Adjust length and save
601		mov %cl,name_len
602		pop %si				# Restore
603ff.load:	mov rec_lba,%eax		# Load LBA
604		mov $MEM_DIR,%ebx		# Address buffer
605		mov $1,%dh			# One sector
606		call read			# Read directory block
607		incl rec_lba			# Update LBA to next block
608ff.scan:	mov %ebx,%edx			# Check for EOF
609		sub $MEM_DIR,%edx
610		cmp %edx,rec_size
611		ja ff.scan.1
612		stc				# EOF reached
613		ret
614ff.scan.1:	cmpb $0,%es:DIR_LEN(%bx)	# Last record in block?
615		je ff.nextblock
616		push %si			# Save
617		movzbw %es:DIR_NAMELEN(%bx),%si	# Find end of string
618ff.checkver:	cmpb $'0',%es:DIR_NAME-1(%bx,%si)	# Less than '0'?
619		jb ff.checkver.1
620		cmpb $'9',%es:DIR_NAME-1(%bx,%si)	# Greater than '9'?
621		ja ff.checkver.1
622		dec %si				# Next char
623		jnz ff.checkver
624		jmp ff.checklen			# All numbers in name, so
625						#  no version
626ff.checkver.1:	movzbw %es:DIR_NAMELEN(%bx),%cx
627		cmp %cx,%si			# Did we find any digits?
628		je ff.checkdot			# No
629		cmpb $';',%es:DIR_NAME-1(%bx,%si)	# Check for semicolon
630		jne ff.checkver.2
631		dec %si				# Skip semicolon
632		mov %si,%cx
633		mov %cl,%es:DIR_NAMELEN(%bx)	# Adjust length
634		jmp ff.checkdot
635ff.checkver.2:	mov %cx,%si			# Restore %si to end of string
636ff.checkdot:	cmpb $'.',%es:DIR_NAME-1(%bx,%si)	# Trailing dot?
637		jne ff.checklen			# No
638		decb %es:DIR_NAMELEN(%bx)	# Adjust length
639ff.checklen:	pop %si				# Restore
640		movzbw name_len,%cx		# Load length of name
641		cmp %cl,%es:DIR_NAMELEN(%bx)	# Does length match?
642		je ff.checkname			# Yes, check name
643ff.nextrec:	add %es:DIR_LEN(%bx),%bl	# Next record
644		adc $0,%bh
645		jmp ff.scan
646ff.nextblock:	subl $SECTOR_SIZE,rec_size	# Adjust size
647		jnc ff.load			# If subtract ok, keep going
648		ret				# End of file, so not found
649ff.checkname:	lea DIR_NAME(%bx),%di		# Address name in record
650		push %si			# Save
651		repe cmpsb			# Compare name
652		je ff.match			# We have a winner!
653		pop %si				# Restore
654		jmp ff.nextrec			# Keep looking.
655ff.match:	add $2,%sp			# Discard saved %si
656		clc				# Clear carry
657		ret
658
659#
660# Load DH sectors starting at LBA EAX into [EBX].
661#
662# Trashes: EAX
663#
664read:		push %es			# Save
665		push %bp
666		push %dx
667		push %cx
668		push %ebx
669		mov %bx,%bp			# Set destination address
670		and $0x000f,%bp
671		shr $4,%ebx
672		mov %bx,%es
673		xor %bx,%bx			# Set read bytes
674		mov %dh,%bl
675		shl $SECTOR_SHIFT,%bx		# 2048 bytes/sec
676		mov %ax,%cx			# Set LBA
677		shr $16,%eax
678		mov %ax,%dx
679read.retry:	mov $0x06,%ah			# BIOS device read
680		mov drive,%al
681		and $0x7f,%al
682		call twiddle			# Entertain the user
683		int $0x1b			# Call BIOS
684		jc read.fail			# Worked?
685		pop %ebx			# Restore
686		pop %cx
687		pop %dx
688		pop %bp
689		pop %es
690		ret				# Return
691read.fail:	cmp $ERROR_TIMEOUT,%ah		# Timeout?
692		je read.retry			# Yes, Retry.
693read.error:	mov %ah,%al			# Save error
694		mov $hex_error,%di		# Format it
695		call hex8			#  as hex
696		mov $msg_badread,%si		# Display Read error message
697		jmp error
698
699#
700# Output the "twiddle"
701#
702twiddle:	push %ax			# Save
703		push %bx			# Save
704		mov twiddle_index,%al		# Load index
705		mov $twiddle_chars,%bx		# Address table
706		inc %al				# Next
707		and $3,%al			#  char
708		mov %al,twiddle_index		# Save index for next call
709		xlat				# Get char
710		call putc			# Output it
711		pop %bx				# Restore
712		pop %ax				# Restore
713		ret
714
715#
716# Convert AL to hex, saving the result to [EDI].
717#
718hex8:		pushl %eax			# Save
719		shrb $0x4,%al			# Do upper
720		call hex8.1			#  4
721		popl %eax			# Restore
722hex8.1: 	andb $0xf,%al			# Get lower 4
723		cmpb $0xa,%al			# Convert
724		sbbb $0x69,%al			#  to hex
725		das				#  digit
726		orb $0x20,%al			# To lower case
727		mov %al,(%di)			# Save char
728		inc %di
729		ret				# (Recursive)
730
731#
732# BTX client to start btxldr
733#
734		.code32
735btx_client:	mov $(MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE-4), %esi
736						# %ds:(%esi) -> end
737						#  of boot[12] args
738		mov $(MEM_ARG_SIZE/4),%ecx	# Number of words to push
739		std				# Go backwards
740push_arg:	lodsl				# Read argument
741		push %eax			# Push it onto the stack
742		loop push_arg			# Push all of the arguments
743		cld				# In case anyone depends on this
744		pushl MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE # Entry point of
745						#  the loader
746		push %eax			# Emulate a near call
747		mov $0x1,%eax			# 'exec' system call
748		int $INT_SYS			# BTX system call
749btx_client_end:
750		.code16
751
752		.p2align 4
753#
754# Global descriptor table.
755#
756gdt:		.word 0x0,0x0,0x0,0x0			# Null entry
757		.word 0xffff,0x0000,0x9200,0x00cf	# SEL_SDATA
758		.word 0xffff,0x0000,0x9200,0x0000	# SEL_RDATA
759		.word 0xffff,LOAD_SEG<<4,0x9a00,0x00cf	# SEL_SCODE (32-bit)
760		.word 0xffff,LOAD_SEG<<4,0x9a00,0x008f	# SEL_SCODE16 (16-bit)
761gdt.1:
762#
763# Pseudo-descriptors.
764#
765gdtdesc:	.word gdt.1-gdt-1		# Limit
766		.long LOAD_SEG<<4 + gdt		# Base
767
768#
769# BOOT device
770#
771drive:		.byte 0
772cylinder:	.word 0
773
774#
775# State for searching dir
776#
777rec_lba:	.long 0x0			# LBA (adjusted for EA)
778rec_size:	.long 0x0			# File size
779name_len:	.byte 0x0			# Length of current name
780
781cursor:		.word 0
782twiddle_index:	.byte 0x0
783
784msg_welcome:	.asciz	"CD Loader 1.2\r\n\n"
785msg_bootinfo:	.asciz	"Building the boot loader arguments\r\n"
786msg_relocate:	.asciz	"Relocating the loader and the BTX\r\n"
787msg_jump:	.asciz	"Starting the BTX loader\r\n"
788msg_badread:	.ascii  "Read Error: 0x"
789hex_error:	.asciz	"00\r\n"
790msg_novd:	.asciz  "Could not find Primary Volume Descriptor\r\n"
791msg_lookup:	.asciz  "Looking up "
792msg_lookup2:	.asciz  "... "
793msg_lookupok:	.asciz  "Found\r\n"
794msg_lookupfail:	.asciz  "File not found\r\n"
795msg_load2big:	.asciz  "File too big\r\n"
796msg_failed:	.asciz	"Boot failed\r\n"
797twiddle_chars:	.ascii	"|/-\\"
798loader_paths:	.asciz  "/BOOT.PC98/LOADER"
799		.asciz	"/boot.pc98/loader"
800		.asciz  "/BOOT/LOADER"
801		.asciz	"/boot/loader"
802		.byte 0
803
804/* Boot signature */
805
806		.org SIG2_OFF,0x90
807
808		.word 0xaa55			# Magic number
809