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