1/*	$OpenBSD: biosboot.S,v 1.13 2023/05/30 08:30:00 jsg Exp $	*/
2
3/*
4 * Copyright (c) 2003 Tobias Weingartner
5 * Copyright (c) 2003 Tom Cosgrove <tom.cosgrove@arches-consulting.com>
6 * Copyright (c) 1997 Michael Shalayeff, Tobias Weingartner
7 * All rights reserved.
8 *
9 * Redistribution and use in source and binary forms, with or without
10 * modification, are permitted provided that the following conditions
11 * are met:
12 * 1. Redistributions of source code must retain the above copyright
13 *    notice, this list of conditions and the following disclaimer.
14 * 2. Redistributions in binary form must reproduce the above copyright
15 *    notice, this list of conditions and the following disclaimer in the
16 *    documentation and/or other materials provided with the distribution.
17 *
18 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
19 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
20 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
21 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
22 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
23 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
24 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
25 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
26 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
27 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
28 * SUCH DAMAGE.
29 *
30 */
31	.file	"biosboot.S"
32
33#include <machine/asm.h>
34#include <assym.h>
35
36/* Error indicators */
37#define PBR_READ_ERROR			'R'
38#define PBR_CANT_BOOT			'X'
39#define PBR_BAD_MAGIC			'M'
40#define PBR_TOO_MANY_INDIRECTS		'I'
41
42#define CHAR_BLOCK_READ		'.'
43#define CHAR_CHS_READ		';'
44
45/*
46 * Memory layout:
47 *
48 * 0x00000 -> 0x07BFF	our stack		(to  31k)
49 * 0x07A00 -> 0x07BFF	typical MBR loc		(at  30k5)
50 * 0x07C00 -> 0x07DFF	our code		(at  31k)
51 * 0x07E00 -> ...    	/boot inode block	(at  31k5)
52 * 0x07E00 -> ...    	(indirect block if nec)
53 * 0x40000 -> ...	/boot			(at 256k)
54 *
55 * The BIOS loads the MBR at physical address 0x07C00.  It then relocates
56 * itself to (typically) 0x07A00.
57 *
58 * The MBR then loads us at physical address 0x07C00.
59 *
60 * We use a long jmp to normalise our address to seg:offset 07C0:0000.
61 * (In real mode on x86, segment registers contain a base address in
62 * paragraphs (16 bytes).  0000:00010 is the same as 0001:0000.)
63 *
64 * We set the stack to start at 0000:7BFC (grows down on i386)
65 *
66 * We then read the inode for /boot into memory just above us at
67 * 07E0:0000, and run through the direct block table (and the first
68 * indirect block table, if necessary).
69 *
70 * We load /boot at seg:offset 4000:0000.
71 *
72 * Previous versions limited the size of /boot to 64k (loaded in a single
73 * segment).  This version does not have this limitation.
74 */
75#define INODESEG	0x07e0	/* where we put /boot's inode's block */
76#define INDIRECTSEG	0x07e0	/* where we put indirect table, if nec */
77#define BOOTSEG		0x07c0	/* biosboot loaded here */
78#define BOOTSTACKOFF  ((BOOTSEG << 4) - 4)  /* stack starts here, grows down */
79#define LFMAGIC		0x464c  /* LFMAGIC (last two bytes of \7fELF) */
80#define ELFMAGIC    0x464c457f  /* ELFMAGIC ("\7fELF") */
81
82#define INODEOFF  ((INODESEG-BOOTSEG) << 4)
83
84/*
85 * The data passed by installboot is:
86 *
87 * inodeblk	uint32	the filesystem block that holds /boot's inode
88 * inodedbl	uint32	the memory offset to the beginning of the
89 *			direct block list (di_db[]).  (This is the
90 *			offset within the block + $INODEOFF, which is
91 *			where we load the block to.)
92 * fs_bsize_p	uint16	the filesystem block size _in paragraphs_
93 *			(i.e. fs_bsize / 16)
94 * fs_bsize_s	uint16	the number of disk sectors in a filesystem
95 *			block (i.e. fs_bsize / d_secsize). Directly written
96 *			into the LBA command block, at lba_count.
97 *			XXX LIMITED TO 127 BY PHOENIX EDD SPEC.
98 * fsbtodb	uint8	shift count to convert filesystem blocks to
99 *			disk blocks (sectors).  Note that this is NOT
100 *			log2 fs_bsize, since fragmentation allows
101 *			the trailing part of a file to use part of a
102 *			filesystem block.  In other words, filesystem
103 *			block numbers can point into the middle of
104 *			filesystem blocks.
105 * p_offset	uint32	the starting disk block (sector) of the
106 *			filesystem
107 * nblocks	uint16	the number of filesystem blocks to read.
108 *			While this can be calculated as
109 *			howmany(di_size, fs_bsize) it takes us too
110 *			many code bytes to do it.
111 * blkincr	uint8	the increment used to parse di_db[]. set to four by
112 *			installboot for ffs2 (due to 64-bit blocks) and should
113 *			be zero for ffs1.
114 *
115 * All of these are patched directly into the code where they are used
116 * (once only, each), to save space.
117 */
118
119	.globl	inodeblk, inodedbl, fs_bsize_p, fsbtodb, p_offset, nblocks
120	.globl	fs_bsize_s, blkincr
121	.type	inodeblk, @function
122	.type	inodedbl, @function
123	.type	fs_bsize_p, @function
124	.type	fs_bsize_s, @function
125	.type	fsbtodb, @function
126	.type	p_offset, @function
127	.type	nblocks, @function
128	.type	blkincr, @function
129
130
131/* Clobbers %ax, maybe more */
132#define	putc(c)		movb	$c, %al;	call	Lchr
133
134/* Clobbers %ax, %si, maybe more */
135#define	puts(s)		movw	$s, %si;	call	Lmessage
136
137
138	.text
139	.code16
140	.globl	_start
141_start:
142	jmp	begin
143	nop
144
145	/*
146	 * BIOS Parameter Block.  Read by many disk utilities.
147	 *
148	 * We would have liked biosboot to go from the superblock to
149	 * the root directory to the inode for /boot, thence to read
150	 * its blocks into memory.
151	 *
152	 * As code and data space is quite tight in the 512-byte
153	 * partition boot sector, we instead get installboot to pass
154	 * us some pre-processed fields.
155	 *
156	 * We would have liked to put these in the BIOS parameter block,
157	 * as that seems to be the right place to put them (it's really
158	 * the equivalent of the superblock for FAT filesystems), but
159	 * caution prevents us.
160	 *
161	 * For now, these fields are either directly in the code (when they
162	 * are used once only) or at the end of this sector.
163	 */
164
165	. = _start + 3
166
167	.asciz	"OpenBSD"
168
169	/* BPB */
170	. = _start + 0x0b
171bpb:	.word	DEV_BSIZE			/* sector size */
172	.byte	2				/* sectors/cluster */
173	.word	0				/* reserved sectors */
174	.byte	0				/* # of FAT */
175	.word	0				/* root entries */
176	.word	0				/* small sectors */
177	.byte	0xf8				/* media type (hd) */
178	.word	0				/* sectors/fat */
179	.word	0				/* sectors per track */
180	.word	0				/* # of heads */
181
182	/* EBPB */
183	. = _start + 0x1c
184ebpb:	.long	16			/* hidden sectors */
185	.long	0			/* large sectors */
186	.word	0			/* physical disk */
187	.byte	0x29			/* signature, needed by NT */
188	.space	4, 0			/* volume serial number */
189	.asciz	"UNIX LABEL"
190	.asciz	"UFS 4.4"
191
192	/* boot code */
193	. = _start + 0x3e
194
195begin:
196	/* Fix up %cs just in case */
197	ljmp	$BOOTSEG, $main
198
199	/*
200	 * Come here if we have to do a CHS boot, but we get an error from
201	 * BIOS get drive parameters, or it returns nsectors == 0 (in which
202	 * case we can't do the division we need to convert LBA sector
203	 * number to CHS).
204	 */
205cant_boot:
206	movb	$PBR_CANT_BOOT, %al
207	jmp	err_print_crlf
208
209main:
210	/* Set up stack */
211	xorw	%ax, %ax
212	movw	%ax, %ss
213	movw	$BOOTSTACKOFF, %sp
214
215	/* Set up needed data segment reg */
216	pushw	%cs
217	popw	%ds			/* Now %cs == %ds, != %ss (%ss == 0) */
218
219#ifdef SERIAL
220	/* Initialize the serial port to 9600 baud, 8N1 */
221	push	%dx
222	movw	$0x00e3, %ax
223	movw	SERIAL, %dx
224	int	$0x14
225	pop	%dx
226#endif
227
228#ifdef BDEBUG
229	putc('R')
230#endif
231
232	/*
233	 * We're going to print our sign-on message.
234	 *
235	 * We're now LBA-aware, and will use LBA to load /boot if
236	 * it's available.
237	 */
238	movw	$load_msg, %si	/* "Loading" */
239	call	Lmessage /* Print pretty message */
240
241	/*
242	 * We will use LBA reads if we have LBA support, but don't even try
243	 * on floppies.
244	 */
245	testb	$0x80, %dl
246	jz	no_lba
247
248	/*
249	 * BIOS call "INT 0x13 Extensions Installation Check"
250	 *	Call with	%ah = 0x41
251	 *			%bx = 0x55AA
252	 *			%dl = drive (0x80 for 1st hd, 0x81 for 2nd, etc)
253	 *	Return:
254	 *			carry set: failure
255	 *				%ah = error code (0x01, invalid func)
256	 *			carry clear: success
257	 *				%bx = 0xAA55 (must verify)
258	 *				%ah = major version of extensions
259	 *				%al   (internal use)
260	 *				%cx = capabilities bitmap
261	 *					0x0001 - extnd disk access funcs
262	 *					0x0002 - rem. drive ctrl funcs
263	 *					0x0004 - EDD functions with EBP
264	 *				%dx   (extension version?)
265	 */
266
267	pushw	%dx			/* Save the drive number (%dl) */
268	movw	$0x55AA, %bx
269	movb	$0x41, %ah
270	int	$0x13
271	popw	%dx			/* Retrieve drive number */
272
273	jc	no_lba			/* Did the command work? Jump if not */
274	cmpw	$0xAA55, %bx		/* Check that bl, bh exchanged */
275	jne	no_lba			/* If not, don't have EDD extensions */
276	testb	$0x01, %cl		/* And do we have "read" available? */
277	jz	no_lba			/* Again, use CHS if not */
278
279	/* We have LBA support, so that's the vector to use */
280
281	movw	$load_lba, load_fsblock
282	jmp	get_going
283
284no_lba:
285	pushw	%dx
286
287	/*
288	 * BIOS call "INT 0x13 Function 0x08" to get drive parameters
289	 *	Call with        %ah = 0x08
290	 *                       %dl = drive (0x80 for 1st hd, 0x81 for 2nd...)
291	 *       Return:
292	 *                       carry set: failure
293	 *                           %ah = err code
294	 *                       carry clear: success
295	 *                           %ah = 0x00
296	 *                           %al = 0x00 (some BIOSes)
297	 *                           %ch = 0x00 (some BIOSes)
298	 *                           %ch = max-cylinder & 0xFF
299	 *                           %cl = max sector | rest of max-cyl bits
300	 *                           %dh = max head number
301	 *                           %dl = number of drives
302	 *                                 (according to Ralph Brown Int List)
303	 */
304	movb	$0x08, %ah
305	int	$0x13			/* We need to know heads & sectors */
306
307	jc	cant_boot		/* If error, can't boot */
308
309	movb	%dh, maxheads		/* Remember this */
310
311	andb	$0x3F, %cl
312	jz	cant_boot
313	movb	%cl, nsectors
314
315	putc(CHAR_CHS_READ)		/* Indicate (subtly) CHS reads */
316
317	popw	%dx			/* Retrieve the drive number */
318
319get_going:
320	/*
321	 * Older versions of biosboot used to set up the destination
322	 * segment, and increase the target offset every time a number
323	 * of blocks was read.  That limits /boot to 64k.
324	 *
325	 * In order to support /boots > 64k, we always read to offset
326	 * 0000 in the target segment, and just increase the target segment
327	 * each time.
328	 */
329
330	/*
331	 * We would do movl inodeblk, %eax  here, but that instruction
332	 * is 4 bytes long; add 4 bytes for data takes 8 bytes.  Using
333	 * a load immediate takes 6 bytes, and we just get installboot
334	 * to patch here, rather than data anywhere else.
335	 */
336inodeblk = .+2
337	movl	$0x90909090, %eax	/* mov $inodeblk, %eax */
338
339	movw	$INODESEG, %bx		/* Where to put /boot's inode */
340
341	/*
342	 * %eax - filesystem block to read
343	 * %bx  - target segment (target offset is 0000)
344	 * %dl  - BIOS drive number
345	 */
346	call	*load_fsblock		/* This will crash'n'burn on errs */
347
348	/*
349	 * We now have /boot's inode in memory.
350	 *
351	 * /usr/include/ufs/ufs/dinode.h for the details:
352	 *
353	 * Offset  8 (decimal): 64-bit file size (only use low 32 bits)
354	 * Offset 40 (decimal): list of NDADDR (12) direct disk blocks
355	 * Offset 88 (decimal): list of NIADDR (3) indirect disk blocks
356	 *
357	 * NOTE: list of indirect blocks immediately follows list of
358	 * direct blocks.  We use this fact in the code.
359	 *
360	 * We only support loading from direct blocks plus the first
361	 * indirect block.  This is the same as the previous biosboot/
362	 * installboot limit.  Note that, with default 16,384-bytes
363	 * filesystem blocks, the direct block list supports files up
364	 * to 192 KB.  /boot is currently around 60 KB.
365	 *
366	 * The on-disk format can't change (filesystems with this format
367	 * already exist) so okay to hardcode offsets here.
368	 *
369	 * The nice thing about doing things with filesystem blocks
370	 * rather than sectors is that filesystem blocks numbers have
371	 * 32 bits, so fit into a single register (even if "e"d).
372	 *
373	 * Note that this code does need updating if booting from a new
374	 * filesystem is required.
375	 */
376#define NDADDR	12
377#define di_db	40			/* Not used; addr put in by instboot */
378#define di_ib	88			/* Not used; run on from direct blks */
379
380	/*
381	 * Register usage:
382	 *
383	 * %eax - block number for load_fsblock
384	 * %bx  - target segment (target offset is 0000) for load_fsblock
385	 * %dl  - BIOS drive number for load_fsblock
386	 * %esi - points to block table in inode/indirect block
387	 * %cx  - number of blocks to load within loop (i.e. from current
388	 *	  block list, which is either the direct block list di_db[]
389	 *	  or the indirect block list)
390	 * %di  - total number of blocks to load
391	 */
392
393	/*
394	 * We would do movl inodedbl, %esi  here, but that instruction
395	 * is 4 bytes long; add 4 bytes for data takes 8 bytes.  Using
396	 * a load immediate takes 6 bytes, and we just get installboot
397	 * to patch here, rather than in data anywhere else.
398	 */
399inodedbl = .+2
400	movl	$0x90909090, %esi	/* mov $inodedbl, %esi */
401					/* Now esi -> di_db[] */
402
403nblocks = .+1
404	movw	$0x9090, %di		/* mov nblocks, %di */
405	movw	%di, %cx
406	cmpw	$NDADDR, %cx
407	jc	1f
408	movw	$NDADDR, %cx
4091:					/* %cx = min(nblocks, $NADDR) */
410
411	movw	$(LOADADDR >> 4), %bx	/* Target segment for /boot */
412
413load_blocks:
414	putc(CHAR_BLOCK_READ)		/* Show progress indicator */
415
416	cld
417
418	/* Get the next filesystem block number into %eax */
419	lodsl			/* %eax = *(%si++), make sure 0x66 0xad */
420
421	/*
422	 * The addw could be a 3 byte instruction, but stick to a 4 byte
423	 * one since the former introduces mysterious hangs on *some*
424	 * BIOS implementations, possibly alignment related.
425	 * Grand prize for somebody finding the root cause!
426	 */
427blkincr = .+2
428	addw	$0x90, %si	/* adjust %si if needed (for ffs2) */
429
430	pushal				/* Save all 32-bit registers */
431
432	/*
433	 * Read a single filesystem block (will almost certainly be multiple
434	 * disk sectors)
435	 *
436	 * %eax - filesystem block to read
437	 * %bx  - target segment (target offset is 0000)
438	 * %dl  - BIOS drive number
439	 */
440	call	*load_fsblock		/* This will crash'n'burn on errs */
441
442	popal				/* Restore 32-bit registers */
443
444	/*
445	 * We want to put addw fs_bsize_p, %bx, which takes 4 bytes
446	 * of code and two bytes of data.
447	 *
448	 * Instead, use an immediate load, and have installboot patch
449	 * here directly.
450	 */
451	/* Move on one filesystem block */
452fs_bsize_p = .+2
453	addw	$0x9090, %bx		/* addw $fs_bsize_p, %bx */
454
455	decw	%di
456	loop	load_blocks
457
458	/* %cx == 0 ... important it stays this way (used later) */
459
460	/*
461	 * Finished reading a set of blocks.
462	 *
463	 * This was either the direct blocks, and there may or may not
464	 * be indirect blocks to read, or it was the indirect blocks,
465	 * and we may or may not have read in all of /boot.  (Ideally
466	 * will have read in all of /boot.)
467	 */
468	orw	%di, %di
469	jz	done_load		/* No more sectors to read */
470
471	/* We have more blocks to load */
472
473	/* We only support a single indirect block (the same as previous
474	 * versions of installboot.  This is required for the boot floppies.
475	 *
476	 * We use a bit of the code to store a flag that indicates
477	 * whether we have read the first indirect block or not.
478	 *
479	 * If we've already read the indirect list, we can't load this /boot.
480	 *
481	 * indirect	uint8	0 => running through load_blocks loop reading
482	 *			direct blocks.  If != 0, we're reading the
483	 *			indirect blocks.  Must use a field that is
484	 *			initialised to 0.
485	 */
486indirect = .+2
487	movw	$PBR_TOO_MANY_INDIRECTS, %ax	/* movb $PRB_TOO..., %al */
488						/* movb indirect, %ah */
489	orb	%ah, %ah
490	jnz	err_print_crlf
491
492	incb	indirect		/* No need to worry about wrap */
493					/* around, as this will only be done */
494					/* once before we fail */
495
496	/* Okay, let's read in the indirect block */
497
498	lodsl				/* Get blk num of 1st indirect blk */
499
500	pushw	%bx			/* Remember where we got to */
501	movw	$INODESEG, %bx
502	call	*load_fsblock		/* This will crash'n'burn on errs */
503	popw	%bx			/* Indirect blocks get added on to */
504					/* just after where we got to */
505	movl	$INODEOFF, %esi
506	movw	%di, %cx		/* How many blocks left to read */
507
508	jmp	load_blocks
509
510done_load:
511	puts(crlf)
512
513	/* %cx == 0 from loop above... keep it that way */
514
515	/*
516	 * Check the magic signature at the beginning of /boot.
517	 * Since /boot is now ELF, this should be 0x7F E L F.
518	 */
519	movw	$(LOADADDR >> 4), %ax	/* Target segment */
520	movw	%ax, %es
521
522	/*
523	 * We cheat a little here, and only check the L and F.
524	 *
525	 * (Saves 3 bytes of code... the two signature bytes we
526	 * don't check, and the operand size prefix that's not
527	 * needed.)
528	 */
529	cmpw	$LFMAGIC, %es:2(,1)
530	je	exec_boot
531
532	movb	$PBR_BAD_MAGIC, %al
533
534err_print:
535	movw	$err_txt, %si
536err_print2:
537	movb	%al, err_id
538err_stop:
539	call	Lmessage
540stay_stopped:
541	sti				/* Ensure Ctl-Alt-Del will work */
542	hlt				/* (don't require power cycle) */
543	jmp	stay_stopped		/* Just to make sure :-) */
544
545exec_boot:
546	/* At this point we could try to use the entry point in
547	 * the image we just loaded.  But if we do that, we also
548	 * have to potentially support loading that image where it
549	 * is supposed to go.  Screw it, just assume that the image
550	 * is sane.
551	 */
552#ifdef BDEBUG
553	putc('P')
554#endif
555
556	/* %cx == 0 from loop above... keep it that way */
557
558	/*
559	 * We want to do movzbl %dl, %eax ; pushl %eax to zero-extend the
560	 * drive number to 32 bits and pass it to /boot.  However, this
561	 * takes 6 bytes.
562	 *
563	 * Doing it this way saves 2 bytes.
564	 */
565	pushw	%cx
566	movb	%dl, %cl
567	pushw	%cx
568
569	pushl	$BOOTMAGIC	/* use some magic */
570
571	/* jmp	/boot */
572	ljmp $(LINKADDR >> 4), $0
573	/* not reached */
574
575
576/*
577 * Load a single filesystem block into memory using CHS calls.
578 *
579 * Input:	%eax - 32-bit filesystem block number
580 * 		%bx  - target segment (target offset is 0000)
581 * 		%dl  - BIOS drive number
582 *
583 * Output:	block successfully read in (panics if not)
584 *		all general purpose registers may have been trashed
585 */
586load_chs:
587	/*
588	 * BIOS call "INT 0x13 Function 0x2" to read sectors from disk into
589	 * memory.
590	 *	Call with        %ah = 0x42
591	 *                       %ah = 0x2
592	 *                       %al = number of sectors
593	 *                       %ch = cylinder & 0xFF
594	 *                       %cl = sector (0-63) | rest of cylinder bits
595	 *                       %dh = head
596	 *                       %dl = drive (0x80 for 1st hd, 0x81 for 2nd...)
597	 *                       %es:%bx = segment:offset of buffer
598	 *       Return:
599	 *                       carry set: failure
600	 *                           %ah = err code
601	 *                           %al = number of sectors transferred
602	 *                       carry clear: success
603	 *                           %al = 0x0 OR number of sectors transferred
604	 *                                 (depends on BIOS!)
605	 *                                 (according to Ralph Brown Int List)
606	 */
607
608	/* Convert the filesystem block into a sector value */
609	call	fsbtosector
610	movl	lba_sector, %eax	/* we can only use 24 bits, really */
611
612	movw	fs_bsize_s, %cx	/* sectors per filesystem block */
613
614	/*
615	 * Some BIOSes require that reads don't cross track boundaries.
616	 * Therefore we do all CHS reads single-sector.
617	 */
618calc_chs:
619	pushal
620	movw	%bx, %es	/* Set up target segment */
621
622	pushw	%dx		/* Save drive number (in %dl) */
623	xorl	%edx, %edx
624	movl	%edx, %ecx
625
626nsectors = .+1
627	movb	$0x90, %cl	/* movb $nsectors, %cl */
628				/* Doing it this way saves 4-2 = 2 bytes code */
629				/* bytes (no data, since we would overload) */
630
631	divl	%ecx, %eax
632				/* Now have sector number in %dl */
633	pushw	%dx		/* Remember for later */
634
635	xorl	%edx, %edx
636
637maxheads = .+1
638	movb	$0x90, %cl	/* movb $maxheads, %cl; 0 <= maxheads <= 255 */
639				/* Doing it this way saves 4-2 = 2 code */
640				/* bytes (no data, since we would overload */
641
642	incw	%cx		/* Number of heads is 1..256, no "/0" worries */
643
644	divl	%ecx, %eax
645				/* Have head number in %dl */
646				/* Cylinder number in %ax */
647	movb	%al, %ch	/* Bottom 8 bits of cyl number */
648	shlb	$6, %ah		/* Move up top 2 bits of cyl number */
649	movb	%ah, %cl	/* Top 2 bits of cyl number in here */
650
651	popw	%bx		/* (pushed %dx, but need %dl for now */
652	incb	%bl		/* Sector numbers run from 1, not 0 */
653	orb	%bl, %cl	/* Or the sector number into top bits cyl */
654
655				/* Remember, %dl has head number */
656	popw	%ax
657				/* %al has BIOS drive number -> %dl */
658
659	movb	%dl, %dh	/* Now %dh has head number (from 0) */
660	movb	%al, %dl	/* Now %dl has BIOS drive number */
661
662	xorw	%bx, %bx	/* Set up target offset */
663
664	movw	$0x0201, %ax	/* %al = 1 - read one sector at a time */
665				/* %ah = 2 - int 0x13 function for CHS read */
666
667	call	do_int_13	/* saves us 1 byte :-) */
668
669	/* Get the next sector */
670
671	popal
672	incl	%eax
673	addw	$32, %bx	/* Number of segments/paras in a sector */
674	loop	calc_chs
675
676	ret
677
678	/* read error */
679read_error:
680	movb	$PBR_READ_ERROR, %al
681err_print_crlf:
682	movw	$err_txt_crlf, %si
683	jmp	err_print2
684
685
686/*
687 * Load a single filesystem block into memory using LBA calls.
688 *
689 * Input:	%eax - 32-bit filesystem block number
690 * 		%bx  - target segment (target offset is 0000)
691 * 		%dl  - BIOS drive number
692 *
693 * Output:	block successfully read in (panics if not)
694 *		all general purpose registers may have been trashed
695 */
696load_lba:
697	/*
698	 * BIOS call "INT 0x13 Extensions Extended Read"
699	 *	Call with	%ah = 0x42
700	 *			%dl = drive (0x80 for 1st hd, 0x81 for 2nd, etc)
701	 *			%ds:%si = segment:offset of command packet
702	 *	Return:
703	 *			carry set: failure
704	 *				%ah = error code (0x01, invalid func)
705	 *				command packet's sector count field set
706	 *				to the number of sectors successfully
707	 *				transferred
708	 *			carry clear: success
709	 *				%ah = 0 (success)
710	 *	Command Packet:
711	 *			0x0000	BYTE	packet size (0x10 or 0x18)
712	 *			0x0001	BYTE	reserved (should be 0)
713	 *			0x0002	WORD	sectors to transfer (max 127)
714	 *			0x0004	DWORD	seg:offset of transfer buffer
715	 *			0x0008	QWORD	starting sector number
716	 */
717	call	fsbtosector		/* Set up lba_sector & lba_sector+4 */
718
719	/* movb	%dh, lba_count		<- XXX done by installboot */
720	movw	%bx, lba_seg
721	movw	$lba_command, %si
722	movb	$0x42, %ah
723do_int_13:
724	int	$0x13
725	jc	read_error
726
727	ret
728
729
730/*
731 * Converts a given filesystem block number into a disk sector
732 * at lba_sector and lba_sector+4.
733 *
734 * Input:	%eax - 32-bit filesystem block number
735 *
736 * Output:	lba_sector and lba_sector+4 set up
737 *		XXX
738 */
739fsbtosector:
740	/*
741	 * We want to do
742	 *
743	 * movb	fsbtodb, %ch		/# Shift counts we'll need #/
744	 * movb	$32, %cl
745	 *
746	 * which is 6 bytes of code + 1 byte of data.
747	 *
748	 * We'll actually code it with an immediate 16-bit load into %cx,
749	 * which is just 3 bytes of data (saves 4 bytes).
750	 */
751fsbtodb = .+2
752	movw	$0x9020, %cx		/* %ch = fsbtodb, %cl = 0x20 */
753
754	pushl	%eax
755	subb	%ch, %cl
756	shrl	%cl, %eax
757	movl	%eax, lba_sector+4
758	popl	%eax
759
760	movb	%ch, %cl
761	shll	%cl, %eax
762
763	/*
764	 * And add p_offset, which is the block offset to the start
765	 * of the filesystem.
766	 *
767	 * We would do addl p_offset, %eax, which is 5 bytes of code
768	 * and 4 bytes of data, but it's more efficient to have
769	 * installboot patch directly in the code (this variable is
770	 * only used here) for 6 bytes of code (but no data).
771	 */
772p_offset = .+2
773	addl	$0x90909090, %eax	/* addl $p_offset, %eax */
774
775	movl	%eax, lba_sector
776	jnc	1f
777
778	incl	lba_sector+4
7791:
780	ret
781
782
783/*
784 * Display string
785 */
786Lmessage:
787	cld
7881:
789	lodsb			/* load a byte into %al */
790	orb	%al, %al
791	jz	1f
792	call	Lchr
793	jmp	1b
794
795/*
796 *	Lchr: write the character in %al to console
797 */
798Lchr:
799#ifdef SERIAL
800	pushw	%dx
801	movb	$0x01, %ah
802	xorw	%dx, %dx
803	movb	SERIAL, %dl
804	int	$0x14
805	popw	%dx
806#else
807	pushw	%bx
808	movb	$0x0e, %ah
809	xorw	%bx, %bx
810	incw	%bx		/* movw $0x01, %bx */
811	int	$0x10
812	popw	%bx
813#endif
8141:
815	ret
816
817	/* .data */
818
819/* vector to the routine to read a particular filesystem block for us */
820load_fsblock:
821	.word	load_chs
822
823
824/* This next block is used for the EDD command packet used to read /boot
825 * sectors.
826 *
827 * lba_count is set up for us by installboot.  It is the number of sectors
828 * in a filesystem block.  (Max value 127.)
829 *
830 * XXX The EDD limit of 127 sectors in one read means that we currently
831 *     restrict filesystem blocks to 127 sectors, or < 64 KB.  That is
832 *     effectively a 32 KB block limit, as filesystem block sizes are
833 *     powers of two.  The default filesystem block size is 16 KB.
834 *
835 *     I say we run with this limitation and see where it bites us...
836 */
837
838lba_command:
839	.byte	0x10			/* size of command packet */
840	.byte	0x00			/* reserved */
841fs_bsize_s:
842lba_count:
843	.word	0			/* sectors to transfer, max 127 */
844	.word	0			/* target buffer, offset */
845lba_seg:
846	.word	0			/* target buffer, segment */
847lba_sector:
848	.long	0, 0			/* sector number */
849
850load_msg:
851	.asciz	"Loading"
852err_txt_crlf:
853	.ascii	"\r\n"
854err_txt:
855	.ascii	"ERR "
856err_id:
857	.ascii	"?"
858crlf:	.asciz	"\r\n"
859
860	. = 0x200 - 2
861	/* a little signature */
862	.word	DOSMBR_SIGNATURE
863