xref: /openbsd/sys/arch/i386/stand/mbr/mbr.S (revision 3cab2bb3)
1/*	$OpenBSD: mbr.S,v 1.23 2012/06/04 16:17:04 mglocker Exp $	*/
2
3/*
4 * Copyright (c) 1997 Michael Shalayeff and Tobias Weingartner
5 * Copyright (c) 2003 Tom Cosgrove <tom.cosgrove@arches-consulting.com>
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 *
17 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
18 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
19 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
20 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
21 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
22 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
23 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
24 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
25 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
26 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
27 * SUCH DAMAGE.
28 *
29 */
30/* Copyright (c) 1996 VaX#n8 (vax@linkdead.paranoia.com)
31 * last edited 9 July 1996
32 * many thanks to Erich Boleyn (erich@uruk.org) for putting up with
33 * all my questions, and for his work on GRUB
34 * You may use this code or fragments thereof in a manner consistent
35 * with the other copyrights as long as you retain my pseudonym and
36 * this copyright notice in the file.
37 */
38
39	.file	"mbr.S"
40
41#include <machine/asm.h>
42#include <assym.h>
43
44/*
45 * Memory layout:
46 *
47 * 0x07C00 -> 0x07DFF	BIOS loads us here	(at  31k)
48 * 0x07E00 -> 0x17BFC	our stack		(to  95k)
49 *
50 * 0x07A00 -> 0x07BFF	we relocate to here	(at  30k5)
51 *
52 * 0x07C00 -> 0x07DFF	we load PBR here	(at  31k)
53 *
54 * The BIOS loads us at physical address 0x07C00.  We use a long jmp to
55 * normalise our address to seg:offset 07C0:0000.  We then relocate to
56 * 0x07A00, seg:offset 07A0:0000.
57 *
58 * We use a long jmp to normalise our address to seg:offset 07A0:0000
59 * We set the stack to start at 07C0:FFFC (grows down on i386)
60 * The partition boot record (PBR) loads /boot at seg:offset 4000:0000
61 */
62#define BOOTSEG		0x7c0	/* segment where we are loaded */
63#define BOOTRELOCSEG	0x7a0	/* segment where we relocate to */
64#define BOOTSTACKOFF	0xfffc	/* stack starts here, grows down */
65#define PARTSZ		16	/* each partition table entry is 16 bytes */
66
67#define CHAR_LBA_READ	'.'
68#define CHAR_CHS_READ	';'
69#define CHAR_SHIFT_SEEN	0x07	/* Use BEL */
70
71#define MBR_FLAGS_FORCE_CHS	0x0001
72
73#ifdef DEBUG
74#define CHAR_S		'S'	/* started */
75#define CHAR_R		'R'	/* relocated */
76#define CHAR_L		'L'	/* looking for bootable partition */
77#define CHAR_B		'B'	/* loading boot */
78#define CHAR_G		'G'	/* jumping to boot */
79
80#define DBGMSG(c)	movb	$c, %al;	call	Lchr
81#else /* !DEBUG */
82#define DBGMSG(c)
83#endif /* !DEBUG */
84
85/* Clobbers %al - maybe more */
86#define	putc(c)		movb	$c, %al;	call	Lchr
87
88/* Clobbers %esi - maybe more */
89#define	puts(s)		movw	$s, %si;	call	Lmessage
90
91
92	.text
93	.code16
94
95	.globl	start
96start:
97	/* Adjust %cs to be right */
98	ljmp 	$BOOTSEG, $1f
991:
100	/* Set up stack */
101	movw	%cs, %ax
102
103	/*
104	 * We don't need to disable and re-enable interrupts around the
105	 * the load of ss and sp.
106	 *
107	 * From 80386 Programmer's Reference Manual:
108	 * "A MOV into SS inhibits all interrupts until after the execution
109	 * of the next instruction (which is presumably a MOV into eSP)"
110	 *
111	 * According to Hamarsoft's 86BUGS list (which is distributed with
112	 * Ralph Brown's Interrupt List), some early 8086/88 processors
113	 * failed to disable interrupts following a load into a segment
114	 * register, but this was fixed with later steppings.
115	 *
116	 * Accordingly, this code will fail on very early 8086/88s, but
117	 * nick@ will just have to live with it.  Others will note that
118	 * we require an 80386 (or compatible) or above processor, anyway.
119	 */
120	/* cli */
121	movw	%ax, %ss
122	movw	$BOOTSTACKOFF, %sp
123	/* sti */			/* XXX not necessary; see above */
124
125	/* Set up data segment */
126	movw	%ax, %ds
127	DBGMSG(CHAR_S)
128
129	/*
130	 * On the PC architecture, the boot record (originally on a floppy
131	 * disk) is loaded at 0000:7C00 (hex) and execution starts at the
132	 * beginning.
133	 *
134	 * When hard disk support was added, a scheme to partition disks into
135	 * four separate partitions was used, to allow multiple operating
136	 * systems to be installed on the one disk.  The boot sectors of the
137	 * operating systems on each partition would of course expect to be
138	 * loaded at 0000:7C00.
139	 *
140	 * The first sector of the hard disk is the master boot record (MBR).
141	 * It is this which defines the partitions and says which one is
142	 * bootable.  Of course, the BIOS loads the MBR at 0000:7C00, the
143	 * same location where the MBR needs to load the partition boot
144	 * record (PBR, called biosboot in OpenBSD).
145	 *
146	 * Therefore, the MBR needs to relocate itself before loading the PBR.
147	 *
148	 * Make it so.
149	 */
150	movw	$BOOTRELOCSEG, %ax
151	movw	%ax, %es
152	xorw	%si, %si
153	xorw	%di, %di
154	movw	$0x200, %cx		/* Bytes in MBR, relocate it all */
155	cld
156	rep
157	movsb
158
159	/* Jump to relocated self */
160	ljmp $BOOTRELOCSEG, $reloc
161reloc:
162	DBGMSG(CHAR_R)
163
164	/* Set up %es and %ds */
165	pushw	%ds
166	popw	%es	/* next boot is at the same place as we were loaded */
167	pushw	%cs
168	popw	%ds	/* and %ds is at the %cs */
169
170#ifdef SERIAL
171	/* Initialize the serial port to 9600 baud, 8N1.
172	 */
173	pushw	%dx
174	xorw	%ax, %ax
175	movb	$0xe3, %ax
176	movw	$SERIAL, %dx
177	int	$0x14
178	popw	%dx
179#endif
180
181	/*
182	 * If the SHIFT key is held down on entry, force CHS read
183	 */
184
185	/*
186	 * BIOS call "INT 0x16 Get Keyboard Shift Flags
187	 *	Call with	%ah = 0x02
188	 *	Return:
189	 *			%al = shift flags
190	 *			%ah - undefined by many BIOSes
191	 */
192	movb	$0x02, %ah
193	int	$0x16
194	testb	$0x3, %al	/* Either shift key down? */
195	jz	no_shift
196
197	putc(CHAR_SHIFT_SEEN)	/* Signal that shift key was seen */
198
199	orb	$MBR_FLAGS_FORCE_CHS, flags
200
201no_shift:
202	/* BIOS passes us drive number in %dl
203	 *
204	 * XXX - This is not always true.  We currently check if %dl
205	 * points to a HD, and if not we complain, and set it to point
206	 * to the first HDD.  Note, this is not 100% correct, since
207	 * there is a possibility that you boot from HD #2, and still
208	 * get (%dl & 0x80) == 0x00, these type of systems will lose.
209	 */
210	testb	$0x80, %dl
211	jnz	drive_ok
212
213	/* MBR on floppy or old BIOS
214	 * Note: MBR (this code) should never be on a floppy.  It does
215	 * not belong there, so %dl should never be 0x00.
216	 *
217	 * Here we simply complain (should we?), and then hardcode the
218	 * boot drive to 0x80.
219	 */
220	puts(efdmbr)
221
222	/* If we are passed bogus data, set it to HD #1
223	 */
224	movb	$0x80, %dl
225
226drive_ok:
227	/* Find the first active partition.
228	 * Note: this should be the only active partition.  We currently
229	 * don't check for that.
230	 */
231	movw	$pt, %si
232
233	movw	$NDOSPART, %cx
234find_active:
235	DBGMSG(CHAR_L)
236	movb	(%si), %al
237
238	cmpb	$DOSACTIVE, %al
239	je	found
240
241	addw	$PARTSZ, %si
242	loop	find_active
243
244	/* No bootable partition */
245no_part:
246	movw	$enoboot, %si
247
248err_stop:
249	call	Lmessage
250
251stay_stopped:
252	sti				/* Ensure Ctl-Alt-Del will work */
253	hlt				/* (don't require power cycle) */
254	/* Just to make sure */
255	jmp	stay_stopped
256
257found:
258	/*
259	 * Found bootable partition
260	 */
261
262	DBGMSG(CHAR_B)
263
264	/* Store the drive number (from %dl) in decimal */
265	movb	%dl, %al
266	andb	$0x0F, %al
267	addb	$'0', %al
268	movb	%al, drive_num
269
270	/*
271	 * Store the partition number, in decimal.
272	 *
273	 * We started with cx = 4; if found we want part '0'
274	 *                 cx = 3;                  part '1'
275	 *                 cx = 2;                  part '2'
276	 *                 cx = 1;                  part '3'
277	 *
278	 * We'll come into this with no other values for cl.
279	 */
280	movb	$'0'+4, %al
281	subb	%cl, %al
282	movb	%al, part_num
283
284	/*
285	 * Tell operator what partition we're trying to boot.
286	 *
287	 * Using drive X, partition Y
288	 * - this used to be printed out after successfully loading the
289	 *   partition boot record; we now print it out before
290	 */
291	pushw	%si
292	movw	$info, %si
293	testb	$MBR_FLAGS_FORCE_CHS, flags
294	jnz	1f
295	incw	%si
2961:
297	call	Lmessage
298	popw	%si
299
300	/*
301	 * Partition table entry format:
302	 *
303	 * 0x00	BYTE boot indicator (0x80 = active, 0x00 = inactive)
304	 * 0x01	BYTE start head
305	 * 0x02	WORD start cylinder, sector
306	 * 0x04	BYTE system type (0xA6 = OpenBSD)
307	 * 0x05 BYTE end head
308	 * 0x06	WORD end cylinder, sector
309	 * 0x08	LONG start LBA sector
310	 * 0x0C	LONG number of sectors in partition
311	 *
312	 * In the case of a partition that extends beyond the 8GB boundary,
313	 * the LBA values will be correct, the CHS values will have their
314	 * maximums (typically (C,H,S) = (1023,255,63)).
315	 *
316	 * %ds:%si points to the active partition table entry.
317	 */
318
319	/* We will load the partition boot sector (biosboot) where we
320	 * were originally loaded.  We'll check to make sure something
321	 * valid comes in.  So that we don't find ourselves, zero out
322	 * the signature at the end.
323	 */
324	movw	$0, %es:signature(,1)
325
326	/*
327	 * Have we been instructed to ignore LBA?
328	 */
329	testb	$MBR_FLAGS_FORCE_CHS, flags
330	jnz	do_chs
331
332	/*
333	 * We will use the LBA sector number if we have LBA support,
334	 * so find out.
335	 */
336
337	/*
338	 * BIOS call "INT 0x13 Extensions Installation Check"
339	 *	Call with	%ah = 0x41
340	 *			%bx = 0x55AA
341	 *			%dl = drive (0x80 for 1st hd, 0x81 for 2nd, etc)
342	 *	Return:
343	 *			carry set: failure
344	 *				%ah = error code (0x01, invalid func)
345	 *			carry clear: success
346	 *				%bx = 0xAA55 (must verify)
347	 *				%ah = major version of extensions
348	 *				%al   (internal use)
349	 *				%cx = capabilities bitmap
350	 *					0x0001 - extnd disk access funcs
351	 *					0x0002 - rem. drive ctrl funcs
352	 *					0x0004 - EDD functions with EBP
353	 *				%dx   (extension version?)
354	 */
355
356	movb	%dl, (%si)		/* Store drive here temporarily */
357					/* (This call trashes %dl) */
358					/*
359					 * XXX This is actually the correct
360					 *     place to store this.  The 0x80
361					 *     value used to indicate the
362					 *     active partition is by intention
363					 *     the same as the BIOS drive value
364					 *     for the first hard disk (0x80).
365					 *     At one point, 0x81 would go here
366					 *     for the second hard disk; the
367					 *     0x80 value is often used as a
368					 *     bit flag for testing, rather
369					 *     than an exact byte value.
370					 */
371	movw	$0x55AA, %bx
372	movb	$0x41, %ah
373	int	$0x13
374
375	movb	(%si), %dl		/* Get back drive number */
376
377	jc	do_chs			/* Did the command work? Jump if not */
378	cmpw	$0xAA55, %bx		/* Check that bl, bh exchanged */
379	jne	do_chs			/* If not, don't have EDD extensions */
380	testb	$0x01, %cl		/* And do we have "read" available? */
381	jz	do_chs			/* Again, use CHS if not */
382
383do_lba:
384	/*
385	 * BIOS call "INT 0x13 Extensions Extended Read"
386	 *	Call with	%ah = 0x42
387	 *			%dl = drive (0x80 for 1st hd, 0x81 for 2nd, etc)
388	 *			%ds:%si = segment:offset of command packet
389	 *	Return:
390	 *			carry set: failure
391	 *				%ah = error code (0x01, invalid func)
392	 *				command packet's sector count field set
393	 *				to the number of sectors successfully
394	 *				transferred
395	 *			carry clear: success
396	 *				%ah = 0 (success)
397	 *	Command Packet:
398	 *			0x0000	BYTE	packet size (0x10 or 0x18)
399	 *			0x0001	BYTE	reserved (should be 0)
400	 *			0x0002	WORD	sectors to transfer (max 127)
401	 *			0x0004	DWORD	seg:offset of transfer buffer
402	 *			0x0008	QWORD	starting sector number
403	 */
404	movb	$CHAR_LBA_READ, %al
405	call	Lchr
406
407	/* Load LBA sector number from active partition table entry */
408	movl	8(%si), %ecx
409	movl	%ecx, lba_sector
410
411	pushw	%si			/* We'll need %si later */
412
413	movb	$0x42, %ah
414	movw	$lba_command, %si
415	int	$0x13
416
417	popw	%si			/* (get back %si) flags unchanged */
418
419	jnc	booting_os		/* If it worked, run the pbr we got */
420
421	/*
422	 * LBA read failed, fall through to try CHS read
423	 */
424
425do_chs:
426	/*
427	 * BIOS call "INT 0x13 Function 0x2" to read sectors from disk into
428	 * memory
429	 *       Call with       %ah = 0x2
430	 *                       %al = number of sectors
431	 *                       %ch = cylinder & 0xFF
432	 *                       %cl = sector (0-63) | rest of cylinder bits
433	 *                       %dh = head
434	 *                       %dl = drive (0x80 for hard disk)
435	 *                       %es:%bx = segment:offset of buffer
436	 *       Return:
437	 *                       carry set: failure
438	 *                           %ah = err code
439	 *                           %al = number of sectors transferred
440	 *                       carry clear: success
441	 *                           %al = 0x0 OR number of sectors transferred
442	 *                                 (depends on BIOS!)
443	 *                                 (according to Ralph Brown Int List)
444	 */
445	movb	$CHAR_CHS_READ, %al
446	call	Lchr
447
448	/* Load values from active partition table entry */
449	movb	1(%si), %dh		/* head */
450	movw	2(%si), %cx		/* sect, cyl */
451	movw	$0x201, %ax		/* function and number of blocks */
452	xorw	%bx, %bx		/* put it at %es:0 */
453	int	$0x13
454	jnc	booting_os
455
456read_error:
457	movw	$eread, %si
458	jmp	err_stop
459
460booting_os:
461	puts(crlf)
462	DBGMSG(CHAR_G)
463
464	/*
465	 * Make sure the pbr we loaded has a valid signature at the end.
466	 * This also ensures that something did load where we were expecting
467	 * it, as there's still a copy of our code there...
468	 */
469	cmpw	$DOSMBR_SIGNATURE, %es:signature(,1)
470	jne	missing_os
471
472	/* jump to the new code (%ds:%si is at the right point) */
473	ljmp	$0, $BOOTSEG << 4
474	/* not reached */
475
476missing_os:
477	movw	$enoos, %si
478	jmp	err_stop
479
480/*
481 * Display string
482 */
483Lmessage:
484	pushw	%ax
485	cld
4861:
487	lodsb			/* %al = *%si++ */
488	testb	%al, %al
489	jz	1f
490	call    Lchr
491	jmp	1b
492
493/*
494 *	Lchr: write the error message in %ds:%si to console
495 */
496Lchr:
497	pushw	%ax
498
499#ifdef SERIAL
500	pushw	%dx
501	movb	$0x01, %ah
502	movw	$SERIAL, %dx
503	int	$0x14
504	popw	%dx
505#else
506	pushw	%bx
507	movb	$0x0e, %ah
508	movw	$1, %bx
509	int	$0x10
510	popw	%bx
511#endif
5121:	popw	%ax
513	ret
514
515/* command packet for LBA read of boot sector */
516lba_command:
517	.byte	0x10			/* size of command packet */
518	.byte	0x00			/* reserved */
519	.word	0x0001			/* sectors to transfer, just 1 */
520	.word	0			/* target buffer, offset */
521	.word	BOOTSEG			/* target buffer, segment */
522lba_sector:
523	.long	0, 0			/* sector number */
524
525/* Info messages */
526info:	.ascii		"!Using drive "
527drive_num:
528	.byte		'X'
529	.ascii		", partition "
530part_num:
531	.asciz		"Y"
532
533/* Error messages */
534efdmbr:	.asciz		"MBR on floppy or old BIOS\r\n"
535eread:	.asciz		"\r\nRead error\r\n"
536enoos:	.asciz		"No O/S\r\n"
537enoboot: .ascii		"No active partition"	/* runs into crlf... */
538crlf:	.asciz		"\r\n"
539
540endofcode:
541	nop
542
543/* We're going to store a flags word here */
544
545	. = 0x1b4
546flags:
547	.word	0x0000
548	.ascii	"Ox"			/* Indicate that the two bytes */
549					/* before us are the flags word */
550
551/* (MBR) NT disk signature offset */
552	. = 0x1b8
553	.space  4, 0
554
555/* partition table */
556/* flag, head, sec, cyl, type, ehead, esect, ecyl, start, len */
557	. = DOSPARTOFF	/* starting address of partition table */
558pt:
559	.byte	0x0,0,0,0,0,0,0,0
560	.long	0,0
561	.byte	0x0,0,0,0,0,0,0,0
562	.long	0,0
563	.byte	0x0,0,0,0,0,0,0,0
564	.long	0,0
565	.byte	DOSACTIVE,0,1,0,DOSPTYP_OPENBSD,255,255,255
566	.long	0,0x7FFFFFFF
567/* the last 2 bytes in the sector 0 contain the signature */
568	. = 0x1fe
569signature:
570	.short	DOSMBR_SIGNATURE
571	. = 0x200
572