xref: /netbsd-src/sys/arch/i386/stand/bootxx/pbr.S (revision 69b6d498973bb4d7230c2d3c12bd9a032738ec8e)
1/*	$NetBSD: pbr.S,v 1.12 2005/01/17 21:28:51 dsl Exp $	*/
2
3/*-
4 * Copyright (c) 2003,2004 The NetBSD Foundation, Inc.
5 * All rights reserved.
6 *
7 * This code is derived from software contributed to The NetBSD Foundation
8 * by David Laight.
9 *
10 * Redistribution and use in source and binary forms, with or without
11 * modification, are permitted provided that the following conditions
12 * are met:
13 * 1. Redistributions of source code must retain the above copyright
14 *    notice, this list of conditions and the following disclaimer.
15 * 2. Redistributions in binary form must reproduce the above copyright
16 *    notice, this list of conditions and the following disclaimer in the
17 *    documentation and/or other materials provided with the distribution.
18 * 3. All advertising materials mentioning features or use of this software
19 *    must display the following acknowledgement:
20 *        This product includes software developed by the NetBSD
21 *        Foundation, Inc. and its contributors.
22 * 4. Neither the name of The NetBSD Foundation nor the names of its
23 *    contributors may be used to endorse or promote products derived
24 *    from this software without specific prior written permission.
25 *
26 * THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
27 * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
28 * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
29 * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS
30 * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
31 * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
32 * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
33 * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
34 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
35 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
36 * POSSIBILITY OF SUCH DAMAGE.
37 */
38
39/*
40 * i386 partition boot code
41 *
42 * This code resides in sector zero of the netbsd partition, or sector
43 * zero of an unpartitioned disk (eg a floppy).
44 * Sector 1 is assumed to contain the netbsd disklabel.
45 * Sectors 2 until the end of the track contain the next phase of bootstrap.
46 * Which know how to read the interactive 'boot' program from filestore.
47 * The job of this code is to read in the phase 1 bootstrap.
48 *
49 * Makefile supplies:
50 * PRIMARY_LOAD_ADDRESS:	Address we load code to (0x600).
51 * BOOTXX_SECTORS:		Number of sectors we load (15).
52 * X86_BOOT_MAGIC_1:		A random magic number.
53 *
54 * Although this code is executing at 0x7c00, it is linked to address 0x600.
55 * All data references MUST be fixed up using R().
56 */
57
58#include <machine/asm.h>
59#include <sys/bootblock.h>
60
61#define	OURADDR		0x7c00		/* our address */
62#define BOOTADDR	PRIMARY_LOAD_ADDRESS
63
64#define R(a) (a - BOOTADDR + OURADDR)
65
66#define lba_info R(_lba_info)
67#define lba_sector R(_lba_sector)
68#define errtxt R(_errtxt)
69#define errcod R(_errcod)
70#define newline R(_newline)
71
72#define TABENTRYSIZE	(MBR_BS_PARTNAMESIZE + 1)
73#define NAMETABSIZE	(4 * TABENTRYSIZE)
74
75#ifdef BOOT_FROM_FAT
76#define MBR_AFTERBPB	90		/* BPB size in FAT32 partition BR */
77#else
78#define MBR_AFTERBPB	62		/* BPB size in floppy master BR */
79#endif
80
81#ifdef TERSE_ERROR
82/*
83 * Error codes. Done this way to save space.
84 */
85#define ERR_READ	'2'		/* Read error */
86#define ERR_NO_BOOTXX	'B'		/* No bootxx_xfs in 3rd sector */
87#define	ERR_PTN		'P'		/* partition not defined */
88#define	ERR_NO_LBA	'L'		/* sector above chs limit */
89
90#define	set_err(err)	movb	$err, %al
91
92#else
93#define	set_err(err)	mov	$R(err), %ax
94#endif
95
96/*
97 * This code is loaded to addresss 0:7c00 by either the system BIOS
98 * (for a floppy) or the mbr boot code.  Since the boot program will
99 * be loaded to address 1000:0, we don't need to relocate ourselves
100 * and can load the subsequent blocks (that load boot) to an address
101 * of our choosing. 0:600 is a not unreasonable choice.
102 *
103 * On entry the BIOS drive number is in %dl and %esi may contain the
104 * sector we were loaded from (if we were loaded by NetBSD mbr code).
105 * In any case we have to re-read sector zero of the disk and hunt
106 * through the BIOS partition table for the NetBSD partition.
107 */
108
109	.text
110	.code16
111ENTRY(start)
112	/*
113	 * The PC BIOS architecture defines a Boot Parameter Block (BPB) here.
114	 * The actual format varies between different MS-DOS versions, but
115	 * apparantly some system BIOS insist on patching this area
116	 * (especially on LS120 drives - which I thought had an MBR...).
117	 * The initial jmp and nop are part of the standard and may be
118	 * tested for by the system BIOS.
119	 */
120	jmp	start0
121	nop
122	.ascii	"NetBSD20"		/* oemname (8 bytes) */
123
124	. = start + MBR_BPB_OFFSET	/* move to start of BPB */
125					/* (ensures oemname doesn't overflow) */
126
127	. = start + MBR_AFTERBPB	/* skip BPB */
128start0:
129	xor	%ax, %ax		/* don't trust values of ds, es or ss */
130	mov	%ax, %ds
131	mov	%ax, %es
132	mov	%ax, %ss
133	mov	$0xfffc, %sp
134
135	/* A 'reset disk system' request is traditional here... */
136	push	%dx			/* some BIOS zap %dl here :-( */
137	int	$0x13			/* ah == 0 from code above */
138	pop	%dx
139
140	/* Read from start of disk */
141	movw	$0x0001, %cx		/* track zero sector 1 */
142	movb	%ch, %dh		/* dh = head = 0 */
143	call	chs_read
144
145/* See if this is our code, if so we have already loaded the next stage */
146
147	xorl	%ebp, %ebp		/* pass sector 0 to next stage */
148	movl	(%bx), %eax		/* MBR code shouldn't even have ... */
149	cmpl	R(start), %eax		/* ... a jmp at the start. */
150	je	pbr_read_ok1
151
152/* Now scan the MBR partition table for a netbsd partition */
153
154	xorl	%ebx, %ebx		/* for base extended ptn chain */
155scan_ptn_tbl:
156	xorl	%ecx, %ecx		/* for next extended ptn */
157	movw	$BOOTADDR + MBR_PART_OFFSET, %di
1581:	movb	4(%di), %al		/* mbrp_type */
159	movl	8(%di), %ebp		/* mbrp_start == LBA sector */
160	addl	lba_sector, %ebp	/* add base of extended partition */
161#ifdef BOOT_FROM_FAT
162	cmpb	$MBR_PTYPE_FAT12, %al
163	je	5f
164	cmpb	$MBR_PTYPE_FAT16S, %al
165	je	5f
166	cmpb	$MBR_PTYPE_FAT16B, %al
167	je	5f
168	cmpb	$MBR_PTYPE_FAT32, %al
169	je	5f
170	cmpb	$MBR_PTYPE_FAT32L, %al
171	je	5f
172	cmpb	$MBR_PTYPE_FAT16L, %al
173	je	5f
174#else
175	cmpb	$MBR_PTYPE_NETBSD, %al
176#endif
177	jne	10f
1785:	testl	%esi, %esi		/* looking for a specific sector? */
179	je	boot
180	cmpl	%ebp, %esi		/* ptn we wanted? */
181	je	boot
182	/* check for extended partition */
18310:	cmpb	$MBR_PTYPE_EXT, %al
184	je	15f
185	cmpb	$MBR_PTYPE_EXT_LBA, %al
186	je	15f
187	cmpb	$MBR_PTYPE_EXT_LNX, %al
188	jne	20f
18915:	movl	8(%di), %ecx		/* sector of next ext. ptn */
19020:	add	$0x10, %di
191	cmp	$BOOTADDR + MBR_MAGIC_OFFSET, %di
192	jne	1b
193
194	/* not in base partitions, check extended ones */
195	jecxz	no_netbsd_ptn
196	testl	%ebx, %ebx
197	jne	30f
198	xchgl	%ebx, %ecx		/* save base of ext ptn chain */
19930:	addl	%ebx, %ecx		/* address this ptn */
200	movl	%ecx, lba_sector	/* sector to read */
201	call	read_lba
202	jmp	scan_ptn_tbl
203
204no_netbsd_ptn:
205	/* Specific sector not found: try again looking for first NetBSD ptn */
206	testl	%esi, %esi
207	set_err(ERR_PTN)
208	jz	error
209	xorl	%esi, %esi
210	movl	%esi, lba_sector
211	jmp	start
212
213/*
214 * Sector below CHS limit
215 * Do a cylinder-head-sector read instead
216 * I believe the BIOS should do reads that cross track boundaries.
217 * (but the read should start at the beginning of a track...)
218 */
219read_chs:
220	movb	1(%di), %dh			/* head */
221	movw	2(%di), %cx			/* ch=cyl, cl=sect */
222	call	chs_read
223pbr_read_ok1:
224	jmp	pbr_read_ok
225
226/*
227 * Active partition pointed to by di.
228 *
229 * We can either do a CHS (Cylinder Head Sector) or an LBA (Logical
230 * Block Address) read.  Always doing the LBA one
231 * would be nice - unfortunately not all systems support it.
232 * Also some may contain a separate (eg SCSI) BIOS that doesn't
233 * support it even when the main BIOS does.
234 *
235 * The safest thing seems to be to find out whether the sector we
236 * want is inside the CHS sector count.  If it is we use CHS, if
237 * outside we use LBA.
238 *
239 * Actually we check that the CHS values reference the LBA sector,
240 * if not we assume that the LBA sector is above the limit, or that
241 * the geometry used (by fdisk) isn't correct.
242 */
243boot:
244	movl	%ebp, lba_sector	/* to control block */
245	testl	%ebx, %ebx		/* was it an extended ptn? */
246	jnz	boot_lba		/* yes - boot with LBA reads */
247
248/* get CHS values from BIOS */
249	push	%dx				/* save drive number */
250	movb	$8, %ah
251	int	$0x13				/* chs info */
252
253/*
254 * Validate geometry, if the CHS sector number doesn't match the LBA one
255 * we'll do an LBA read.
256 * calc: (cylinder * number_of_heads + head) * number_of_sectors + sector
257 * and compare against LBA sector number.
258 * Take a slight 'flier' and assume we can just check 16bits (very likely
259 * to be true because the number of sectors per track is 63).
260 */
261	movw	2(%di), %ax			/* cylinder + sector */
262	push	%ax				/* save for sector */
263	shr	$6, %al
264	xchgb	%al, %ah			/* 10 bit cylinder number */
265	shr	$8, %dx				/* last head */
266	inc	%dx				/* number of heads */
267	mul	%dx
268	mov	1(%di), %dl			/* head we want */
269	add	%dx, %ax
270	and	$0x3f, %cx			/* number of sectors */
271	mul	%cx
272	pop	%dx				/* recover sector we want */
273	and	$0x3f, %dx
274	add	%dx, %ax
275	dec	%ax
276	pop	%dx				/* recover drive nmber */
277
278	cmp	%bp, %ax
279	je	read_chs
280
281check_lba:
282#ifdef NO_LBA_CHECK
283	jmp	boot_lba
284#else
285/*
286 * Determine whether we have int13-extensions, by calling
287 * int 13, function 41. Check for the magic number returned,
288 * and the disk packet capability.
289 *
290 * This is actually relatively pointless:
291 * 1) we only use LBA reads if CHS ones would fail
292 * 2) the MBR code managed to read the same sectors
293 * 3) the BIOS will (ok should) reject the LBA read as a bad BIOS call
294 */
295	movw	$0x55aa, %bx
296	movb	$0x41, %ah
297	int	$0x13
298	jc	1f				/* no int13 extensions */
299	cmpw	$0xaa55, %bx
300	jnz	1f
301	testb	$1, %cl
302	jnz	boot_lba
3031:	set_err(ERR_NO_LBA)
304#endif	/* NO_LBA_CHECK */
305
306/*
307 * Something went wrong,
308 * Output error code,
309 */
310
311error:
312#ifdef TERSE_ERROR
313	movb	%al, errcod
314	movw	$errtxt, %si
315	call	message
316#else
317	push	%ax
318	movw	$errtxt, %si
319	call	message
320	pop	%si
321	call	message
322	movw	$newline, %si
323	call	message
324#endif
3251:	sti
326	hlt
327	jmp	1b
328
329boot_lba:
330	call	read_lba
331
332/*
333 * Check magic number for valid stage 2 bootcode
334 * then jump into it.
335 */
336pbr_read_ok:
337	cmpl	$X86_BOOT_MAGIC_1, bootxx_magic
338	set_err(ERR_NO_BOOTXX)
339	jnz	error
340
341	movl	%ebp, %esi			/* %esi ptn base, %dl disk id */
342	jmp	$0, $bootxx			/* our %cs may not be zero */
343
344/* Read disk using int13-extension parameter block */
345read_lba:
346	pusha
347	movw	$lba_info, %si			/* ds:si is ctl block */
348	movb	$0x42, %ah
349do_read:
350	int	$0x13
351	popa
352
353	set_err(ERR_READ)
354	jc	error
355	ret
356
357/* Read using CHS */
358
359chs_read:
360	movw	$BOOTADDR, %bx			/* es:bx is buffer */
361	pusha
362	movw	$0x200 + BOOTXX_SECTORS, %ax	/* command 2, xx sectors */
363	jmp	do_read
364
365_errtxt: .ascii	"Error "			/* runs into newline... */
366_errcod: .byte	0				/* ... if errcod set */
367_newline:
368	.asciz	"\r\n"
369
370#ifndef TERSE_ERROR
371ERR_READ:	.asciz	"Disk read"
372ERR_NO_BOOTXX:	.asciz	"Not a bootxx image"
373ERR_PTN:	.asciz	"No NetBSD partition"
374#ifndef NO_LBA_CHECK
375ERR_NO_LBA:	.asciz	"Invalid CHS read"
376#endif
377#endif
378
379/*
380 * I hate #including source files, but pbr_magic below has to be at
381 * the correct absolute address.
382 * Clearly this could be done with a linker script.
383 */
384
385#include <message.S>
386#if 0
387#include <dump_eax.S>
388#endif
389
390/* Control block for int-13 LBA read. */
391_lba_info:
392	.word	0x10				/* control block length */
393	.word	BOOTXX_SECTORS			/* sector count */
394	.word	BOOTADDR			/* offset in segment */
395	.word	0				/* segment */
396_lba_sector:
397	.long	0x0000				/* sector # goes here... */
398	.long	0x0000
399
400/* Drive Serial Number */
401	. = _C_LABEL(start) + MBR_DSN_OFFSET
402	.long	0
403
404/* mbr_bootsel_magic (not used here) */
405	. = _C_LABEL(start) + MBR_BS_MAGIC_OFFSET
406	.word	0
407
408/*
409 * Provide empty MBR partition table.
410 * If this is installed as an MBR, the user can use fdisk(8) to create
411 * the correct partition table ...
412 */
413	. = _C_LABEL(start) + MBR_PART_OFFSET
414_pbr_part0:
415	.byte	0, 0, 0, 0, 0, 0, 0, 0
416	.long	0, 0
417_pbr_part1:
418	.byte	0, 0, 0, 0, 0, 0, 0, 0
419	.long	0, 0
420_pbr_part2:
421	.byte	0, 0, 0, 0, 0, 0, 0, 0
422	.long	0, 0
423_pbr_part3:
424	.byte	0, 0, 0, 0, 0, 0, 0, 0
425	.long	0, 0
426
427/*
428 * The magic comes last
429 */
430	. = _C_LABEL(start) + MBR_MAGIC_OFFSET
431pbr_magic:
432	.word	MBR_MAGIC
433