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