cdboot.S revision 85998
1#
2# Copyright (c) 2001 John Baldwin
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
16# $FreeBSD: head/sys/boot/i386/cdboot/cdboot.s 85998 2001-11-04 03:24:16Z jhb $
17
18#
19# This program is a freestanding boot program to load an a.out binary
20# from a CD-ROM booted with no emulation mode as described by the El
21# Torito standard.  Due to broken BIOSen that do not load the desired
22# number of sectors, we try to fit this in as small a space as possible.
23#
24# Basically, we first create a set of boot arguments to pass to the loaded
25# binary.  Then we attempt to load /boot/loader from the CD we were booted
26# off of.
27#
28
29#
30# Memory locations.
31#
32		.set MEM_PAGE_SIZE,0x1000	# memory page size, 4k
33		.set MEM_ARG,0x900		# Arguments at start
34		.set MEM_ARG_BTX,0xa100		# Where we move them to so the
35						#  BTX client can see them
36		.set MEM_ARG_SIZE,0x18		# Size of the arguments
37		.set MEM_BTX_ADDRESS,0x9000	# where BTX lives
38		.set MEM_BTX_ENTRY,0x9010	# where BTX starts to execute
39		.set MEM_BTX_OFFSET,MEM_PAGE_SIZE # offset of BTX in the loader
40		.set MEM_BTX_CLIENT,0xa000	# where BTX clients live
41#
42# a.out header fields
43#
44		.set AOUT_TEXT,0x04		# text segment size
45		.set AOUT_DATA,0x08		# data segment size
46		.set AOUT_BSS,0x0c		# zero'd BSS size
47		.set AOUT_SYMBOLS,0x10		# symbol table
48		.set AOUT_ENTRY,0x14		# entry point
49		.set AOUT_HEADER,MEM_PAGE_SIZE	# size of the a.out header
50#
51# Flags for kargs->bootflags
52#
53		.set KARGS_FLAGS_CD,0x1		# flag to indicate booting from
54						#  CD loader
55#
56# Segment selectors.
57#
58		.set SEL_SDATA,0x8		# Supervisor data
59		.set SEL_RDATA,0x10		# Real mode data
60		.set SEL_SCODE,0x18		# PM-32 code
61		.set SEL_SCODE16,0x20		# PM-16 code
62#
63# BTX constants
64#
65		.set INT_SYS,0x30		# BTX syscall interrupt
66#
67# Constants for reading from the CD.
68#
69		.set ERROR_TIMEOUT,0x80		# BIOS timeout on read
70		.set NUM_RETRIES,3		# Num times to retry
71		.set SECTOR_SIZE,0x800		# size of a sector
72		.set SECTOR_SHIFT,11		# number of place to shift
73		.set BUFFER_LEN,0x100		# number of sectors in buffer
74		.set MAX_READ,0x10000		# max we can read at a time
75		.set MAX_READ_SEC,MAX_READ >> SECTOR_SHIFT
76		.set MEM_READ_BUFFER,0x9000	# buffer to read from CD
77		.set MEM_VOLDESC,MEM_READ_BUFFER # volume descriptor
78		.set MEM_DIR,MEM_VOLDESC+SECTOR_SIZE # Lookup buffer
79		.set VOLDESC_LBA,0x10		# LBA of vol descriptor
80		.set VD_PRIMARY,1		# Primary VD
81		.set VD_END,255			# VD Terminator
82		.set VD_ROOTDIR,156		# Offset of Root Dir Record
83		.set DIR_LEN,0			# Offset of Dir Record length
84		.set DIR_EA_LEN,1		# Offset of EA length
85		.set DIR_EXTENT,2		# Offset of 64-bit LBA
86		.set DIR_SIZE,10		# Offset of 64-bit length
87		.set DIR_NAMELEN,32		# Offset of 8-bit name len
88		.set DIR_NAME,33		# Offset of dir name
89#
90# We expect to be loaded by the BIOS at 0x7c00 (standard boot loader entry
91# point)
92#
93		.code16
94		.globl start
95		.org 0x0, 0x0
96#
97# Program start.
98#
99start:		cld				# string ops inc
100		xor %ax,%ax			# zero %ax
101		mov %ax,%ss			# setup the
102		mov $start,%sp			#  stack
103		mov %ax,%ds			# setup the
104		mov %ax,%es			#  data segments
105		mov %dl,drive			# Save BIOS boot device
106		mov $0xe3,%al
107		xor %dx,%dx
108		int $0x14			# Init COM1 9600,n,8,1
109		mov $msg_welcome,%si		# %ds:(%si) -> welcome message
110		call putstr			# display the welcome message
111#
112# Setup the arguments that the loader is expecting from boot[12]
113#
114		mov $msg_bootinfo,%si		# %ds:(%si) -> boot args message
115		call putstr			# display the message
116		mov $MEM_ARG,%bx		# %ds:(%bx) -> boot args
117		mov %bx,%di			# %es:(%di) -> boot args
118		xor %eax,%eax			# zero %eax
119		mov $(MEM_ARG_SIZE/4),%cx	# Size of arguments in 32-bit
120						#  dwords
121		rep				# Clear the arguments
122		stosl				#  to zero
123		mov drive,%dl			# Store BIOS boot device
124		mov %dl,0x4(%bx)		#  in kargs->bootdev
125		or $KARGS_FLAGS_CD,0x8(%bx)	# kargs->bootflags |=
126						#  KARGS_FLAGS_CD
127#
128# Load Volume Descriptor
129#
130		mov $VOLDESC_LBA,%eax		# Set LBA of first VD
131load_vd:	push %eax			# Save %eax
132		mov $1,%dh			# One sector
133		mov $MEM_VOLDESC,%ebx		# Destination
134		call read			# Read it in
135		mov $16,%cx
136		call hexdump
137		cmpb $VD_PRIMARY,(%bx)		# Primary VD?
138		je have_vd			# Yes
139		pop %eax			# Prepare to
140		inc %eax			#  try next
141		cmpb $VD_END,(%bx)		# Last VD?
142		jne load_vd			# No, read next
143		mov $msg_novd,%si		# No VD
144		jmp error			# Halt
145have_vd:	mov $msg_vd,%si			# Have Primary VD
146		call putstr
147#
148# Lookup the loader binary.
149#
150		mov $loader_path,%si		# File to lookup
151		call lookup			# Try to find it
152		mov $msg_lookup_done,%si
153		call putstr
154#
155# Load the binary into the buffer.  Due to real mode addressing limitations
156# we have to read it in in 64k chunks.
157#
158		mov DIR_SIZE(%bx),%eax		# Read file length
159		add $SECTOR_SIZE-1,%eax		# Convert length to sectors
160		shr $11,%eax
161		cmp $BUFFER_LEN,%eax
162		jbe load_sizeok
163		mov $msg_load2big,%si		# Error message
164		call error
165load_sizeok:	movzbw %al,%cx			# Num sectors to read
166		mov DIR_EXTENT(%bx),%eax	# Load extent
167		xor %edx,%edx
168		mov DIR_EA_LEN(%bx),%dl
169		add %edx,%eax			# Skip extended
170		mov $MEM_READ_BUFFER,%ebx	# Read into the buffer
171load_loop:	mov %cl,%dh
172		cmp $MAX_READ_SEC,%cl		# Truncate to max read size
173		jbe load_notrunc
174		mov $MAX_READ_SEC,%dh
175load_notrunc:	sub %dh,%cl			# Update count
176		push %eax			# Save
177		call read			# Read it in
178		pop %eax			# Restore
179		add $MAX_READ_SEC,%eax		# Update LBA
180		add $MAX_READ,%ebx		# Update dest addr
181		jcxz load_done			# Done?
182		jmp load_loop			# Keep going
183load_done:
184#
185# Turn on the A20 address line
186#
187		call seta20			# Turn A20 on
188#
189# Relocate the loader and BTX using a very lazy protected mode
190#
191		mov $msg_relocate,%si		# Display the
192		call putstr			#  relocation message
193		mov MEM_READ_BUFFER+AOUT_ENTRY,%edi # %edi is the destination
194		mov $(MEM_READ_BUFFER+AOUT_HEADER),%esi	# %esi is
195						#  the start of the text
196						#  segment
197		mov MEM_READ_BUFFER+AOUT_TEXT,%ecx # %ecx = length of the text
198						#  segment
199		push %edi			# Save entry point for later
200		lgdt gdtdesc			# setup our own gdt
201		cli				# turn off interrupts
202		mov %cr0,%eax			# Turn on
203		or $0x1,%al			#  protected
204		mov %eax,%cr0			#  mode
205		ljmp $SEL_SCODE,$pm_start	# long jump to clear the
206						#  instruction pre-fetch queue
207		.code32
208pm_start:	mov $SEL_SDATA,%ax		# Initialize
209		mov %ax,%ds			#  %ds and
210		mov %ax,%es			#  %es to a flat selector
211		rep				# Relocate the
212		movsb				#  text segment
213		add $(MEM_PAGE_SIZE - 1),%edi	# pad %edi out to a new page
214		and $~(MEM_PAGE_SIZE - 1),%edi #  for the data segment
215		mov MEM_READ_BUFFER+AOUT_DATA,%ecx # size of the data segment
216		rep				# Relocate the
217		movsb				#  data segment
218		mov MEM_READ_BUFFER+AOUT_BSS,%ecx # size of the bss
219		xor %eax,%eax			# zero %eax
220		add $3,%cl			# round %ecx up to
221		shr $2,%ecx			#  a multiple of 4
222		rep				# zero the
223		stosl				#  bss
224		mov MEM_READ_BUFFER+AOUT_ENTRY,%esi # %esi -> relocated loader
225		add $MEM_BTX_OFFSET,%esi	# %esi -> BTX in the loader
226		mov $MEM_BTX_ADDRESS,%edi	# %edi -> where BTX needs to go
227		movzwl 0xa(%esi),%ecx		# %ecx -> length of BTX
228		rep				# Relocate
229		movsb				#  BTX
230		ljmp $SEL_SCODE16,$pm_16	# Jump to 16-bit PM
231		.code16
232pm_16:		mov $SEL_RDATA,%ax		# Initialize
233		mov %ax,%ds			#  %ds and
234		mov %ax,%es			#  %es to a real mode selector
235		mov %cr0,%eax			# Turn off
236		and $~0x1,%al			#  protected
237		mov %eax,%cr0			#  mode
238		ljmp $0,$pm_end			# Long jump to clear the
239						#  instruction pre-fetch queue
240pm_end:		sti				# Turn interrupts back on now
241#
242# Copy the BTX client to MEM_BTX_CLIENT
243#
244		xor %ax,%ax			# zero %ax and set
245		mov %ax,%ds			#  %ds and %es
246		mov %ax,%es			#  to segment 0
247		mov $MEM_BTX_CLIENT,%di		# Prepare to relocate
248		mov $btx_client,%si		#  the simple btx client
249		mov $(btx_client_end-btx_client),%cx # length of btx client
250		rep				# Relocate the
251		movsb				#  simple BTX client
252#
253# Copy the boot[12] args to where the BTX client can see them
254#
255		mov $MEM_ARG,%si		# where the args are at now
256		mov $MEM_ARG_BTX,%di		# where the args are moving to
257		mov $(MEM_ARG_SIZE/4),%cx	# size of the arguments in longs
258		rep				# Relocate
259		movsl				#  the words
260#
261# Save the entry point so the client can get to it later on
262#
263		pop %eax			# Restore saved entry point
264		stosl				#  and add it to the end of
265						#  the arguments
266		mov $msg_entry2,%di
267		call hex32
268		mov $msg_entry,%si
269		call putstr
270#
271# Now we just start up BTX and let it do the rest
272#
273		mov $msg_jump,%si		# Display the
274		call putstr			#  jump message
275		ljmp $0,$MEM_BTX_ENTRY		# Jump to the BTX entry point
276
277#
278# Lookup the file in the path at [SI] from the root directory.
279#
280# Trashes: All but BX
281# Returns: BX = pointer to record
282#
283lookup:		mov $VD_ROOTDIR+MEM_VOLDESC,%bx	# Root directory record
284		push %si
285		mov $msg_lookup,%si		# Display lookup message
286		call putstr
287		pop %si
288		push %si
289		call putstr
290		mov $msg_lookup2,%si
291		call putstr
292		pop %si
293lookup_dir:	lodsb				# Get first char of path
294		cmp $0,%al			# Are we done?
295		je lookup_done			# Yes
296		cmp $'/',%al			# Skip path separator.
297		je lookup_dir
298		dec %si				# Undo lodsb side effect
299		call find_file			# Lookup first path item
300		jnc lookup_dir			# Try next component
301		mov $msg_lookupfail,%si		# Not found.
302		jmp error
303lookup_done:	mov $msg_lookupok,%si		# Success message
304		call putstr
305		ret
306
307#
308# Lookup file at [SI] in directory whose record is at [BX].
309#
310# Trashes: All but returns
311# Returns: CF = 0 (success), BX = pointer to record, SX = next path item
312#          CF = 1 (not found), SI = preserved
313#
314find_file:	push %si
315		mov $msg_startff,%si
316		call putstr
317		pop %si
318		movzbw DIR_LEN(%bx),%cx
319		call hexdump
320		mov DIR_EXTENT(%bx),%eax	# Load extent
321		xor %edx,%edx
322		mov DIR_EA_LEN(%bx),%dl
323		add %edx,%eax			# Skip extended attributes
324		mov %eax,rec_lba		# Save LBA
325		mov DIR_SIZE(%bx),%eax		# Save size
326		mov %eax,rec_size
327		xor %cl,%cl			# Zero length
328		push %si			# Save
329ff.namelen:	inc %cl				# Update length
330		lodsb				# Read char
331		cmp $0,%al			# Nul?
332		je ff.namedone			# Yes
333		cmp $'/',%al			# Path separator?
334		jnz ff.namelen			# No, keep going
335ff.namedone:	dec %cl				# Adjust length and save
336		mov %cl,name_len
337		mov %cl,%al
338		mov $msg_fflen,%di
339		call hex8
340		mov $msg_ffpath,%si
341		call putstr
342		pop %si
343		push %si
344		call putstr
345		mov $msg_ffpath2,%si
346		call putstr
347		pop %si				# Restore
348ff.load:	mov rec_lba,%eax		# Load LBA
349		mov $MEM_DIR,%ebx		# Address buffer
350		mov $1,%dh			# One sector
351		call read			# Read directory block
352		incl rec_lba			# Update LBA to next block
353ff.scan:	mov %ebx,%edx			# Check for EOF
354		sub $MEM_DIR,%edx
355		cmp %edx,rec_size
356		ja ff.scan.1
357		stc				# EOF reached
358		ret
359ff.scan.1:	cmpb $0,DIR_LEN(%bx)		# Last record in block?
360		je ff.nextblock
361		movzbw DIR_LEN(%bx),%cx
362		call hexdump
363		push %si			# Save
364		mov $msg_ffscan,%si
365		call putstr
366		movzbw DIR_NAMELEN(%bx),%si	# Find end of string
367ff.checkver:	push %bx
368		mov DIR_NAME-1(%bx,%si),%al
369		call putc
370		pop %bx
371		cmpb $'0',DIR_NAME-1(%bx,%si)	# Less than '0'?
372		jb ff.checkver.1
373		cmpb $'9',DIR_NAME-1(%bx,%si)	# Greater than '9'?
374		ja ff.checkver.1
375		dec %si				# Next char
376		jnz ff.checkver
377		jmp ff.checklen			# All numbers in name, so
378						#  no version
379ff.checkver.1:	movzbw DIR_NAMELEN(%bx),%cx
380		cmp %cx,%si			# Did we find any digits?
381		je ff.checkdot			# No
382		push %bx
383		mov DIR_NAME-1(%bx,%si),%al
384		call putc
385		pop %bx
386		cmpb $';',DIR_NAME-1(%bx,%si)	# Check for semicolon
387		jne ff.checkver.2
388		dec %si				# Skip semicolon
389		mov %si,%cx
390		mov %cl,DIR_NAMELEN(%bx)	# Adjust length
391		push %bx
392		mov $'-',%al
393		call putc
394		pop %bx
395		jmp ff.checkdot
396ff.checkver.2:	mov %cx,%si			# Restore %si to end of string
397ff.checkdot:	cmpb $'.',DIR_NAME-1(%bx,%si)	# Trailing dot?
398		jne ff.checklen			# No
399		push %bx
400		mov $'-',%al
401		call putc
402		pop %bx
403		decb DIR_NAMELEN(%bx)		# Adjust length
404ff.checklen:	pop %si				# Restore
405		push %si
406		mov $msg_ffscan2,%si
407		call putstr
408		mov $msg_ffcheck,%si
409		call putstr
410		lea DIR_NAMELEN(%bx),%si
411		call putstrl
412		mov $msg_ffcheck2,%si
413		call putstr
414		pop %si
415		movzbw name_len,%cx		# Load length of name
416		cmp %cl,DIR_NAMELEN(%bx)	# Does length match?
417		je ff.checkname			# Yes, check name
418ff.nextrec:	add DIR_LEN(%bx),%bl		# Next record
419		adc $0,%bh
420		jmp ff.scan
421ff.nextblock:	subl $SECTOR_SIZE,rec_size	# Adjust size
422		jnc ff.load			# If subtract ok, keep going
423		ret				# End of file, so not found
424ff.checkname:	push %si
425		mov $msg_lenmatch,%si
426		call putstr
427		pop %si
428		lea DIR_NAME(%bx),%di		# Address name in record
429		push %si			# Save
430		repe cmpsb			# Compare name
431		jcxz ff.match			# We have a winner!
432		pop %si				# Restore
433		jmp ff.nextrec			# Keep looking.
434ff.match:	add $2,%sp			# Discard saved %si
435		clc				# Clear carry
436		ret
437
438#
439# Load DH sectors starting at LBA EAX into [EBX].
440#
441# Trashes: EAX
442#
443read:		push %si			# Save
444		mov %eax,edd_lba		# LBA to read from
445		mov %ebx,%eax			# Convert address
446		shr $4,%eax			#  to segment
447		mov %ax,edd_addr+0x2		#  and store
448read.retry:	#call twiddle			# Entertain the user
449		push %dx			# Save
450		push %di			# DEBUG: dump packet
451		push %bx
452		mov %dh,%al			# Length
453		mov $dump_len,%di
454		call hex8
455		mov edd_addr+0x2,%ax		# Seg
456		mov $dump_seg,%di
457		call hex16
458		mov edd_addr,%ax		# Offset
459		mov $dump_offset,%di
460		call hex16
461		mov edd_lba,%eax		# LBA
462		mov $dump_lba,%di
463		call hex32
464		mov $dump_packet,%si		# Display
465		call putstr
466		pop %bx
467		pop %di
468		mov $edd_packet,%si		# Address Packet
469		mov %dh,edd_len			# Set length
470		mov drive,%dl			# BIOS Device
471		mov $0x42,%ah			# BIOS: Extended Read
472		int $0x13			# Call BIOS
473		pop %dx				# Restore
474		jc read.fail			# Worked?
475		pop %si				# Restore
476		ret				# Return
477read.fail:	cmp $ERROR_TIMEOUT,%ah		# Timeout?
478		je read.retry			# Yes, Retry.
479read.error:	mov %ah,%al			# Save error
480		mov $hex_error,%di		# Format it
481		call hex8			#  as hex
482		mov $msg_badread,%si		# Display Read error message
483
484#
485# Display error message at [SI] and halt.
486#
487error:		call putstr			# Display message
488halt:		hlt
489		jmp halt			# Spin
490
491#
492# Dump CX bytes from memory at [BX].
493#
494hexdump:	push %ax			# Save
495		push %bx			# Save
496		push %dx			# Save
497		push %si			# Save
498		push %di			# Save
499		mov %bx,%si			# Where to read from
500hd.line:	mov $16,%dx			# Bytes per line
501		push %si			# Save offset
502		push %cx			# Save
503		push %dx			#  counts
504		mov $hex_line,%di
505		mov %si,%ax			# Format hex
506		call hex16			#  offset
507		inc %di
508hd.hexloop:	jcxz hd.hexblank		# Are we done yet?
509		lodsb				# Read
510		call hex8			# Hexify
511		inc %di
512		dec %cx				# Update total count
513		dec %dx				#  and per-line count
514		jnz hd.hexloop			# Next char
515		jmp hd.raw			# Second half of line
516hd.hexblank:	mov $' ',%al			# Put spaces as
517hd.hb.loop:	stosb				#  placeholders
518		stosb
519		inc %di
520		dec %dx				# Just do per-line count
521		jnz hd.hb.loop			# Next blank
522hd.raw:		pop %dx				# Restore
523		pop %cx				#  counts
524		pop %si				# Restart input
525		inc %di				# Skip pipe char
526hd.rawloop:	jcxz hd.rawblank		# Done yet?
527		lodsb				# Read
528		cmp $0x20,%al			# Use '.' for
529		jge hd.rawok			#  special
530		mov $'.',%al			#  characters
531hd.rawok:	stosb
532		dec %cx
533		dec %dx
534		jnz hd.rawloop			# Next char
535		jmp hd.outline			# Next line
536hd.rawblank:	mov $' ',%al			# Space as placeholder
537		mov %dx,%cx			# Fill rest
538		rep stosb			#  of line
539hd.outline:	push %si			# Save
540		mov $hex_line,%si		# Now spit it out
541		call putstr
542		pop %si				# Restore
543		jcxz hd.ret			# Return if done
544		jmp hd.line			# Next line
545hd.ret:		pop %di				# Restore
546		pop %si				# Restore
547		pop %dx				# Restore
548		pop %bx				# Restore
549		pop %ax				# Restore
550		ret
551
552#
553# Display a null-terminated string.
554#
555# Trashes: AX, SI
556#
557putstr:		push %bx			# Save
558putstr.load:	lodsb				# load %al from %ds:(%si)
559		test %al,%al			# stop at null
560		jnz putstr.putc			# if the char != null, output it
561		pop %bx				# Restore
562		ret				# return when null is hit
563putstr.putc:	call putc			# output char
564		jmp putstr.load			# next char
565
566#
567# Print out length-based string from [SI].
568#
569# Trashes: AX, SI
570#
571putstrl:	push %bx			# Save
572		push %cx			# Save
573		lodsb
574		movzbw %al,%cx			# Length
575		jcxz putstrl.ret		# Skip if empty
576putstrl.loop:	lodsb				# Read char
577		call putc			# Display
578		loop putstrl.loop		# Loop
579putstrl.ret:	pop %cx				# Restore
580		pop %bx				# Restore
581		ret
582
583#
584# Display a single char.
585#
586putc:		push %ax
587		push %dx
588		mov $0x1,%ah
589		xor %dx,%dx
590		int $0x14
591		pop %dx
592		pop %ax
593		mov $0x7,%bx			# attribute for output
594		mov $0xe,%ah			# BIOS: put_char
595		int $0x10			# call BIOS, print char in %al
596		ret				# Return to caller
597
598#
599# Output the "twiddle"
600#
601twiddle:	push %ax			# Save
602		push %bx			# Save
603		mov twiddle_index,%al		# Load index
604		mov twiddle_chars,%bx		# Address table
605		inc %al				# Next
606		and $3,%al			#  char
607		xlat				# Get char
608		call putc			# Output it
609		mov $8,%al			# Backspace
610		call putc			# Output it
611		pop %bx				# Restore
612		pop %ax				# Restore
613		ret
614
615#
616# Enable A20
617#
618seta20: 	cli				# Disable interrupts
619seta20.1:	in $0x64,%al			# Get status
620		test $0x2,%al			# Busy?
621		jnz seta20.1			# Yes
622		mov $0xd1,%al			# Command: Write
623		out %al,$0x64			#  output port
624seta20.2:	in $0x64,%al			# Get status
625		test $0x2,%al			# Busy?
626		jnz seta20.2			# Yes
627		mov $0xdf,%al			# Enable
628		out %al,$0x60			#  A20
629		sti				# Enable interrupts
630		ret				# To caller
631
632#
633# Convert EAX, AX, or AL to hex, saving the result to [EDI].
634#
635hex32:		pushl %eax			# Save
636		shrl $0x10,%eax 		# Do upper
637		call hex16			#  16
638		popl %eax			# Restore
639hex16:		call hex16.1			# Do upper 8
640hex16.1:	xchgb %ah,%al			# Save/restore
641hex8:		pushl %eax			# Save
642		shrb $0x4,%al			# Do upper
643		call hex8.1			#  4
644		popl %eax			# Restore
645hex8.1: 	andb $0xf,%al			# Get lower 4
646		cmpb $0xa,%al			# Convert
647		sbbb $0x69,%al			#  to hex
648		das				#  digit
649		orb $0x20,%al			# To lower case
650		stosb				# Save char
651		ret				# (Recursive)
652
653#
654# BTX client to start btxldr
655#
656		.code32
657btx_client:	mov $(MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE-4), %esi
658						# %ds:(%esi) -> end
659						#  of boot[12] args
660		mov $(MEM_ARG_SIZE/4),%ecx	# Number of words to push
661		std				# Go backwards
662push_arg:	lodsl				# Read argument
663		push %eax			# Push it onto the stack
664		loop push_arg			# Push all of the arguments
665		cld				# In case anyone depends on this
666		pushl MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE # Entry point of
667						#  the loader
668		push %eax			# Emulate a near call
669		mov $0x1,%eax			# 'exec' system call
670		int $INT_SYS			# BTX system call
671btx_client_end:
672		.code16
673
674		.p2align 4
675#
676# Global descriptor table.
677#
678gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
679		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
680		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
681		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE (32-bit)
682		.word 0xffff,0x0,0x9a00,0x8f	# SEL_SCODE16 (16-bit)
683gdt.1:
684#
685# Pseudo-descriptors.
686#
687gdtdesc:	.word gdt.1-gdt-1		# Limit
688		.long gdt			# Base
689#
690# EDD Packet
691#
692edd_packet:	.byte 0x10			# Length
693		.byte 0				# Reserved
694edd_len:	.byte 0x0			# Num to read
695		.byte 0				# Reserved
696edd_addr:	.word 0x0,0x0			# Seg:Off
697edd_lba:	.quad 0x0			# LBA
698
699drive:		.byte 0
700
701#
702# State for searching dir
703#
704rec_lba:	.long 0x0			# LBA (adjusted for EA)
705rec_size:	.long 0x0			# File size
706name_len:	.byte 0x0			# Length of current name
707
708twiddle_index:	.byte 0x0
709
710msg_welcome:	.asciz	"CD Loader 1.01\r\n\n"
711msg_bootinfo:	.asciz	"Building the boot loader arguments\r\n"
712msg_relocate:	.asciz	"Relocating the loader and the BTX\r\n"
713msg_jump:	.asciz	"Starting the BTX loader\r\n"
714msg_badread:	.ascii  "Read Error: 0x"
715hex_error:	.ascii	"00\r\n"
716msg_vd:		.asciz  "Read Volume Descriptor\r\n"
717msg_novd:	.asciz  "Could not find Primary Volume Descriptor\r\n"
718msg_lookup:	.asciz  "Looking up "
719msg_lookup2:	.asciz  "... "
720msg_lookupok:	.asciz  "Found\r\n"
721msg_lookupfail:	.asciz  "File not found\r\n"
722msg_load2big:	.asciz  "File too big\r\n"
723loader_path:	.asciz  "/BOOT/LOADER"
724twiddle_chars:	.ascii	"|/-\\"
725
726msg_entry:	.ascii	"Entry point: "
727msg_entry2:	.asciz	"00000000\r\n"
728msg_lookup_done:.asciz	"Lookup returned\r\n"
729msg_startff:	.asciz	"\r\nStarting find_file\r\n"
730msg_ffpath:	.asciz	"Path = \""
731msg_ffpath2:	.ascii	"\"  Length = "
732msg_fflen:	.asciz	"00\r\n"
733msg_lenmatch:	.asciz	"ff: Length matched\r\n"
734msg_ffcheck:	.asciz	"ff: Checking name: "
735msg_ffscan2:
736msg_ffcheck2:	.asciz	"\r\n"
737msg_ffscan:	.asciz	"ff: Scanning name: "
738
739dump_packet:	.ascii	"Len "
740dump_len:	.ascii	"00  Addr "
741dump_seg:	.ascii	"0000:"
742dump_offset:	.ascii  "0000  LBA "
743dump_lba:	.asciz  "00000000\r\n"
744
745dump_bx:	.ascii	"bx = "
746hex_bx:		.asciz	"0000\r\n"
747
748hex_line:	.ascii	"0000:00 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00 "
749		.asciz	"|................|\r\n"
750
751