cdboot.S revision 124445
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 124445 2004-01-12 20:34:42Z 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 $msg_welcome,%si		# %ds:(%si) -> welcome message
107		call putstr			# display the welcome message
108#
109# Setup the arguments that the loader is expecting from boot[12]
110#
111		mov $msg_bootinfo,%si		# %ds:(%si) -> boot args message
112		call putstr			# display the message
113		mov $MEM_ARG,%bx		# %ds:(%bx) -> boot args
114		mov %bx,%di			# %es:(%di) -> boot args
115		xor %eax,%eax			# zero %eax
116		mov $(MEM_ARG_SIZE/4),%cx	# Size of arguments in 32-bit
117						#  dwords
118		rep				# Clear the arguments
119		stosl				#  to zero
120		mov drive,%dl			# Store BIOS boot device
121		mov %dl,0x4(%bx)		#  in kargs->bootdev
122		or $KARGS_FLAGS_CD,0x8(%bx)	# kargs->bootflags |=
123						#  KARGS_FLAGS_CD
124#
125# Load Volume Descriptor
126#
127		mov $VOLDESC_LBA,%eax		# Set LBA of first VD
128load_vd:	push %eax			# Save %eax
129		mov $1,%dh			# One sector
130		mov $MEM_VOLDESC,%ebx		# Destination
131		call read			# Read it in
132		cmpb $VD_PRIMARY,(%bx)		# Primary VD?
133		je have_vd			# Yes
134		pop %eax			# Prepare to
135		inc %eax			#  try next
136		cmpb $VD_END,(%bx)		# Last VD?
137		jne load_vd			# No, read next
138		mov $msg_novd,%si		# No VD
139		jmp error			# Halt
140have_vd:					# Have Primary VD
141#
142# Try to look up the loader binary using the paths in the loader_paths
143# array.
144#
145		mov $loader_paths,%si		# Point to start of array
146lookup_path:	push %si			# Save file name pointer
147		call lookup			# Try to find file
148		pop %di				# Restore file name pointer
149		jnc lookup_found		# Found this file
150		xor %al,%al			# Look for next
151		mov $0xffff,%cx			#  path name by
152		repnz				#  scanning for
153		scasb				#  nul char
154		inc %di				# Skip nul
155		mov %di,%si			# Point %si at next path
156		mov (%si),%al			# Get first char of next path
157		or %al,%al			# Is it double nul?
158		jnz lookup_path			# No, try it.
159		mov $msg_failed,%si		# Failed message
160		jmp error			# Halt
161lookup_found:					# Found a loader file
162#
163# Load the binary into the buffer.  Due to real mode addressing limitations
164# we have to read it in in 64k chunks.
165#
166		mov DIR_SIZE(%bx),%eax		# Read file length
167		add $SECTOR_SIZE-1,%eax		# Convert length to sectors
168		shr $SECTOR_SHIFT,%eax
169		cmp $BUFFER_LEN,%eax
170		jbe load_sizeok
171		mov $msg_load2big,%si		# Error message
172		call error
173load_sizeok:	movzbw %al,%cx			# Num sectors to read
174		mov DIR_EXTENT(%bx),%eax	# Load extent
175		xor %edx,%edx
176		mov DIR_EA_LEN(%bx),%dl
177		add %edx,%eax			# Skip extended
178		mov $MEM_READ_BUFFER,%ebx	# Read into the buffer
179load_loop:	mov %cl,%dh
180		cmp $MAX_READ_SEC,%cl		# Truncate to max read size
181		jbe load_notrunc
182		mov $MAX_READ_SEC,%dh
183load_notrunc:	sub %dh,%cl			# Update count
184		push %eax			# Save
185		call read			# Read it in
186		pop %eax			# Restore
187		add $MAX_READ_SEC,%eax		# Update LBA
188		add $MAX_READ,%ebx		# Update dest addr
189		jcxz load_done			# Done?
190		jmp load_loop			# Keep going
191load_done:
192#
193# Turn on the A20 address line
194#
195		call seta20			# Turn A20 on
196#
197# Relocate the loader and BTX using a very lazy protected mode
198#
199		mov $msg_relocate,%si		# Display the
200		call putstr			#  relocation message
201		mov MEM_READ_BUFFER+AOUT_ENTRY,%edi # %edi is the destination
202		mov $(MEM_READ_BUFFER+AOUT_HEADER),%esi	# %esi is
203						#  the start of the text
204						#  segment
205		mov MEM_READ_BUFFER+AOUT_TEXT,%ecx # %ecx = length of the text
206						#  segment
207		push %edi			# Save entry point for later
208		lgdt gdtdesc			# setup our own gdt
209		cli				# turn off interrupts
210		mov %cr0,%eax			# Turn on
211		or $0x1,%al			#  protected
212		mov %eax,%cr0			#  mode
213		ljmp $SEL_SCODE,$pm_start	# long jump to clear the
214						#  instruction pre-fetch queue
215		.code32
216pm_start:	mov $SEL_SDATA,%ax		# Initialize
217		mov %ax,%ds			#  %ds and
218		mov %ax,%es			#  %es to a flat selector
219		rep				# Relocate the
220		movsb				#  text segment
221		add $(MEM_PAGE_SIZE - 1),%edi	# pad %edi out to a new page
222		and $~(MEM_PAGE_SIZE - 1),%edi #  for the data segment
223		mov MEM_READ_BUFFER+AOUT_DATA,%ecx # size of the data segment
224		rep				# Relocate the
225		movsb				#  data segment
226		mov MEM_READ_BUFFER+AOUT_BSS,%ecx # size of the bss
227		xor %eax,%eax			# zero %eax
228		add $3,%cl			# round %ecx up to
229		shr $2,%ecx			#  a multiple of 4
230		rep				# zero the
231		stosl				#  bss
232		mov MEM_READ_BUFFER+AOUT_ENTRY,%esi # %esi -> relocated loader
233		add $MEM_BTX_OFFSET,%esi	# %esi -> BTX in the loader
234		mov $MEM_BTX_ADDRESS,%edi	# %edi -> where BTX needs to go
235		movzwl 0xa(%esi),%ecx		# %ecx -> length of BTX
236		rep				# Relocate
237		movsb				#  BTX
238		ljmp $SEL_SCODE16,$pm_16	# Jump to 16-bit PM
239		.code16
240pm_16:		mov $SEL_RDATA,%ax		# Initialize
241		mov %ax,%ds			#  %ds and
242		mov %ax,%es			#  %es to a real mode selector
243		mov %cr0,%eax			# Turn off
244		and $~0x1,%al			#  protected
245		mov %eax,%cr0			#  mode
246		ljmp $0,$pm_end			# Long jump to clear the
247						#  instruction pre-fetch queue
248pm_end:		sti				# Turn interrupts back on now
249#
250# Copy the BTX client to MEM_BTX_CLIENT
251#
252		xor %ax,%ax			# zero %ax and set
253		mov %ax,%ds			#  %ds and %es
254		mov %ax,%es			#  to segment 0
255		mov $MEM_BTX_CLIENT,%di		# Prepare to relocate
256		mov $btx_client,%si		#  the simple btx client
257		mov $(btx_client_end-btx_client),%cx # length of btx client
258		rep				# Relocate the
259		movsb				#  simple BTX client
260#
261# Copy the boot[12] args to where the BTX client can see them
262#
263		mov $MEM_ARG,%si		# where the args are at now
264		mov $MEM_ARG_BTX,%di		# where the args are moving to
265		mov $(MEM_ARG_SIZE/4),%cx	# size of the arguments in longs
266		rep				# Relocate
267		movsl				#  the words
268#
269# Save the entry point so the client can get to it later on
270#
271		pop %eax			# Restore saved entry point
272		stosl				#  and add it to the end of
273						#  the arguments
274#
275# Now we just start up BTX and let it do the rest
276#
277		mov $msg_jump,%si		# Display the
278		call putstr			#  jump message
279		ljmp $0,$MEM_BTX_ENTRY		# Jump to the BTX entry point
280
281#
282# Lookup the file in the path at [SI] from the root directory.
283#
284# Trashes: All but BX
285# Returns: CF = 0 (success), BX = pointer to record
286#          CF = 1 (not found)
287#
288lookup:		mov $VD_ROOTDIR+MEM_VOLDESC,%bx	# Root directory record
289		push %si
290		mov $msg_lookup,%si		# Display lookup message
291		call putstr
292		pop %si
293		push %si
294		call putstr
295		mov $msg_lookup2,%si
296		call putstr
297		pop %si
298lookup_dir:	lodsb				# Get first char of path
299		cmp $0,%al			# Are we done?
300		je lookup_done			# Yes
301		cmp $'/',%al			# Skip path separator.
302		je lookup_dir
303		dec %si				# Undo lodsb side effect
304		call find_file			# Lookup first path item
305		jnc lookup_dir			# Try next component
306		mov $msg_lookupfail,%si		# Not found message
307		call putstr
308		stc				# Set carry
309		ret
310		jmp error
311lookup_done:	mov $msg_lookupok,%si		# Success message
312		call putstr
313		clc				# Clear carry
314		ret
315
316#
317# Lookup file at [SI] in directory whose record is at [BX].
318#
319# Trashes: All but returns
320# Returns: CF = 0 (success), BX = pointer to record, SI = next path item
321#          CF = 1 (not found), SI = preserved
322#
323find_file:	mov DIR_EXTENT(%bx),%eax	# Load extent
324		xor %edx,%edx
325		mov DIR_EA_LEN(%bx),%dl
326		add %edx,%eax			# Skip extended attributes
327		mov %eax,rec_lba		# Save LBA
328		mov DIR_SIZE(%bx),%eax		# Save size
329		mov %eax,rec_size
330		xor %cl,%cl			# Zero length
331		push %si			# Save
332ff.namelen:	inc %cl				# Update length
333		lodsb				# Read char
334		cmp $0,%al			# Nul?
335		je ff.namedone			# Yes
336		cmp $'/',%al			# Path separator?
337		jnz ff.namelen			# No, keep going
338ff.namedone:	dec %cl				# Adjust length and save
339		mov %cl,name_len
340		pop %si				# Restore
341ff.load:	mov rec_lba,%eax		# Load LBA
342		mov $MEM_DIR,%ebx		# Address buffer
343		mov $1,%dh			# One sector
344		call read			# Read directory block
345		incl rec_lba			# Update LBA to next block
346ff.scan:	mov %ebx,%edx			# Check for EOF
347		sub $MEM_DIR,%edx
348		cmp %edx,rec_size
349		ja ff.scan.1
350		stc				# EOF reached
351		ret
352ff.scan.1:	cmpb $0,DIR_LEN(%bx)		# Last record in block?
353		je ff.nextblock
354		push %si			# Save
355		movzbw DIR_NAMELEN(%bx),%si	# Find end of string
356ff.checkver:	cmpb $'0',DIR_NAME-1(%bx,%si)	# Less than '0'?
357		jb ff.checkver.1
358		cmpb $'9',DIR_NAME-1(%bx,%si)	# Greater than '9'?
359		ja ff.checkver.1
360		dec %si				# Next char
361		jnz ff.checkver
362		jmp ff.checklen			# All numbers in name, so
363						#  no version
364ff.checkver.1:	movzbw DIR_NAMELEN(%bx),%cx
365		cmp %cx,%si			# Did we find any digits?
366		je ff.checkdot			# No
367		cmpb $';',DIR_NAME-1(%bx,%si)	# Check for semicolon
368		jne ff.checkver.2
369		dec %si				# Skip semicolon
370		mov %si,%cx
371		mov %cl,DIR_NAMELEN(%bx)	# Adjust length
372		jmp ff.checkdot
373ff.checkver.2:	mov %cx,%si			# Restore %si to end of string
374ff.checkdot:	cmpb $'.',DIR_NAME-1(%bx,%si)	# Trailing dot?
375		jne ff.checklen			# No
376		decb DIR_NAMELEN(%bx)		# Adjust length
377ff.checklen:	pop %si				# Restore
378		movzbw name_len,%cx		# Load length of name
379		cmp %cl,DIR_NAMELEN(%bx)	# Does length match?
380		je ff.checkname			# Yes, check name
381ff.nextrec:	add DIR_LEN(%bx),%bl		# Next record
382		adc $0,%bh
383		jmp ff.scan
384ff.nextblock:	subl $SECTOR_SIZE,rec_size	# Adjust size
385		jnc ff.load			# If subtract ok, keep going
386		ret				# End of file, so not found
387ff.checkname:	lea DIR_NAME(%bx),%di		# Address name in record
388		push %si			# Save
389		repe cmpsb			# Compare name
390		jcxz ff.match			# We have a winner!
391		pop %si				# Restore
392		jmp ff.nextrec			# Keep looking.
393ff.match:	add $2,%sp			# Discard saved %si
394		clc				# Clear carry
395		ret
396
397#
398# Load DH sectors starting at LBA EAX into [EBX].
399#
400# Trashes: EAX
401#
402read:		push %si			# Save
403		push %cx			# Save since some BIOSs trash
404		mov %eax,edd_lba		# LBA to read from
405		mov %ebx,%eax			# Convert address
406		shr $4,%eax			#  to segment
407		mov %ax,edd_addr+0x2		#  and store
408read.retry:	call twiddle			# Entertain the user
409		push %dx			# Save
410		mov $edd_packet,%si		# Address Packet
411		mov %dh,edd_len			# Set length
412		mov drive,%dl			# BIOS Device
413		mov $0x42,%ah			# BIOS: Extended Read
414		int $0x13			# Call BIOS
415		pop %dx				# Restore
416		jc read.fail			# Worked?
417		pop %cx				# Restore
418		pop %si
419		ret				# Return
420read.fail:	cmp $ERROR_TIMEOUT,%ah		# Timeout?
421		je read.retry			# Yes, Retry.
422read.error:	mov %ah,%al			# Save error
423		mov $hex_error,%di		# Format it
424		call hex8			#  as hex
425		mov $msg_badread,%si		# Display Read error message
426
427#
428# Display error message at [SI] and halt.
429#
430error:		call putstr			# Display message
431halt:		hlt
432		jmp halt			# Spin
433
434#
435# Display a null-terminated string.
436#
437# Trashes: AX, SI
438#
439putstr:		push %bx			# Save
440putstr.load:	lodsb				# load %al from %ds:(%si)
441		test %al,%al			# stop at null
442		jnz putstr.putc			# if the char != null, output it
443		pop %bx				# Restore
444		ret				# return when null is hit
445putstr.putc:	call putc			# output char
446		jmp putstr.load			# next char
447
448#
449# Display a single char.
450#
451putc:		mov $0x7,%bx			# attribute for output
452		mov $0xe,%ah			# BIOS: put_char
453		int $0x10			# call BIOS, print char in %al
454		ret				# Return to caller
455
456#
457# Output the "twiddle"
458#
459twiddle:	push %ax			# Save
460		push %bx			# Save
461		mov twiddle_index,%al		# Load index
462		mov twiddle_chars,%bx		# Address table
463		inc %al				# Next
464		and $3,%al			#  char
465		mov %al,twiddle_index		# Save index for next call
466		xlat				# Get char
467		call putc			# Output it
468		mov $8,%al			# Backspace
469		call putc			# Output it
470		pop %bx				# Restore
471		pop %ax				# Restore
472		ret
473
474#
475# Enable A20
476#
477seta20: 	cli				# Disable interrupts
478seta20.1:	in $0x64,%al			# Get status
479		test $0x2,%al			# Busy?
480		jnz seta20.1			# Yes
481		mov $0xd1,%al			# Command: Write
482		out %al,$0x64			#  output port
483seta20.2:	in $0x64,%al			# Get status
484		test $0x2,%al			# Busy?
485		jnz seta20.2			# Yes
486		mov $0xdf,%al			# Enable
487		out %al,$0x60			#  A20
488		sti				# Enable interrupts
489		ret				# To caller
490
491#
492# Convert AL to hex, saving the result to [EDI].
493#
494hex8:		pushl %eax			# Save
495		shrb $0x4,%al			# Do upper
496		call hex8.1			#  4
497		popl %eax			# Restore
498hex8.1: 	andb $0xf,%al			# Get lower 4
499		cmpb $0xa,%al			# Convert
500		sbbb $0x69,%al			#  to hex
501		das				#  digit
502		orb $0x20,%al			# To lower case
503		stosb				# Save char
504		ret				# (Recursive)
505
506#
507# BTX client to start btxldr
508#
509		.code32
510btx_client:	mov $(MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE-4), %esi
511						# %ds:(%esi) -> end
512						#  of boot[12] args
513		mov $(MEM_ARG_SIZE/4),%ecx	# Number of words to push
514		std				# Go backwards
515push_arg:	lodsl				# Read argument
516		push %eax			# Push it onto the stack
517		loop push_arg			# Push all of the arguments
518		cld				# In case anyone depends on this
519		pushl MEM_ARG_BTX-MEM_BTX_CLIENT+MEM_ARG_SIZE # Entry point of
520						#  the loader
521		push %eax			# Emulate a near call
522		mov $0x1,%eax			# 'exec' system call
523		int $INT_SYS			# BTX system call
524btx_client_end:
525		.code16
526
527		.p2align 4
528#
529# Global descriptor table.
530#
531gdt:		.word 0x0,0x0,0x0,0x0		# Null entry
532		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
533		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
534		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE (32-bit)
535		.word 0xffff,0x0,0x9a00,0x8f	# SEL_SCODE16 (16-bit)
536gdt.1:
537#
538# Pseudo-descriptors.
539#
540gdtdesc:	.word gdt.1-gdt-1		# Limit
541		.long gdt			# Base
542#
543# EDD Packet
544#
545edd_packet:	.byte 0x10			# Length
546		.byte 0				# Reserved
547edd_len:	.byte 0x0			# Num to read
548		.byte 0				# Reserved
549edd_addr:	.word 0x0,0x0			# Seg:Off
550edd_lba:	.quad 0x0			# LBA
551
552drive:		.byte 0
553
554#
555# State for searching dir
556#
557rec_lba:	.long 0x0			# LBA (adjusted for EA)
558rec_size:	.long 0x0			# File size
559name_len:	.byte 0x0			# Length of current name
560
561twiddle_index:	.byte 0x0
562
563msg_welcome:	.asciz	"CD Loader 1.2\r\n\n"
564msg_bootinfo:	.asciz	"Building the boot loader arguments\r\n"
565msg_relocate:	.asciz	"Relocating the loader and the BTX\r\n"
566msg_jump:	.asciz	"Starting the BTX loader\r\n"
567msg_badread:	.ascii  "Read Error: 0x"
568hex_error:	.ascii	"00\r\n"
569msg_novd:	.asciz  "Could not find Primary Volume Descriptor\r\n"
570msg_lookup:	.asciz  "Looking up "
571msg_lookup2:	.asciz  "... "
572msg_lookupok:	.asciz  "Found\r\n"
573msg_lookupfail:	.asciz  "File not found\r\n"
574msg_load2big:	.asciz  "File too big\r\n"
575msg_failed:	.asciz	"Boot failed\r\n"
576twiddle_chars:	.ascii	"|/-\\"
577loader_paths:	.asciz  "/BOOT/LOADER"
578		.asciz	"/boot/loader"
579		.byte 0
580
581