cdboot.S revision 329011
1169691Skan#
2169691Skan# Copyright (c) 2001 John Baldwin <jhb@FreeBSD.org>
3169691Skan# All rights reserved.
4169691Skan#
5169691Skan# Redistribution and use in source and binary forms, with or without
6169691Skan# modification, are permitted provided that the following conditions
7169691Skan# are met:
8169691Skan# 1. Redistributions of source code must retain the above copyright
9169691Skan#    notice, this list of conditions and the following disclaimer.
10169691Skan# 2. Redistributions in binary form must reproduce the above copyright
11169691Skan#    notice, this list of conditions and the following disclaimer in the
12169691Skan#    documentation and/or other materials provided with the distribution.
13169691Skan#
14169691Skan# THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
15169691Skan# ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
16169691Skan# IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
17169691Skan# ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
18169691Skan# FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
19169691Skan# DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
20169691Skan# OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
21169691Skan# HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
22169691Skan# LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
23169691Skan# OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
24169691Skan# SUCH DAMAGE.
25169691Skan#
26169691Skan
27169691Skan# $FreeBSD: stable/11/sys/boot/i386/cdboot/cdboot.S 329011 2018-02-08 02:50:47Z kevans $
28169691Skan
29169691Skan#
30169691Skan# This program is a freestanding boot program to load an a.out binary
31169691Skan# from a CD-ROM booted with no emulation mode as described by the El
32169691Skan# Torito standard.  Due to broken BIOSen that do not load the desired
33169691Skan# number of sectors, we try to fit this in as small a space as possible.
34169691Skan#
35169691Skan# Basically, we first create a set of boot arguments to pass to the loaded
36169691Skan# binary.  Then we attempt to load /boot/loader from the CD we were booted
37169691Skan# off of.
38169691Skan#
39169691Skan
40169691Skan#include <bootargs.h>
41169691Skan
42169691Skan#
43169691Skan# Memory locations.
44169691Skan#
45169691Skan		.set MEM_PAGE_SIZE,0x1000	# memory page size, 4k
46169691Skan		.set MEM_ARG,0x900		# Arguments at start
47169691Skan		.set MEM_ARG_BTX,0xa100		# Where we move them to so the
48169691Skan						#  BTX client can see them
49169691Skan		.set MEM_ARG_SIZE,0x18		# Size of the arguments
50169691Skan		.set MEM_BTX_ADDRESS,0x9000	# where BTX lives
51169691Skan		.set MEM_BTX_ENTRY,0x9010	# where BTX starts to execute
52169691Skan		.set MEM_BTX_OFFSET,MEM_PAGE_SIZE # offset of BTX in the loader
53169691Skan		.set MEM_BTX_CLIENT,0xa000	# where BTX clients live
54169691Skan#
55169691Skan# a.out header fields
56169691Skan#
57169691Skan		.set AOUT_TEXT,0x04		# text segment size
58169691Skan		.set AOUT_DATA,0x08		# data segment size
59169691Skan		.set AOUT_BSS,0x0c		# zero'd BSS size
60169691Skan		.set AOUT_SYMBOLS,0x10		# symbol table
61169691Skan		.set AOUT_ENTRY,0x14		# entry point
62169691Skan		.set AOUT_HEADER,MEM_PAGE_SIZE	# size of the a.out header
63169691Skan#
64169691Skan# Segment selectors.
65169691Skan#
66169691Skan		.set SEL_SDATA,0x8		# Supervisor data
67169691Skan		.set SEL_RDATA,0x10		# Real mode data
68169691Skan		.set SEL_SCODE,0x18		# PM-32 code
69169691Skan		.set SEL_SCODE16,0x20		# PM-16 code
70169691Skan#
71169691Skan# BTX constants
72169691Skan#
73169691Skan		.set INT_SYS,0x30		# BTX syscall interrupt
74169691Skan#
75169691Skan# Constants for reading from the CD.
76169691Skan#
77169691Skan		.set ERROR_TIMEOUT,0x80		# BIOS timeout on read
78169691Skan		.set NUM_RETRIES,3		# Num times to retry
79169691Skan		.set SECTOR_SIZE,0x800		# size of a sector
80169691Skan		.set SECTOR_SHIFT,11		# number of place to shift
81169691Skan		.set BUFFER_LEN,0x100		# number of sectors in buffer
82169691Skan		.set MAX_READ,0x10000		# max we can read at a time
83169691Skan		.set MAX_READ_SEC,MAX_READ >> SECTOR_SHIFT
84169691Skan		.set MEM_READ_BUFFER,0x9000	# buffer to read from CD
85169691Skan		.set MEM_VOLDESC,MEM_READ_BUFFER # volume descriptor
86169691Skan		.set MEM_DIR,MEM_VOLDESC+SECTOR_SIZE # Lookup buffer
87169691Skan		.set VOLDESC_LBA,0x10		# LBA of vol descriptor
88169691Skan		.set VD_PRIMARY,1		# Primary VD
89169691Skan		.set VD_END,255			# VD Terminator
90169691Skan		.set VD_ROOTDIR,156		# Offset of Root Dir Record
91169691Skan		.set DIR_LEN,0			# Offset of Dir Record length
92169691Skan		.set DIR_EA_LEN,1		# Offset of EA length
93169691Skan		.set DIR_EXTENT,2		# Offset of 64-bit LBA
94169691Skan		.set DIR_SIZE,10		# Offset of 64-bit length
95169691Skan		.set DIR_NAMELEN,32		# Offset of 8-bit name len
96169691Skan		.set DIR_NAME,33		# Offset of dir name
97169691Skan#
98169691Skan# We expect to be loaded by the BIOS at 0x7c00 (standard boot loader entry
99169691Skan# point)
100169691Skan#
101169691Skan		.code16
102169691Skan		.globl start
103169691Skan		.org 0x0, 0x0
104169691Skan#
105169691Skan# Program start.
106169691Skan#
107169691Skanstart:		cld				# string ops inc
108169691Skan		xor %ax,%ax			# zero %ax
109169691Skan		mov %ax,%ss			# setup the
110169691Skan		mov $start,%sp			#  stack
111169691Skan		mov %ax,%ds			# setup the
112169691Skan		mov %ax,%es			#  data segments
113169691Skan		mov %dl,drive			# Save BIOS boot device
114169691Skan		mov $msg_welcome,%si		# %ds:(%si) -> welcome message
115169691Skan		call putstr			# display the welcome message
116169691Skan#
117169691Skan# Setup the arguments that the loader is expecting from boot[12]
118169691Skan#
119169691Skan		mov $msg_bootinfo,%si		# %ds:(%si) -> boot args message
120169691Skan		call putstr			# display the message
121169691Skan		mov $MEM_ARG,%bx		# %ds:(%bx) -> boot args
122169691Skan		mov %bx,%di			# %es:(%di) -> boot args
123169691Skan		xor %eax,%eax			# zero %eax
124169691Skan		mov $(MEM_ARG_SIZE/4),%cx	# Size of arguments in 32-bit
125169691Skan						#  dwords
126169691Skan		rep				# Clear the arguments
127169691Skan		stosl				#  to zero
128169691Skan		mov drive,%dl			# Store BIOS boot device
129169691Skan		mov %dl,0x4(%bx)		#  in kargs->bootdev
130169691Skan		orb $KARGS_FLAGS_CD,0x8(%bx)	# kargs->bootflags |=
131169691Skan						#  KARGS_FLAGS_CD
132169691Skan#
133169691Skan# Load Volume Descriptor
134169691Skan#
135169691Skan		mov $VOLDESC_LBA,%eax		# Set LBA of first VD
136169691Skanload_vd:	push %eax			# Save %eax
137169691Skan		mov $1,%dh			# One sector
138169691Skan		mov $MEM_VOLDESC,%ebx		# Destination
139169691Skan		call read			# Read it in
140169691Skan		cmpb $VD_PRIMARY,(%bx)		# Primary VD?
141169691Skan		je have_vd			# Yes
142169691Skan		pop %eax			# Prepare to
143169691Skan		inc %eax			#  try next
144169691Skan		cmpb $VD_END,(%bx)		# Last VD?
145169691Skan		jne load_vd			# No, read next
146169691Skan		mov $msg_novd,%si		# No VD
147169691Skan		jmp error			# Halt
148have_vd:					# Have Primary VD
149#
150# Try to look up the loader binary using the paths in the loader_paths
151# array.
152#
153		mov $loader_paths,%si		# Point to start of array
154lookup_path:	push %si			# Save file name pointer
155		call lookup			# Try to find file
156		pop %di				# Restore file name pointer
157		jnc lookup_found		# Found this file
158		xor %al,%al			# Look for next
159		mov $0xffff,%cx			#  path name by
160		repnz				#  scanning for
161		scasb				#  nul char
162		mov %di,%si			# Point %si at next path
163		mov (%si),%al			# Get first char of next path
164		or %al,%al			# Is it double nul?
165		jnz lookup_path			# No, try it.
166		mov $msg_failed,%si		# Failed message
167		jmp error			# Halt
168lookup_found:					# Found a loader file
169#
170# Load the binary into the buffer.  Due to real mode addressing limitations
171# we have to read it in 64k chunks.
172#
173		mov DIR_SIZE(%bx),%eax		# Read file length
174		add $SECTOR_SIZE-1,%eax		# Convert length to sectors
175		shr $SECTOR_SHIFT,%eax
176		cmp $BUFFER_LEN,%eax
177		jbe load_sizeok
178		mov $msg_load2big,%si		# Error message
179		call error
180load_sizeok:	movzbw %al,%cx			# Num sectors to read
181		mov DIR_EXTENT(%bx),%eax	# Load extent
182		xor %edx,%edx
183		mov DIR_EA_LEN(%bx),%dl
184		add %edx,%eax			# Skip extended
185		mov $MEM_READ_BUFFER,%ebx	# Read into the buffer
186load_loop:	mov %cl,%dh
187		cmp $MAX_READ_SEC,%cl		# Truncate to max read size
188		jbe load_notrunc
189		mov $MAX_READ_SEC,%dh
190load_notrunc:	sub %dh,%cl			# Update count
191		push %eax			# Save
192		call read			# Read it in
193		pop %eax			# Restore
194		add $MAX_READ_SEC,%eax		# Update LBA
195		add $MAX_READ,%ebx		# Update dest addr
196		jcxz load_done			# Done?
197		jmp load_loop			# Keep going
198load_done:
199#
200# Turn on the A20 address line
201#
202		call seta20			# Turn A20 on
203#
204# Relocate the loader and BTX using a very lazy protected mode
205#
206		mov $msg_relocate,%si		# Display the
207		call putstr			#  relocation message
208		mov MEM_READ_BUFFER+AOUT_ENTRY,%edi # %edi is the destination
209		mov $(MEM_READ_BUFFER+AOUT_HEADER),%esi	# %esi is
210						#  the start of the text
211						#  segment
212		mov MEM_READ_BUFFER+AOUT_TEXT,%ecx # %ecx = length of the text
213						#  segment
214		push %edi			# Save entry point for later
215		lgdt gdtdesc			# setup our own gdt
216		cli				# turn off interrupts
217		mov %cr0,%eax			# Turn on
218		or $0x1,%al			#  protected
219		mov %eax,%cr0			#  mode
220		ljmp $SEL_SCODE,$pm_start	# long jump to clear the
221						#  instruction pre-fetch queue
222		.code32
223pm_start:	mov $SEL_SDATA,%ax		# Initialize
224		mov %ax,%ds			#  %ds and
225		mov %ax,%es			#  %es to a flat selector
226		rep				# Relocate the
227		movsb				#  text segment
228		add $(MEM_PAGE_SIZE - 1),%edi	# pad %edi out to a new page
229		and $~(MEM_PAGE_SIZE - 1),%edi #  for the data segment
230		mov MEM_READ_BUFFER+AOUT_DATA,%ecx # size of the data segment
231		rep				# Relocate the
232		movsb				#  data segment
233		mov MEM_READ_BUFFER+AOUT_BSS,%ecx # size of the bss
234		xor %eax,%eax			# zero %eax
235		add $3,%cl			# round %ecx up to
236		shr $2,%ecx			#  a multiple of 4
237		rep				# zero the
238		stosl				#  bss
239		mov MEM_READ_BUFFER+AOUT_ENTRY,%esi # %esi -> relocated loader
240		add $MEM_BTX_OFFSET,%esi	# %esi -> BTX in the loader
241		mov $MEM_BTX_ADDRESS,%edi	# %edi -> where BTX needs to go
242		movzwl 0xa(%esi),%ecx		# %ecx -> length of BTX
243		rep				# Relocate
244		movsb				#  BTX
245		ljmp $SEL_SCODE16,$pm_16	# Jump to 16-bit PM
246		.code16
247pm_16:		mov $SEL_RDATA,%ax		# Initialize
248		mov %ax,%ds			#  %ds and
249		mov %ax,%es			#  %es to a real mode selector
250		mov %cr0,%eax			# Turn off
251		and $~0x1,%al			#  protected
252		mov %eax,%cr0			#  mode
253		ljmp $0,$pm_end			# Long jump to clear the
254						#  instruction pre-fetch queue
255pm_end:		sti				# Turn interrupts back on now
256#
257# Copy the BTX client to MEM_BTX_CLIENT
258#
259		xor %ax,%ax			# zero %ax and set
260		mov %ax,%ds			#  %ds and %es
261		mov %ax,%es			#  to segment 0
262		mov $MEM_BTX_CLIENT,%di		# Prepare to relocate
263		mov $btx_client,%si		#  the simple btx client
264		mov $(btx_client_end-btx_client),%cx # length of btx client
265		rep				# Relocate the
266		movsb				#  simple BTX client
267#
268# Copy the boot[12] args to where the BTX client can see them
269#
270		mov $MEM_ARG,%si		# where the args are at now
271		mov $MEM_ARG_BTX,%di		# where the args are moving to
272		mov $(MEM_ARG_SIZE/4),%cx	# size of the arguments in longs
273		rep				# Relocate
274		movsl				#  the words
275#
276# Save the entry point so the client can get to it later on
277#
278		pop %eax			# Restore saved entry point
279		stosl				#  and add it to the end of
280						#  the arguments
281#
282# Now we just start up BTX and let it do the rest
283#
284		mov $msg_jump,%si		# Display the
285		call putstr			#  jump message
286		ljmp $0,$MEM_BTX_ENTRY		# Jump to the BTX entry point
287
288#
289# Lookup the file in the path at [SI] from the root directory.
290#
291# Trashes: All but BX
292# Returns: CF = 0 (success), BX = pointer to record
293#          CF = 1 (not found)
294#
295lookup:		mov $VD_ROOTDIR+MEM_VOLDESC,%bx	# Root directory record
296		push %si
297		mov $msg_lookup,%si		# Display lookup message
298		call putstr
299		pop %si
300		push %si
301		call putstr
302		mov $msg_lookup2,%si
303		call putstr
304		pop %si
305lookup_dir:	lodsb				# Get first char of path
306		cmp $0,%al			# Are we done?
307		je lookup_done			# Yes
308		cmp $'/',%al			# Skip path separator.
309		je lookup_dir
310		dec %si				# Undo lodsb side effect
311		call find_file			# Lookup first path item
312		jnc lookup_dir			# Try next component
313		mov $msg_lookupfail,%si		# Not found message
314		call putstr
315		stc				# Set carry
316		ret
317		jmp error
318lookup_done:	mov $msg_lookupok,%si		# Success message
319		call putstr
320		clc				# Clear carry
321		ret
322
323#
324# Lookup file at [SI] in directory whose record is at [BX].
325#
326# Trashes: All but returns
327# Returns: CF = 0 (success), BX = pointer to record, SI = next path item
328#          CF = 1 (not found), SI = preserved
329#
330find_file:	mov DIR_EXTENT(%bx),%eax	# Load extent
331		xor %edx,%edx
332		mov DIR_EA_LEN(%bx),%dl
333		add %edx,%eax			# Skip extended attributes
334		mov %eax,rec_lba		# Save LBA
335		mov DIR_SIZE(%bx),%eax		# Save size
336		mov %eax,rec_size
337		xor %cl,%cl			# Zero length
338		push %si			# Save
339ff.namelen:	inc %cl				# Update length
340		lodsb				# Read char
341		cmp $0,%al			# Nul?
342		je ff.namedone			# Yes
343		cmp $'/',%al			# Path separator?
344		jnz ff.namelen			# No, keep going
345ff.namedone:	dec %cl				# Adjust length and save
346		mov %cl,name_len
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		push %si			# Save
362		movzbw DIR_NAMELEN(%bx),%si	# Find end of string
363ff.checkver:	cmpb $'0',DIR_NAME-1(%bx,%si)	# Less than '0'?
364		jb ff.checkver.1
365		cmpb $'9',DIR_NAME-1(%bx,%si)	# Greater than '9'?
366		ja ff.checkver.1
367		dec %si				# Next char
368		jnz ff.checkver
369		jmp ff.checklen			# All numbers in name, so
370						#  no version
371ff.checkver.1:	movzbw DIR_NAMELEN(%bx),%cx
372		cmp %cx,%si			# Did we find any digits?
373		je ff.checkdot			# No
374		cmpb $';',DIR_NAME-1(%bx,%si)	# Check for semicolon
375		jne ff.checkver.2
376		dec %si				# Skip semicolon
377		mov %si,%cx
378		mov %cl,DIR_NAMELEN(%bx)	# Adjust length
379		jmp ff.checkdot
380ff.checkver.2:	mov %cx,%si			# Restore %si to end of string
381ff.checkdot:	cmpb $'.',DIR_NAME-1(%bx,%si)	# Trailing dot?
382		jne ff.checklen			# No
383		decb DIR_NAMELEN(%bx)		# Adjust length
384ff.checklen:	pop %si				# Restore
385		movzbw name_len,%cx		# Load length of name
386		cmp %cl,DIR_NAMELEN(%bx)	# Does length match?
387		je ff.checkname			# Yes, check name
388ff.nextrec:	add DIR_LEN(%bx),%bl		# Next record
389		adc $0,%bh
390		jmp ff.scan
391ff.nextblock:	subl $SECTOR_SIZE,rec_size	# Adjust size
392		jnc ff.load			# If subtract ok, keep going
393		ret				# End of file, so not found
394ff.checkname:	lea DIR_NAME(%bx),%di		# Address name in record
395		push %si			# Save
396		repe cmpsb			# Compare name
397		je ff.match			# We have a winner!
398		pop %si				# Restore
399		jmp ff.nextrec			# Keep looking.
400ff.match:	add $2,%sp			# Discard saved %si
401		clc				# Clear carry
402		ret
403
404#
405# Load DH sectors starting at LBA EAX into [EBX].
406#
407# Trashes: EAX
408#
409read:		push %si			# Save
410		push %cx			# Save since some BIOSs trash
411		mov %eax,edd_lba		# LBA to read from
412		mov %ebx,%eax			# Convert address
413		shr $4,%eax			#  to segment
414		mov %ax,edd_addr+0x2		#  and store
415read.retry:	call twiddle			# Entertain the user
416		push %dx			# Save
417		mov $edd_packet,%si		# Address Packet
418		mov %dh,edd_len			# Set length
419		mov drive,%dl			# BIOS Device
420		mov $0x42,%ah			# BIOS: Extended Read
421		int $0x13			# Call BIOS
422		pop %dx				# Restore
423		jc read.fail			# Worked?
424		pop %cx				# Restore
425		pop %si
426		ret				# Return
427read.fail:	cmp $ERROR_TIMEOUT,%ah		# Timeout?
428		je read.retry			# Yes, Retry.
429read.error:	mov %ah,%al			# Save error
430		mov $hex_error,%di		# Format it
431		call hex8			#  as hex
432		mov $msg_badread,%si		# Display Read error message
433
434#
435# Display error message at [SI] and halt.
436#
437error:		call putstr			# Display message
438halt:		hlt
439		jmp halt			# Spin
440
441#
442# Display a null-terminated string.
443#
444# Trashes: AX, SI
445#
446putstr:		push %bx			# Save
447putstr.load:	lodsb				# load %al from %ds:(%si)
448		test %al,%al			# stop at null
449		jnz putstr.putc			# if the char != null, output it
450		pop %bx				# Restore
451		ret				# return when null is hit
452putstr.putc:	call putc			# output char
453		jmp putstr.load			# next char
454
455#
456# Display a single char.
457#
458putc:		mov $0x7,%bx			# attribute for output
459		mov $0xe,%ah			# BIOS: put_char
460		int $0x10			# call BIOS, print char in %al
461		ret				# Return to caller
462
463#
464# Output the "twiddle"
465#
466twiddle:	push %ax			# Save
467		push %bx			# Save
468		mov twiddle_index,%al		# Load index
469		mov $twiddle_chars,%bx		# Address table
470		inc %al				# Next
471		and $3,%al			#  char
472		mov %al,twiddle_index		# Save index for next call
473		xlat				# Get char
474		call putc			# Output it
475		mov $8,%al			# Backspace
476		call putc			# Output it
477		pop %bx				# Restore
478		pop %ax				# Restore
479		ret
480
481#
482# Enable A20. Put an upper limit on the amount of time we wait for the
483# keyboard controller to get ready (65K x ISA access time). If
484# we wait more than that amount, the hardware is probably
485# legacy-free and simply doesn't have a keyboard controller.
486# Thus, the A20 line is already enabled.
487#
488seta20: 	cli				# Disable interrupts
489		xor %cx,%cx			# Clear
490seta20.1:	inc %cx				# Increment, overflow?
491		jz seta20.3			# Yes
492		in $0x64,%al			# Get status
493		test $0x2,%al			# Busy?
494		jnz seta20.1			# Yes
495		mov $0xd1,%al			# Command: Write
496		out %al,$0x64			#  output port
497seta20.2:	in $0x64,%al			# Get status
498		test $0x2,%al			# Busy?
499		jnz seta20.2			# Yes
500		mov $0xdf,%al			# Enable
501		out %al,$0x60			#  A20
502seta20.3:	sti				# Enable interrupts
503		ret				# To caller
504
505#
506# Convert AL to hex, saving the result to [EDI].
507#
508hex8:		pushl %eax			# Save
509		shrb $0x4,%al			# Do upper
510		call hex8.1			#  4
511		popl %eax			# Restore
512hex8.1: 	andb $0xf,%al			# Get lower 4
513		cmpb $0xa,%al			# Convert
514		sbbb $0x69,%al			#  to hex
515		das				#  digit
516		orb $0x20,%al			# To lower case
517		stosb				# Save char
518		ret				# (Recursive)
519
520#
521# BTX client to start btxldr
522#
523		.code32
524btx_client:	mov $(MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE-4), %esi
525						# %ds:(%esi) -> end
526						#  of boot[12] args
527		mov $(MEM_ARG_SIZE/4),%ecx	# Number of words to push
528		std				# Go backwards
529push_arg:	lodsl				# Read argument
530		push %eax			# Push it onto the stack
531		loop push_arg			# Push all of the arguments
532		cld				# In case anyone depends on this
533		pushl MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE # Entry point of
534						#  the loader
535		push %eax			# Emulate a near call
536		mov $0x1,%eax			# 'exec' system call
537		int $INT_SYS			# BTX system call
538btx_client_end:
539		.code16
540
541		.p2align 4
542#
543# Global descriptor table.
544#
545gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
546		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
547		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
548		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE (32-bit)
549		.word 0xffff,0x0,0x9a00,0x8f	# SEL_SCODE16 (16-bit)
550gdt.1:
551#
552# Pseudo-descriptors.
553#
554gdtdesc:	.word gdt.1-gdt-1		# Limit
555		.long gdt			# Base
556#
557# EDD Packet
558#
559edd_packet:	.byte 0x10			# Length
560		.byte 0				# Reserved
561edd_len:	.byte 0x0			# Num to read
562		.byte 0				# Reserved
563edd_addr:	.word 0x0,0x0			# Seg:Off
564edd_lba:	.quad 0x0			# LBA
565
566drive:		.byte 0
567
568#
569# State for searching dir
570#
571rec_lba:	.long 0x0			# LBA (adjusted for EA)
572rec_size:	.long 0x0			# File size
573name_len:	.byte 0x0			# Length of current name
574
575twiddle_index:	.byte 0x0
576
577msg_welcome:	.asciz	"CD Loader 1.2\r\n\n"
578msg_bootinfo:	.asciz	"Building the boot loader arguments\r\n"
579msg_relocate:	.asciz	"Relocating the loader and the BTX\r\n"
580msg_jump:	.asciz	"Starting the BTX loader\r\n"
581msg_badread:	.ascii  "Read Error: 0x"
582hex_error:	.asciz	"00\r\n"
583msg_novd:	.asciz  "Could not find Primary Volume Descriptor\r\n"
584msg_lookup:	.asciz  "Looking up "
585msg_lookup2:	.asciz  "... "
586msg_lookupok:	.asciz  "Found\r\n"
587msg_lookupfail:	.asciz  "File not found\r\n"
588msg_load2big:	.asciz  "File too big\r\n"
589msg_failed:	.asciz	"Boot failed\r\n"
590twiddle_chars:	.ascii	"|/-\\"
591loader_paths:	.asciz  "/BOOT/LOADER"
592		.asciz	"/boot/loader"
593		.byte 0
594
595