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