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