xref: /openbsd/sys/arch/amd64/stand/cdbr/cdbr.S (revision d415bd75)
1/*	$OpenBSD: cdbr.S,v 1.5 2013/01/17 12:07:19 jsing Exp $	*/
2
3/*
4 * Copyright (c) 2004 Tom Cosgrove <tom.cosgrove@arches-consulting.com>
5 * Copyright (c) 2001 John Baldwin <jhb@FreeBSD.org>
6 * All rights reserved.
7 *
8 * Redistribution and use in source and binary forms, with or without
9 * modification, are permitted provided that the following conditions
10 * are met:
11 * 1. Redistributions of source code must retain the above copyright
12 *    notice, this list of conditions and the following disclaimer.
13 * 2. Redistributions in binary form must reproduce the above copyright
14 *    notice, this list of conditions and the following disclaimer in the
15 *    documentation and/or other materials provided with the distribution.
16 * 3. Neither the name of the author nor the names of any co-contributors
17 *    may be used to endorse or promote products derived from this software
18 *    without specific prior written permission.
19 *
20 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
21 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
22 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
23 * ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
24 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
25 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
26 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
27 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
28 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
29 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
30 * SUCH DAMAGE.
31 */
32
33	.file	"cdbr.S"
34
35/*
36 * This program is a CD boot sector, similar to the partition boot record
37 * (pbr, also called biosboot) used by hard disks.  It is implemented as a
38 * "no-emulation" boot sector, as described in the "El Torito" Bootable
39 * CD-ROM Format Specification.
40 *
41 * The function of this boot sector is to load and start the next-stage
42 * cdboot program, which will load the kernel.
43 *
44 * The El Torito standard allows us to specify where we want to be loaded,
45 * but for maximum compatibility we choose the default load address of
46 * 0x07C00.
47 *
48 * Memory layout:
49 *
50 * 0x00000 -> 0x003FF	real mode interrupt vector table
51 * 0x00400 -> 0x00500	BIOS data segment
52 *
53 * 0x00000 -> 0x073FF	our stack (grows down)		(from 29k)
54 * 0x07400 -> 0x07BFF	we relocate to here		(at 29k)
55 * 0x07C00 -> 0x08400	BIOS loads us here		(at 31k, for 2k)
56 * 0x07C00 -> ...	/cdboot
57 *
58 * The BIOS loads us at physical address 0x07C00.  We then relocate to
59 * 0x07400, seg:offset 0740:0000.  We then load /cdboot at seg:offset
60 * 07C0:0000.
61 */
62#define BOOTSEG		0x7c0			/* segment we're loaded to */
63#define BOOTSECTSIZE	0x800			/* our size in bytes */
64#define BOOTRELOCSEG	0x740			/* segment we relocate to */
65#define BOOTSTACKOFF  ((BOOTRELOCSEG << 4) - 4)	/* starts here, grows down */
66
67/* Constants for reading from the CD */
68#define ERROR_TIMEOUT		0x80		/* BIOS timeout on read */
69#define NUM_RETRIES		3		/* Num times to retry */
70#define SECTOR_SIZE		0x800		/* size of a sector */
71#define SECTOR_SHIFT		11		/* number of place to shift */
72#define BUFFER_LEN		0x100		/* number of sectors in buffr */
73#define MAX_READ		0x10000		/* max we can read at a time */
74#define MAX_READ_PARAS		MAX_READ >> 4
75#define MAX_READ_SEC		MAX_READ >> SECTOR_SHIFT
76#define MEM_READ_BUFFER		0x9000		/* buffer to read from CD */
77#define MEM_VOLDESC		MEM_READ_BUFFER /* volume descriptor */
78#define MEM_DIR			MEM_VOLDESC+SECTOR_SIZE /* Lookup buffer */
79#define VOLDESC_LBA		0x10		/* LBA of vol descriptor */
80#define VD_PRIMARY		1		/* Primary VD */
81#define VD_END			255		/* VD Terminator */
82#define VD_ROOTDIR		156		/* Offset of Root Dir Record */
83#define DIR_LEN			0		/* Offset of Dir Rec length */
84#define DIR_EA_LEN		1		/* Offset of EA length */
85#define DIR_EXTENT		2		/* Offset of 64-bit LBA */
86#define DIR_SIZE		10		/* Offset of 64-bit length */
87#define DIR_NAMELEN		32		/* Offset of 8-bit name len */
88#define DIR_NAME		33		/* Offset of dir name */
89
90	.text
91	.code16
92
93	.globl	start
94start:
95	/* Set up stack */
96	xorw	%ax, %ax
97	movw	%ax, %ss
98	movw	$BOOTSTACKOFF, %sp
99
100	/* Relocate so we can load cdboot where we were */
101	movw	$BOOTSEG, %ax
102	movw	%ax, %ds
103	movw	$BOOTRELOCSEG, %ax
104	movw	%ax, %es
105	xorw	%si, %si
106	xorw	%di, %di
107	movw	$BOOTSECTSIZE, %cx	/* Bytes in cdbr, relocate it all */
108	cld
109	rep
110	movsb
111
112	/* Jump to relocated self */
113	ljmp $BOOTRELOCSEG, $reloc
114reloc:
115
116	/*
117	 * Set up %ds and %es: %ds is our data segment (= %cs), %es is
118	 * used to specify the segment address of the destination buffer
119	 * for cd reads.  We initially have %es = %ds.
120	 */
121	movw	%cs, %ax
122	movw	%ax, %ds
123	movw	%ax, %es
124
125	movb	%dl, drive		/* Store the boot drive number */
126
127	movw	$signon, %si		/* Say "hi", and give boot drive */
128	call	display_string
129	movb	drive, %al
130	call	hex_byte
131	movw	$crlf, %si
132	call	display_string
133
134/*
135 * Load Volume Descriptor
136 */
137	movl	$VOLDESC_LBA, %eax	/* Get the sector # for vol desc */
138load_vd:
139	pushl	%eax
140	movb	$1, %dh			/* One sector */
141	movw	$MEM_VOLDESC, %bx	/* Destination */
142	call	read			/* Read it in */
143	popl	%eax
144	cmpb	$VD_PRIMARY, (%bx)	/* Primary vol descriptor? */
145	je	have_vd			/* Yes */
146	inc	%eax			/* Try the next one */
147	cmpb	$VD_END, (%bx)		/* Is it the last one? */
148	jne	load_vd			/* No, so go try the next one */
149	movw	$msg_novd, %si		/* No pri vol descriptor */
150	jmp	err_stop		/* Panic */
151have_vd:				/* Have Primary VD */
152
153/*
154 * Look for the next-stage loader binary at pre-defined paths (loader_paths)
155 */
156	movw	$loader_paths, %si	/* Point to start of array */
157lookup_path:
158	movw	%si, loader		/* remember the one we're looking for */
159	pushw	%si			/* Save file name pointer */
160	call	lookup			/* Try to find file */
161	popw	%di			/* Restore file name pointer */
162	jnc	lookup_found		/* Found this file */
163	xorb	%al, %al		/* Look for next */
164	movw	$0xffff, %cx		/*  path name by */
165	repnz				/*  scanning for */
166	scasb				/*  nul char */
167	movw	%di, %si		/* Point %si at next path */
168	movb	(%si), %al		/* Get first char of next path */
169	orb	%al, %al		/* Is it double nul? */
170	jnz	lookup_path		/* No, try it */
171	movw	$msg_failed, %si	/* Failed message */
172	jmp	err_stop		/* Print it and halt */
173
174lookup_found:				/* Found a loader file */
175
176/*
177 * Load the binary into the buffer.  Due to real mode addressing limitations
178 * we have to read it in in 64k chunks.
179 */
180	movl	DIR_SIZE(%bx), %eax	/* Read file length */
181	add	$SECTOR_SIZE-1, %eax	/* Convert length to sectors */
182	shr	$SECTOR_SHIFT, %eax
183	cmp	$BUFFER_LEN, %eax
184	jbe	load_sizeok
185	movw	$msg_load2big, %si	/* Error message */
186	jmp	err_stop
187load_sizeok:
188	movzbw	%al, %cx		/* Num sectors to read */
189	movl	DIR_EXTENT(%bx), %eax	/* Load extent */
190	xorl	%edx, %edx
191	movb	DIR_EA_LEN(%bx), %dl
192	addl	%edx, %eax		/* Skip extended */
193
194	/* Use %bx to hold the segment (para) number */
195	movw	$BOOTSEG, %bx		/* We put cdboot here too */
196load_loop:
197	movb	%cl, %dh
198	cmpb	$MAX_READ_SEC, %cl	/* Truncate to max read size */
199	jbe	load_notrunc
200	movb	$MAX_READ_SEC, %dh
201load_notrunc:
202	subb	%dh, %cl		/* Update count */
203	pushl	%eax			/* Save */
204	pushl	%ebx			/* Save */
205	movw	%bx, %es		/* %bx has the segment (para) number */
206	xorw	%bx, %bx		/* %es:0000 for destination */
207	call	read			/* Read it in */
208	popl	%ebx			/* Restore */
209	popl	%eax			/* Restore */
210	addl	$MAX_READ_SEC, %eax	/* Update LBA */
211	addw	$MAX_READ_PARAS, %bx	/* Update dest addr */
212	jcxz	load_done		/* Done? */
213	jmp	load_loop		/* Keep going */
214load_done:
215
216	/* Now we can start the loaded program */
217
218	movw	loader, %cx		/* Tell cdboot where it is */
219					/* (Older versions of cdbr have */
220					/*  %cx == 0 from the jcxz load_done) */
221	movb	drive, %dl		/* Get the boot drive number */
222	ljmp	$BOOTSEG, $0		/* Go run cdboot */
223
224/*
225 * Lookup the file in the path at [SI] from the root directory.
226 *
227 * Trashes: All but BX
228 * Returns: CF = 0 (success), BX = pointer to record
229 *          CF = 1 (not found)
230 */
231lookup:
232	movw	$VD_ROOTDIR + MEM_VOLDESC, %bx	/* Root directory record */
233
234lookup_dir:
235	lodsb				/* Get first char of path */
236	cmpb	$0, %al			/* Are we done? */
237	je	lookup_done		/* Yes */
238	cmpb	$'/', %al		/* Skip path separator */
239	je	lookup_dir
240	decw	%si			/* Undo lodsb side effect */
241	call	find_file		/* Lookup first path item */
242	jnc	lookup_dir		/* Try next component */
243	ret
244lookup_done:
245	movw	$msg_loading, %si	/* Success message - say which file */
246	call	display_string
247	mov	loader, %si
248	call	display_string
249	mov	$crlf, %si
250	call	display_string
251	clc				/* Clear carry */
252	ret
253
254/*
255 * Lookup file at [SI] in directory whose record is at [BX].
256 *
257 * Trashes: All but returns
258 * Returns: CF = 0 (success), BX = pointer to record, SI = next path item
259 *          CF = 1 (not found), SI = preserved
260 */
261find_file:
262	mov	DIR_EXTENT(%bx), %eax	/* Load extent */
263	xor	%edx, %edx
264	mov	DIR_EA_LEN(%bx), %dl
265	add	%edx, %eax		/* Skip extended attributes */
266	mov	%eax, rec_lba		/* Save LBA */
267	mov	DIR_SIZE(%bx), %eax	/* Save size */
268	mov	%eax, rec_size
269	xor	%cl, %cl		/* Zero length */
270	push	%si			/* Save */
271ff_namelen:
272	inc	%cl			/* Update length */
273	lodsb				/* Read char */
274	cmp	$0, %al			/* Nul? */
275	je	ff_namedone		/* Yes */
276	cmp	$'/', %al		/* Path separator? */
277	jnz	ff_namelen		/* No, keep going */
278ff_namedone:
279	dec	%cl			/* Adjust length and save */
280	mov	%cl, name_len
281	pop	%si			/* Restore */
282ff_load:
283	mov	rec_lba, %eax		/* Load LBA */
284	mov	$MEM_DIR, %ebx		/* Address buffer */
285	mov	$1, %dh			/* One sector */
286	call	read			/* Read directory block */
287	incl	rec_lba			/* Update LBA to next block */
288ff_scan:
289	mov	%ebx, %edx		/* Check for EOF */
290	sub	$MEM_DIR, %edx
291	cmp	%edx, rec_size
292	ja	ff_scan_1
293	stc				/* EOF reached */
294	ret
295ff_scan_1:
296	cmpb	$0, DIR_LEN(%bx)	/* Last record in block? */
297	je	ff_nextblock
298	push	%si			/* Save */
299	movzbw	DIR_NAMELEN(%bx), %si	/* Find end of string */
300ff_checkver:
301	cmpb	$'0', DIR_NAME-1(%bx,%si)	/* Less than '0'? */
302	jb	ff_checkver_1
303	cmpb	$'9', DIR_NAME-1(%bx,%si)	/* Greater than '9'? */
304	ja	ff_checkver_1
305	dec	%si			/* Next char */
306	jnz	ff_checkver
307	jmp	ff_checklen		/* All numbers in name, so */
308					/*  no version */
309ff_checkver_1:
310	movzbw	DIR_NAMELEN(%bx), %cx
311	cmp	%cx, %si		/* Did we find any digits? */
312	je	ff_checkdot		/* No */
313	cmpb	$';', DIR_NAME-1(%bx,%si)	/* Check for semicolon */
314	jne	ff_checkver_2
315	dec	%si			/* Skip semicolon */
316	mov	%si, %cx
317	mov	%cl, DIR_NAMELEN(%bx)	/* Adjust length */
318	jmp	ff_checkdot
319ff_checkver_2:
320	mov	%cx, %si		/* Restore %si to end of string */
321ff_checkdot:
322	cmpb	$'.', DIR_NAME-1(%bx,%si)	/* Trailing dot? */
323	jne	ff_checklen			/* No */
324	decb	DIR_NAMELEN(%bx)	/* Adjust length */
325ff_checklen:
326	pop	%si			/* Restore */
327	movzbw	name_len, %cx		/* Load length of name */
328	cmp	%cl, DIR_NAMELEN(%bx)	/* Does length match? */
329	je	ff_checkname		/* Yes, check name */
330ff_nextrec:
331	add	DIR_LEN(%bx), %bl	/* Next record */
332	adc	$0, %bh
333	jmp	ff_scan
334ff_nextblock:
335	subl	$SECTOR_SIZE, rec_size	/* Adjust size */
336	jnc	ff_load			/* If subtract ok, keep going */
337	ret				/* End of file, so not found */
338ff_checkname:
339	lea	DIR_NAME(%bx), %di	/* Address name in record */
340	push	%si			/* Save */
341	repe	cmpsb			/* Compare name */
342	jcxz	ff_match		/* We have a winner! */
343	pop	%si			/* Restore */
344	jmp	ff_nextrec		/* Keep looking */
345ff_match:
346	add	$2, %sp			/* Discard saved %si */
347	clc				/* Clear carry */
348	ret
349
350/*
351 * Load DH sectors starting at LBA %eax into address %es:%bx.
352 *
353 * Preserves %bx, %cx, %dx, %si, %es
354 * Trashes %eax
355 */
356read:
357	pushw	%si			/* Save */
358	pushw	%cx			/* Save since some BIOSs trash */
359	movl	%eax, edd_lba		/* LBA to read from */
360	movw	%es, %ax		/* Get the segment */
361	movw	%ax, edd_addr + 2	/*  and store */
362	movw	%bx, edd_addr		/* Store offset too */
363read_retry:
364	call	twiddle			/* Entertain the user */
365	pushw	%dx			/* Save */
366	movw	$edd_packet, %si	/* Address Packet */
367	movb	%dh, edd_len		/* Set length */
368	movb	drive, %dl		/* BIOS Device */
369	movb	$0x42, %ah		/* BIOS: Extended Read */
370	int	$0x13			/* Call BIOS */
371	popw	%dx			/* Restore */
372	jc	read_fail		/* Worked? */
373	popw	%cx			/* Restore */
374	popw	%si
375	ret				/* Return */
376read_fail:
377	cmpb	$ERROR_TIMEOUT, %ah	/* Timeout? */
378	je	read_retry		/* Yes, Retry */
379read_error:
380	pushw	%ax			/* Save error */
381	movw	$msg_badread, %si	/* "Read error: 0x" */
382	call	display_string
383	popw	%ax			/* Retrieve error code */
384	movb	%ah, %al		/* Into %al */
385	call	hex_byte		/* Display error code */
386	jmp	stay_stopped		/* ... then hang */
387
388/*
389 * Display the ASCIZ error message in %esi then halt
390 */
391err_stop:
392	call	display_string
393
394stay_stopped:
395	sti				/* Ensure Ctl-Alt-Del will work */
396	hlt				/* (don't require power cycle) */
397	jmp	stay_stopped		/* (Just to make sure) */
398
399/*
400 * Output the "twiddle"
401 */
402twiddle:
403	push	%ax			/* Save */
404	push	%bx			/* Save */
405	mov	twiddle_index, %al	/* Load index */
406	mov	twiddle_chars, %bx	/* Address table */
407	inc	%al			/* Next */
408	and	$3, %al			/*  char */
409	mov	%al, twiddle_index	/* Save index for next call */
410	xlat				/* Get char */
411	call	display_char		/* Output it */
412	mov	$8, %al			/* Backspace */
413	call	display_char		/* Output it */
414	pop	%bx			/* Restore */
415	pop	%ax			/* Restore */
416	ret
417
418/*
419 * Display the ASCIZ string pointed to by %si.
420 *
421 * Destroys %si, possibly others.
422 */
423display_string:
424	pushw	%ax
425	cld
4261:
427	lodsb			/* %al = *%si++ */
428	testb	%al, %al
429	jz	1f
430	call    display_char
431	jmp	1b
432
433/*
434 * Write out value in %eax in hex
435 */
436hex_long:
437	pushl	%eax
438	shrl	$16, %eax
439	call	hex_word
440	popl	%eax
441	/* fall thru */
442
443/*
444 * Write out value in %ax in hex
445 */
446hex_word:
447	pushw	%ax
448	mov	%ah, %al
449	call	hex_byte
450	popw	%ax
451	/* fall thru */
452/*
453 * Write out value in %al in hex
454 */
455hex_byte:
456	pushw	%ax
457	shrb	$4, %al
458	call	hex_nibble
459	popw	%ax
460	/* fall thru */
461
462/* Write out nibble in %al */
463hex_nibble:
464	and	$0x0F, %al
465	add	$'0', %al
466	cmpb	$'9', %al
467	jbe	display_char
468	addb	$'A'-'9'-1, %al
469	/* fall thru to display_char */
470
471/*
472 * Display the character in %al
473 */
474display_char:
475	pushw	%ax
476
477	pushw	%bx
478	movb	$0x0e, %ah
479	movw	$1, %bx
480	int	$0x10
481	popw	%bx
4821:	popw	%ax
483	ret
484
485/*
486 * Data
487 */
488drive:		.byte	0			/* Given to us by the BIOS */
489signon:		.asciz	"CD-ROM: "
490crlf:		.asciz	"\r\n"
491msg_load2big:	.asciz  "File too big"
492msg_badread:	.asciz  "Read error: 0x"
493msg_novd:	.asciz  "No Primary Volume Descriptor"
494msg_loading:	.asciz  "Loading "
495
496/* State for searching dir */
497rec_lba:	.long	0x0			/* LBA (adjusted for EA) */
498rec_size:	.long	0x0			/* File size */
499name_len:	.byte	0x0			/* Length of current name */
500
501twiddle_index:	.byte	0x0
502twiddle_chars:	.ascii	"|/-\\"
503
504/* Packet for LBA (CD) read */
505edd_packet:	.byte	0x10			/* Length */
506		.byte	0			/* Reserved */
507edd_len:	.byte	0x0			/* Num to read */
508		.byte	0			/* Reserved */
509edd_addr:	.word	0x0, 0x0		/* Seg:Off */
510edd_lba:	.quad	0x0			/* LBA */
511
512/* The data from here must be last in the file, only followed by 0x00 bytes */
513
514loader:		.word	0			/* The path we end up using */
515
516msg_failed:	.ascii	"Can't find "		/* This string runs into... */
517
518/* loader_paths is a list of ASCIZ strings followed by a term NUL byte */
519loader_paths:	.asciz  "/cdboot"
520		.asciz	"/CDBOOT"
521		.ascii	"/", OSREV, "/", MACH, "/cdboot"
522		.byte	0			/* NUL-term line above */
523		.ascii	"/", OSREV, "/", MACH_U, "/CDBOOT"
524		.byte	0			/* NUL-term line above */
525		.byte	0			/* Terminate the list */
526
527	. = BOOTSECTSIZE
528
529	.end
530