xref: /illumos-gate/usr/src/boot/i386/cdboot/cdboot.S (revision 22028508)
1#
2# Copyright (c) 2001 John Baldwin <jhb@FreeBSD.org>
3# All rights reserved.
4#
5# Redistribution and use in source and binary forms, with or without
6# modification, are permitted provided that the following conditions
7# are met:
8# 1. Redistributions of source code must retain the above copyright
9#    notice, this list of conditions and the following disclaimer.
10# 2. Redistributions in binary form must reproduce the above copyright
11#    notice, this list of conditions and the following disclaimer in the
12#    documentation and/or other materials provided with the distribution.
13#
14# THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
15# ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
16# IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
17# ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
18# FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
19# DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
20# OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
21# HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
22# LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
23# OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
24# SUCH DAMAGE.
25#
26
27# $FreeBSD$
28
29#
30# This program is a freestanding boot program to load an a.out binary
31# from a CD-ROM booted with no emulation mode as described by the El
32# Torito standard.  Due to broken BIOSen that do not load the desired
33# number of sectors, we try to fit this in as small a space as possible.
34#
35# Basically, we first create a set of boot arguments to pass to the loaded
36# binary.  Then we attempt to load /boot/loader from the CD we were booted
37# from.
38#
39
40#include <bootargs.h>
41
42#
43# Memory locations.
44#
45		.set MEM_PAGE_SIZE,0x1000	# memory page size, 4k
46		.set MEM_ARG,0x900		# Arguments at start
47		.set MEM_ARG_BTX,0xa100		# Where we move them to so the
48						#  BTX client can see them
49		.set MEM_ARG_SIZE,0x18		# Size of the arguments
50		.set MEM_BTX_ADDRESS,0x9000	# where BTX lives
51		.set MEM_BTX_ENTRY,0x9010	# where BTX starts to execute
52		.set MEM_BTX_OFFSET,MEM_PAGE_SIZE # offset of BTX in the loader
53		.set MEM_BTX_CLIENT,0xa000	# where BTX clients live
54#
55# a.out header fields
56#
57		.set AOUT_TEXT,0x04		# text segment size
58		.set AOUT_DATA,0x08		# data segment size
59		.set AOUT_BSS,0x0c		# zero'd BSS size
60		.set AOUT_SYMBOLS,0x10		# symbol table
61		.set AOUT_ENTRY,0x14		# entry point
62		.set AOUT_HEADER,MEM_PAGE_SIZE	# size of the a.out header
63#
64# Segment selectors.
65#
66		.set SEL_SDATA,0x8		# Supervisor data
67		.set SEL_RDATA,0x10		# Real mode data
68		.set SEL_SCODE,0x18		# PM-32 code
69		.set SEL_SCODE16,0x20		# PM-16 code
70#
71# BTX constants
72#
73		.set INT_SYS,0x30		# BTX syscall interrupt
74#
75# Constants for reading from the CD.
76#
77		.set ERROR_TIMEOUT,0x80		# BIOS timeout on read
78		.set NUM_RETRIES,3		# Num times to retry
79		.set SECTOR_SIZE,0x800		# size of a sector
80		.set SECTOR_SHIFT,11		# number of place to shift
81		.set BUFFER_LEN,0x100		# number of sectors in buffer
82		.set MAX_READ,0x10000		# max we can read at a time
83		.set MAX_READ_SEC,MAX_READ >> SECTOR_SHIFT
84		.set MEM_READ_BUFFER,0x9000	# buffer to read from CD
85		.set MEM_VOLDESC,MEM_READ_BUFFER # volume descriptor
86		.set MEM_DIR,MEM_VOLDESC+SECTOR_SIZE # Lookup buffer
87		.set VOLDESC_LBA,0x10		# LBA of vol descriptor
88		.set VD_PRIMARY,1		# Primary VD
89		.set VD_END,255			# VD Terminator
90		.set VD_ROOTDIR,156		# Offset of Root Dir Record
91		.set DIR_LEN,0			# Offset of Dir Record length
92		.set DIR_EA_LEN,1		# Offset of EA length
93		.set DIR_EXTENT,2		# Offset of 64-bit LBA
94		.set DIR_SIZE,10		# Offset of 64-bit length
95		.set DIR_NAMELEN,32		# Offset of 8-bit name len
96		.set DIR_NAME,33		# Offset of dir name
97#
98# We expect to be loaded by the BIOS at 0x7c00 (standard boot loader entry
99# point)
100#
101		.code16
102		.globl start
103		.org 0x0, 0x0
104#
105# Program start.
106#
107start:		jmp real_start
108		.org 0x8, 0x8
109
110bi_pvd:		.long VOLDESC_LBA		# LBA of primary volume desc
111bi_file:	.long 0				# LBA of boot file.
112bi_length:	.long 0				# Length of boot file.
113bi_csum:	.long 0				# Checksum of boot file
114bi_reserved:	.space (10*4)			# Reserved
115
116real_start:	cld				# string ops inc
117		xor %ax,%ax			# zero %ax
118		mov %ax,%ss			# setup the
119		mov $start,%sp			#  stack
120		mov %ax,%ds			# setup the
121		mov %ax,%es			#  data segments
122		mov %dl,drive			# Save BIOS boot device
123		mov $msg_welcome,%si		# %ds:(%si) -> welcome message
124		call putstr			# display the welcome message
125#
126# Setup the arguments that the loader is expecting from boot[12]
127#
128		mov $msg_bootinfo,%si		# %ds:(%si) -> boot args message
129		call putstr			# display the message
130		mov $MEM_ARG,%bx		# %ds:(%bx) -> boot args
131		mov %bx,%di			# %es:(%di) -> boot args
132		xor %eax,%eax			# zero %eax
133		mov $(MEM_ARG_SIZE/4),%cx	# Size of arguments in 32-bit
134						#  dwords
135		rep				# Clear the arguments
136		stosl				#  to zero
137		mov drive,%dl			# Store BIOS boot device
138		mov %dl,0x4(%bx)		#  in kargs->bootdev
139		orb $KARGS_FLAGS_CD,0x8(%bx)	# kargs->bootflags |=
140						#  KARGS_FLAGS_CD
141#
142# Load Volume Descriptor
143#
144		mov $VOLDESC_LBA,%eax		# Set LBA of first VD
145load_vd:	push %eax			# Save %eax
146		mov $1,%dh			# One sector
147		mov $MEM_VOLDESC,%ebx		# Destination
148		call read			# Read it in
149		cmpb $VD_PRIMARY,(%bx)		# Primary VD?
150		je have_vd			# Yes
151		pop %eax			# Prepare to
152		inc %eax			#  try next
153		cmpb $VD_END,(%bx)		# Last VD?
154		jne load_vd			# No, read next
155		mov $msg_novd,%si		# No VD
156		jmp error			# Halt
157have_vd:					# Have Primary VD
158#
159# Try to look up the loader binary using the paths in the loader_paths
160# array.
161#
162		mov $loader_paths,%si		# Point to start of array
163lookup_path:	push %si			# Save file name pointer
164		call lookup			# Try to find file
165		pop %di				# Restore file name pointer
166		jnc lookup_found		# Found this file
167		xor %al,%al			# Look for next
168		mov $0xffff,%cx			#  path name by
169		repnz				#  scanning for
170		scasb				#  nul char
171		mov %di,%si			# Point %si at next path
172		mov (%si),%al			# Get first char of next path
173		or %al,%al			# Is it double nul?
174		jnz lookup_path			# No, try it.
175		mov $msg_failed,%si		# Failed message
176		jmp error			# Halt
177lookup_found:					# Found a loader file
178#
179# Load the binary into the buffer.  Due to real mode addressing limitations
180# we have to read it in 64k chunks.
181#
182		mov DIR_SIZE(%bx),%eax		# Read file length
183		add $SECTOR_SIZE-1,%eax		# Convert length to sectors
184		shr $SECTOR_SHIFT,%eax
185		cmp $BUFFER_LEN,%eax
186		jbe load_sizeok
187		mov $msg_load2big,%si		# Error message
188		call error
189load_sizeok:	movzbw %al,%cx			# Num sectors to read
190		mov DIR_EXTENT(%bx),%eax	# Load extent
191		xor %edx,%edx
192		mov DIR_EA_LEN(%bx),%dl
193		add %edx,%eax			# Skip extended
194		mov $MEM_READ_BUFFER,%ebx	# Read into the buffer
195load_loop:	mov %cl,%dh
196		cmp $MAX_READ_SEC,%cl		# Truncate to max read size
197		jbe load_notrunc
198		mov $MAX_READ_SEC,%dh
199load_notrunc:	sub %dh,%cl			# Update count
200		push %eax			# Save
201		call read			# Read it in
202		pop %eax			# Restore
203		add $MAX_READ_SEC,%eax		# Update LBA
204		add $MAX_READ,%ebx		# Update dest addr
205		jcxz load_done			# Done?
206		jmp load_loop			# Keep going
207load_done:
208#
209# Turn on the A20 address line
210#
211		call seta20			# Turn A20 on
212#
213# Relocate the loader and BTX using a very lazy protected mode
214#
215		mov $msg_relocate,%si		# Display the
216		call putstr			#  relocation message
217		mov MEM_READ_BUFFER+AOUT_ENTRY,%edi # %edi is the destination
218		mov $(MEM_READ_BUFFER+AOUT_HEADER),%esi	# %esi is
219						#  the start of the text
220						#  segment
221		mov MEM_READ_BUFFER+AOUT_TEXT,%ecx # %ecx = length of the text
222						#  segment
223		push %edi			# Save entry point for later
224		lgdt gdtdesc			# setup our own gdt
225		cli				# turn off interrupts
226		mov %cr0,%eax			# Turn on
227		or $0x1,%al			#  protected
228		mov %eax,%cr0			#  mode
229		ljmp $SEL_SCODE,$pm_start	# long jump to clear the
230						#  instruction pre-fetch queue
231		.code32
232pm_start:	mov $SEL_SDATA,%ax		# Initialize
233		mov %ax,%ds			#  %ds and
234		mov %ax,%es			#  %es to a flat selector
235		rep				# Relocate the
236		movsb				#  text segment
237		add $(MEM_PAGE_SIZE - 1),%edi	# pad %edi out to a new page
238		and $~(MEM_PAGE_SIZE - 1),%edi #  for the data segment
239		mov MEM_READ_BUFFER+AOUT_DATA,%ecx # size of the data segment
240		rep				# Relocate the
241		movsb				#  data segment
242		mov MEM_READ_BUFFER+AOUT_BSS,%ecx # size of the bss
243		xor %eax,%eax			# zero %eax
244		add $3,%cl			# round %ecx up to
245		shr $2,%ecx			#  a multiple of 4
246		rep				# zero the
247		stosl				#  bss
248		mov MEM_READ_BUFFER+AOUT_ENTRY,%esi # %esi -> relocated loader
249		add $MEM_BTX_OFFSET,%esi	# %esi -> BTX in the loader
250		mov $MEM_BTX_ADDRESS,%edi	# %edi -> where BTX needs to go
251		movzwl 0xa(%esi),%ecx		# %ecx -> length of BTX
252		rep				# Relocate
253		movsb				#  BTX
254		ljmp $SEL_SCODE16,$pm_16	# Jump to 16-bit PM
255		.code16
256pm_16:		mov $SEL_RDATA,%ax		# Initialize
257		mov %ax,%ds			#  %ds and
258		mov %ax,%es			#  %es to a real mode selector
259		mov %cr0,%eax			# Turn off
260		and $~0x1,%al			#  protected
261		mov %eax,%cr0			#  mode
262		ljmp $0,$pm_end			# Long jump to clear the
263						#  instruction pre-fetch queue
264pm_end:		sti				# Turn interrupts back on now
265#
266# Copy the BTX client to MEM_BTX_CLIENT
267#
268		xor %ax,%ax			# zero %ax and set
269		mov %ax,%ds			#  %ds and %es
270		mov %ax,%es			#  to segment 0
271		mov $MEM_BTX_CLIENT,%di		# Prepare to relocate
272		mov $btx_client,%si		#  the simple btx client
273		mov $(btx_client_end-btx_client),%cx # length of btx client
274		rep				# Relocate the
275		movsb				#  simple BTX client
276#
277# Copy the boot[12] args to where the BTX client can see them
278#
279		mov $MEM_ARG,%si		# where the args are at now
280		mov $MEM_ARG_BTX,%di		# where the args are moving to
281		mov $(MEM_ARG_SIZE/4),%cx	# size of the arguments in longs
282		rep				# Relocate
283		movsl				#  the words
284#
285# Save the entry point so the client can get to it later on
286#
287		pop %eax			# Restore saved entry point
288		stosl				#  and add it to the end of
289						#  the arguments
290#
291# Now we just start up BTX and let it do the rest
292#
293		mov $msg_jump,%si		# Display the
294		call putstr			#  jump message
295		ljmp $0,$MEM_BTX_ENTRY		# Jump to the BTX entry point
296
297#
298# Lookup the file in the path at [SI] from the root directory.
299#
300# Trashes: All but BX
301# Returns: CF = 0 (success), BX = pointer to record
302#          CF = 1 (not found)
303#
304lookup:		mov $VD_ROOTDIR+MEM_VOLDESC,%bx	# Root directory record
305		push %si
306		mov $msg_lookup,%si		# Display lookup message
307		call putstr
308		pop %si
309		push %si
310		call putstr
311		mov $msg_lookup2,%si
312		call putstr
313		pop %si
314lookup_dir:	lodsb				# Get first char of path
315		cmp $0,%al			# Are we done?
316		je lookup_done			# Yes
317		cmp $'/',%al			# Skip path separator.
318		je lookup_dir
319		dec %si				# Undo lodsb side effect
320		call find_file			# Lookup first path item
321		jnc lookup_dir			# Try next component
322		mov $msg_lookupfail,%si		# Not found message
323		call putstr
324		stc				# Set carry
325		ret
326		jmp error
327lookup_done:	mov $msg_lookupok,%si		# Success message
328		call putstr
329		clc				# Clear carry
330		ret
331
332#
333# Lookup file at [SI] in directory whose record is at [BX].
334#
335# Trashes: All but returns
336# Returns: CF = 0 (success), BX = pointer to record, SI = next path item
337#          CF = 1 (not found), SI = preserved
338#
339find_file:	mov DIR_EXTENT(%bx),%eax	# Load extent
340		xor %edx,%edx
341		mov DIR_EA_LEN(%bx),%dl
342		add %edx,%eax			# Skip extended attributes
343		mov %eax,rec_lba		# Save LBA
344		mov DIR_SIZE(%bx),%eax		# Save size
345		mov %eax,rec_size
346		xor %cl,%cl			# Zero length
347		push %si			# Save
348ff.namelen:	inc %cl				# Update length
349		lodsb				# Read char
350		cmp $0,%al			# Nul?
351		je ff.namedone			# Yes
352		cmp $'/',%al			# Path separator?
353		jnz ff.namelen			# No, keep going
354ff.namedone:	dec %cl				# Adjust length and save
355		mov %cl,name_len
356		pop %si				# Restore
357ff.load:	mov rec_lba,%eax		# Load LBA
358		mov $MEM_DIR,%ebx		# Address buffer
359		mov $1,%dh			# One sector
360		call read			# Read directory block
361		incl rec_lba			# Update LBA to next block
362ff.scan:	mov %ebx,%edx			# Check for EOF
363		sub $MEM_DIR,%edx
364		cmp %edx,rec_size
365		ja ff.scan.1
366		stc				# EOF reached
367		ret
368ff.scan.1:	cmpb $0,DIR_LEN(%bx)		# Last record in block?
369		je ff.nextblock
370		push %si			# Save
371		movzbw DIR_NAMELEN(%bx),%si	# Find end of string
372ff.checkver:	cmpb $'0',DIR_NAME-1(%bx,%si)	# Less than '0'?
373		jb ff.checkver.1
374		cmpb $'9',DIR_NAME-1(%bx,%si)	# Greater than '9'?
375		ja ff.checkver.1
376		dec %si				# Next char
377		jnz ff.checkver
378		jmp ff.checklen			# All numbers in name, so
379						#  no version
380ff.checkver.1:	movzbw DIR_NAMELEN(%bx),%cx
381		cmp %cx,%si			# Did we find any digits?
382		je ff.checkdot			# No
383		cmpb $';',DIR_NAME-1(%bx,%si)	# Check for semicolon
384		jne ff.checkver.2
385		dec %si				# Skip semicolon
386		mov %si,%cx
387		mov %cl,DIR_NAMELEN(%bx)	# Adjust length
388		jmp ff.checkdot
389ff.checkver.2:	mov %cx,%si			# Restore %si to end of string
390ff.checkdot:	cmpb $'.',DIR_NAME-1(%bx,%si)	# Trailing dot?
391		jne ff.checklen			# No
392		decb DIR_NAMELEN(%bx)		# Adjust length
393ff.checklen:	pop %si				# Restore
394		movzbw name_len,%cx		# Load length of name
395		cmp %cl,DIR_NAMELEN(%bx)	# Does length match?
396		je ff.checkname			# Yes, check name
397ff.nextrec:	add DIR_LEN(%bx),%bl		# Next record
398		adc $0,%bh
399		jmp ff.scan
400ff.nextblock:	subl $SECTOR_SIZE,rec_size	# Adjust size
401		jnc ff.load			# If subtract ok, keep going
402		ret				# End of file, so not found
403ff.checkname:	lea DIR_NAME(%bx),%di		# Address name in record
404		push %si			# Save
405		repe cmpsb			# Compare name
406		je ff.match			# We have a winner!
407		pop %si				# Restore
408		jmp ff.nextrec			# Keep looking.
409ff.match:	add $2,%sp			# Discard saved %si
410		clc				# Clear carry
411		ret
412
413#
414# Load DH sectors starting at LBA EAX into [EBX].
415#
416# Trashes: EAX
417#
418read:		push %si			# Save
419		push %cx			# Save since some BIOSs trash
420		mov %eax,edd_lba		# LBA to read from
421		mov %ebx,%eax			# Convert address
422		shr $4,%eax			#  to segment
423		mov %ax,edd_addr+0x2		#  and store
424read.retry:	call twiddle			# Entertain the user
425		push %dx			# Save
426		mov $edd_packet,%si		# Address Packet
427		mov %dh,edd_len			# Set length
428		mov drive,%dl			# BIOS Device
429		mov $0x42,%ah			# BIOS: Extended Read
430		int $0x13			# Call BIOS
431		pop %dx				# Restore
432		jc read.fail			# Worked?
433		pop %cx				# Restore
434		pop %si
435		ret				# Return
436read.fail:	cmp $ERROR_TIMEOUT,%ah		# Timeout?
437		je read.retry			# Yes, Retry.
438read.error:	mov %ah,%al			# Save error
439		mov $hex_error,%di		# Format it
440		call hex8			#  as hex
441		mov $msg_badread,%si		# Display Read error message
442
443#
444# Display error message at [SI] and halt.
445#
446error:		call putstr			# Display message
447halt:		hlt
448		jmp halt			# Spin
449
450#
451# Display a null-terminated string.
452#
453# Trashes: AX, SI
454#
455putstr:		push %bx			# Save
456putstr.load:	lodsb				# load %al from %ds:(%si)
457		test %al,%al			# stop at null
458		jnz putstr.putc			# if the char != null, output it
459		pop %bx				# Restore
460		ret				# return when null is hit
461putstr.putc:	call putc			# output char
462		jmp putstr.load			# next char
463
464#
465# Display a single char.
466#
467putc:		mov $0x7,%bx			# attribute for output
468		mov $0xe,%ah			# BIOS: put_char
469		int $0x10			# call BIOS, print char in %al
470		ret				# Return to caller
471
472#
473# Output the "twiddle"
474#
475twiddle:	push %ax			# Save
476		push %bx			# Save
477		mov twiddle_index,%al		# Load index
478		mov $twiddle_chars,%bx		# Address table
479		inc %al				# Next
480		and $3,%al			#  char
481		mov %al,twiddle_index		# Save index for next call
482		xlat				# Get char
483		call putc			# Output it
484		mov $8,%al			# Backspace
485		call putc			# Output it
486		pop %bx				# Restore
487		pop %ax				# Restore
488		ret
489
490#
491# Enable A20. Put an upper limit on the amount of time we wait for the
492# keyboard controller to get ready (65K x ISA access time). If
493# we wait more than that amount, the hardware is probably
494# legacy-free and simply doesn't have a keyboard controller.
495# Thus, the A20 line is already enabled.
496#
497seta20:		cli				# Disable interrupts
498		xor %cx,%cx			# Clear
499seta20.1:	inc %cx				# Increment, overflow?
500		jz seta20.3			# Yes
501		in $0x64,%al			# Get status
502		test $0x2,%al			# Busy?
503		jnz seta20.1			# Yes
504		mov $0xd1,%al			# Command: Write
505		out %al,$0x64			#  output port
506seta20.2:	in $0x64,%al			# Get status
507		test $0x2,%al			# Busy?
508		jnz seta20.2			# Yes
509		mov $0xdf,%al			# Enable
510		out %al,$0x60			#  A20
511seta20.3:	sti				# Enable interrupts
512		ret				# To caller
513
514#
515# Convert AL to hex, saving the result to [EDI].
516#
517hex8:		pushl %eax			# Save
518		shrb $0x4,%al			# Do upper
519		call hex8.1			#  4
520		popl %eax			# Restore
521hex8.1:		andb $0xf,%al			# Get lower 4
522		cmpb $0xa,%al			# Convert
523		sbbb $0x69,%al			#  to hex
524		das				#  digit
525		orb $0x20,%al			# To lower case
526		stosb				# Save char
527		ret				# (Recursive)
528
529#
530# BTX client to start btxldr
531#
532		.code32
533btx_client:	mov $(MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE-4), %esi
534						# %ds:(%esi) -> end
535						#  of boot[12] args
536		mov $(MEM_ARG_SIZE/4),%ecx	# Number of words to push
537		std				# Go backwards
538push_arg:	lodsl				# Read argument
539		push %eax			# Push it onto the stack
540		loop push_arg			# Push all of the arguments
541		cld				# In case anyone depends on this
542		pushl MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE # Entry point of
543						#  the loader
544		push %eax			# Emulate a near call
545		mov $0x1,%eax			# 'exec' system call
546		int $INT_SYS			# BTX system call
547btx_client_end:
548		.code16
549
550		.p2align 4
551#
552# Global descriptor table.
553#
554gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
555		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
556		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
557		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE (32-bit)
558		.word 0xffff,0x0,0x9a00,0x8f	# SEL_SCODE16 (16-bit)
559gdt.1:
560#
561# Pseudo-descriptors.
562#
563gdtdesc:	.word gdt.1-gdt-1		# Limit
564		.long gdt			# Base
565#
566# EDD Packet
567#
568edd_packet:	.byte 0x10			# Length
569		.byte 0				# Reserved
570edd_len:	.byte 0x0			# Num to read
571		.byte 0				# Reserved
572edd_addr:	.word 0x0,0x0			# Seg:Off
573edd_lba:	.quad 0x0			# LBA
574
575drive:		.byte 0
576
577#
578# State for searching dir
579#
580rec_lba:	.long 0x0			# LBA (adjusted for EA)
581rec_size:	.long 0x0			# File size
582name_len:	.byte 0x0			# Length of current name
583
584twiddle_index:	.byte 0x0
585
586msg_welcome:	.asciz	"CD Loader 1.2\r\n\n"
587msg_bootinfo:	.asciz	"Building the boot loader arguments\r\n"
588msg_relocate:	.asciz	"Relocating the loader and the BTX\r\n"
589msg_jump:	.asciz	"Starting the BTX loader\r\n"
590msg_badread:	.ascii  "Read Error: 0x"
591hex_error:	.asciz	"00\r\n"
592msg_novd:	.asciz  "Could not find Primary Volume Descriptor\r\n"
593msg_lookup:	.asciz  "Looking up "
594msg_lookup2:	.asciz  "... "
595msg_lookupok:	.asciz  "Found\r\n"
596msg_lookupfail:	.asciz  "File not found\r\n"
597msg_load2big:	.asciz  "File too big\r\n"
598msg_failed:	.asciz	"Boot failed\r\n"
599twiddle_chars:	.ascii	"|/-\\"
600loader_paths:	.asciz  "/BOOT/LOADER"
601		.asciz	"/boot/loader"
602		.byte 0
603