xref: /openbsd/sys/arch/amd64/stand/biosboot/biosboot.S (revision 09467b48)
1/*	$OpenBSD: biosboot.S,v 1.10 2020/03/09 06:16:56 otto 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 * One more symbol is exported, in anticipation of a "-c" flag in
119 * installboot to force CHS reads:
120 *
121 * force_chs	uint8	set to the value 1 to force biosboot to use CHS
122 *			reads (this will of course cause the boot sequence
123 *			to fail if /boot is above 8 GB).
124 */
125
126	.globl	inodeblk, inodedbl, fs_bsize_p, fsbtodb, p_offset, nblocks
127	.globl	fs_bsize_s, force_chs, blkincr
128	.type	inodeblk, @function
129	.type	inodedbl, @function
130	.type	fs_bsize_p, @function
131	.type	fs_bsize_s, @function
132	.type	fsbtodb, @function
133	.type	p_offset, @function
134	.type	nblocks, @function
135	.type	force_chs, @function
136	.type	blkincr, @function
137
138
139/* Clobbers %ax, maybe more */
140#define	putc(c)		movb	$c, %al;	call	Lchr
141
142/* Clobbers %ax, %si, maybe more */
143#define	puts(s)		movw	$s, %si;	call	Lmessage
144
145
146	.text
147	.code16
148	.globl	_start
149_start:
150	jmp	begin
151	nop
152
153	/*
154	 * BIOS Parameter Block.  Read by many disk utilities.
155	 *
156	 * We would have liked biosboot to go from the superblock to
157	 * the root directory to the inode for /boot, thence to read
158	 * its blocks into memory.
159	 *
160	 * As code and data space is quite tight in the 512-byte
161	 * partition boot sector, we instead get installboot to pass
162	 * us some pre-processed fields.
163	 *
164	 * We would have liked to put these in the BIOS parameter block,
165	 * as that seems to be the right place to put them (it's really
166	 * the equivalent of the superblock for FAT filesystems), but
167	 * caution prevents us.
168	 *
169	 * For now, these fields are either directly in the code (when they
170	 * are used once only) or at the end of this sector.
171	 */
172
173	. = _start + 3
174
175	.asciz	"OpenBSD"
176
177	/* BPB */
178	. = _start + 0x0b
179bpb:	.word	DEV_BSIZE			/* sector size */
180	.byte	2				/* sectors/cluster */
181	.word	0				/* reserved sectors */
182	.byte	0				/* # of FAT */
183	.word	0				/* root entries */
184	.word	0				/* small sectors */
185	.byte	0xf8				/* media type (hd) */
186	.word	0				/* sectors/fat */
187	.word	0				/* sectors per track */
188	.word	0				/* # of heads */
189
190	/* EBPB */
191	. = _start + 0x1c
192ebpb:	.long	16			/* hidden sectors */
193	.long	0			/* large sectors */
194	.word	0			/* physical disk */
195	.byte	0x29			/* signature, needed by NT */
196	.space	4, 0			/* volume serial number */
197	.asciz	"UNIX LABEL"
198	.asciz	"UFS 4.4"
199
200	/* boot code */
201	. = _start + 0x3e
202
203begin:
204	/* Fix up %cs just in case */
205	ljmp	$BOOTSEG, $main
206
207	/*
208	 * Come here if we have to do a CHS boot, but we get an error from
209	 * BIOS get drive parameters, or it returns nsectors == 0 (in which
210	 * case we can't do the division we need to convert LBA sector
211	 * number to CHS).
212	 */
213cant_boot:
214	movb	$PBR_CANT_BOOT, %al
215	jmp	err_print_crlf
216
217main:
218	/* Set up stack */
219	xorw	%ax, %ax
220	movw	%ax, %ss
221	movw	$BOOTSTACKOFF, %sp
222
223	/* Set up needed data segment reg */
224	pushw	%cs
225	popw	%ds			/* Now %cs == %ds, != %ss (%ss == 0) */
226
227#ifdef SERIAL
228	/* Initialize the serial port to 9600 baud, 8N1 */
229	push	%dx
230	movw	$0x00e3, %ax
231	movw	SERIAL, %dx
232	int	$0x14
233	pop	%dx
234#endif
235
236#ifdef BDEBUG
237	putc('R')
238#endif
239
240	/*
241	 * We're going to print our sign-on message.
242	 *
243	 * We're now LBA-aware, and will use LBA to load /boot if the
244	 * BIOS says it's available.  However, we have seen machines
245	 * where CHS is required even when LBA is available.  Therefore
246	 * we provide a way to force CHS use:
247	 *
248	 * If the SHIFT key is held down on entry, force CHS reads.
249	 */
250	movw	$load_msg+1, %si	/* "Loading" */
251	movb	%dl, %dh
252
253	/*
254	 * BIOS call "INT 0x16 Get Keyboard Shift Flags
255	 *	Call with	%ah = 0x02
256	 *	Return:
257	 *			%al = shift flags
258	 *			%ah - undefined by many BIOSes
259	 */
260	movb	$0x02, %ah
261	int	$0x16
262
263	/*
264	 * We provide the ability to force CHS use without having to hold
265	 * down the SHIFT key each boot.  Just set the byte at force_chs
266	 * to 1 (more accurately any value with either of the bottom two
267	 * bits set, but the use of 1 is recommended).
268	 */
269force_chs = .+1
270	orb	$0, %al
271
272	testb	$0x3, %al		/* Either shift key down? */
273	jz	no_force_chs
274
275	decw	%si			/* "!Loading" indicates forced CHS */
276	xorb	%dh, %dh		/* Pretend a floppy, so no LBA use */
277
278no_force_chs:
279	/* Print pretty message */
280	call	Lmessage
281
282	/*
283	 * We will use LBA reads if we have LBA support, so find out.
284	 */
285
286	/*
287	 * But don't even try on floppies, OR if forcing to CHS.
288	 *
289	 * (We're really testing %dl, but use %dh so we can force the
290	 * top bit to zero to force CHS boot.)
291	 */
292	testb	$0x80, %dh
293	jz	no_lba
294
295	/*
296	 * BIOS call "INT 0x13 Extensions Installation Check"
297	 *	Call with	%ah = 0x41
298	 *			%bx = 0x55AA
299	 *			%dl = drive (0x80 for 1st hd, 0x81 for 2nd, etc)
300	 *	Return:
301	 *			carry set: failure
302	 *				%ah = error code (0x01, invalid func)
303	 *			carry clear: success
304	 *				%bx = 0xAA55 (must verify)
305	 *				%ah = major version of extensions
306	 *				%al   (internal use)
307	 *				%cx = capabilities bitmap
308	 *					0x0001 - extnd disk access funcs
309	 *					0x0002 - rem. drive ctrl funcs
310	 *					0x0004 - EDD functions with EBP
311	 *				%dx   (extension version?)
312	 */
313
314	pushw	%dx			/* Save the drive number (%dl) */
315	movw	$0x55AA, %bx
316	movb	$0x41, %ah
317	int	$0x13
318	popw	%dx			/* Retrieve drive number */
319
320	jc	no_lba			/* Did the command work? Jump if not */
321	cmpw	$0xAA55, %bx		/* Check that bl, bh exchanged */
322	jne	no_lba			/* If not, don't have EDD extensions */
323	testb	$0x01, %cl		/* And do we have "read" available? */
324	jz	no_lba			/* Again, use CHS if not */
325
326	/* We have LBA support, so that's the vector to use */
327
328	movw	$load_lba, load_fsblock
329	jmp	get_going
330
331no_lba:
332	pushw	%dx
333
334	/*
335	 * BIOS call "INT 0x13 Function 0x08" to get drive parameters
336	 *	Call with        %ah = 0x08
337	 *                       %dl = drive (0x80 for 1st hd, 0x81 for 2nd...)
338	 *       Return:
339	 *                       carry set: failure
340	 *                           %ah = err code
341	 *                       carry clear: success
342	 *                           %ah = 0x00
343	 *                           %al = 0x00 (some BIOSes)
344	 *                           %ch = 0x00 (some BIOSes)
345	 *                           %ch = max-cylinder & 0xFF
346	 *                           %cl = max sector | rest of max-cyl bits
347	 *                           %dh = max head number
348	 *                           %dl = number of drives
349	 *                                 (according to Ralph Brown Int List)
350	 */
351	movb	$0x08, %ah
352	int	$0x13			/* We need to know heads & sectors */
353
354	jc	cant_boot		/* If error, can't boot */
355
356	movb	%dh, maxheads		/* Remember this */
357
358	andb	$0x3F, %cl
359	jz	cant_boot
360	movb	%cl, nsectors
361
362	putc(CHAR_CHS_READ)		/* Indicate (subtly) CHS reads */
363
364	popw	%dx			/* Retrieve the drive number */
365
366get_going:
367	/*
368	 * Older versions of biosboot used to set up the destination
369	 * segment, and increase the target offset every time a number
370	 * of blocks was read.  That limits /boot to 64k.
371	 *
372	 * In order to support /boots > 64k, we always read to offset
373	 * 0000 in the target segment, and just increase the target segment
374	 * each time.
375	 */
376
377	/*
378	 * We would do movl inodeblk, %eax  here, but that instruction
379	 * is 4 bytes long; add 4 bytes for data takes 8 bytes.  Using
380	 * a load immediate takes 6 bytes, and we just get installboot
381	 * to patch here, rather than data anywhere else.
382	 */
383inodeblk = .+2
384	movl	$0x90909090, %eax	/* mov $inodeblk, %eax */
385
386	movw	$INODESEG, %bx		/* Where to put /boot's inode */
387
388	/*
389	 * %eax - filesystem block to read
390	 * %bx  - target segment (target offset is 0000)
391	 * %dl  - BIOS drive number
392	 */
393	call	*load_fsblock		/* This will crash'n'burn on errs */
394
395	/*
396	 * We now have /boot's inode in memory.
397	 *
398	 * /usr/include/ufs/ufs/dinode.h for the details:
399	 *
400	 * Offset  8 (decimal): 64-bit file size (only use low 32 bits)
401	 * Offset 40 (decimal): list of NDADDR (12) direct disk blocks
402	 * Offset 88 (decimal): list of NIADDR (3) indirect disk blocks
403	 *
404	 * NOTE: list of indirect blocks immediately follows list of
405	 * direct blocks.  We use this fact in the code.
406	 *
407	 * We only support loading from direct blocks plus the first
408	 * indirect block.  This is the same as the previous biosboot/
409	 * installboot limit.  Note that, with default 16,384-bytes
410	 * filesystem blocks, the direct block list supports files up
411	 * to 192 KB.  /boot is currently around 60 KB.
412	 *
413	 * The on-disk format can't change (filesystems with this format
414	 * already exist) so okay to hardcode offsets here.
415	 *
416	 * The nice thing about doing things with filesystem blocks
417	 * rather than sectors is that filesystem blocks numbers have
418	 * 32 bits, so fit into a single register (even if "e"d).
419	 *
420	 * Note that this code does need updating if booting from a new
421	 * filesystem is required.
422	 */
423#define NDADDR	12
424#define di_db	40			/* Not used; addr put in by instboot */
425#define di_ib	88			/* Not used; run on from direct blks */
426
427	/*
428	 * Register usage:
429	 *
430	 * %eax - block number for load_fsblock
431	 * %bx  - target segment (target offset is 0000) for load_fsblock
432	 * %dl  - BIOS drive number for load_fsblock
433	 * %esi - points to block table in inode/indirect block
434	 * %cx  - number of blocks to load within loop (i.e. from current
435	 *	  block list, which is either the direct block list di_db[]
436	 *	  or the indirect block list)
437	 * %di  - total number of blocks to load
438	 */
439
440	/*
441	 * We would do movl inodedbl, %esi  here, but that instruction
442	 * is 4 bytes long; add 4 bytes for data takes 8 bytes.  Using
443	 * a load immediate takes 6 bytes, and we just get installboot
444	 * to patch here, rather than in data anywhere else.
445	 */
446inodedbl = .+2
447	movl	$0x90909090, %esi	/* mov $inodedbl, %esi */
448					/* Now esi -> di_db[] */
449
450nblocks = .+1
451	movw	$0x9090, %di		/* mov nblocks, %di */
452	movw	%di, %cx
453	cmpw	$NDADDR, %cx
454	jc	1f
455	movw	$NDADDR, %cx
4561:					/* %cx = min(nblocks, $NADDR) */
457
458	movw	$(LOADADDR >> 4), %bx	/* Target segment for /boot */
459
460load_blocks:
461	putc(CHAR_BLOCK_READ)		/* Show progress indicator */
462
463	cld
464
465	/* Get the next filesystem block number into %eax */
466	lodsl			/* %eax = *(%si++), make sure 0x66 0xad */
467
468	/*
469	 * The addw could be a 3 byte instruction, but stick to a 4 byte
470	 * one since the former inroduces mysterious hangs on *some*
471	 * BIOS implementations, possibly alignment related.
472	 * Grand prize for somebody finding the root cause!
473	 */
474blkincr = .+2
475	addw	$0x90, %si	/* adjust %si if needed (for ffs2) */
476
477	pushal				/* Save all 32-bit registers */
478
479	/*
480	 * Read a single filesystem block (will almost certainly be multiple
481	 * disk sectors)
482	 *
483	 * %eax - filesystem block to read
484	 * %bx  - target segment (target offset is 0000)
485	 * %dl  - BIOS drive number
486	 */
487	call	*load_fsblock		/* This will crash'n'burn on errs */
488
489	popal				/* Restore 32-bit registers */
490
491	/*
492	 * We want to put addw fs_bsize_p, %bx, which takes 4 bytes
493	 * of code and two bytes of data.
494	 *
495	 * Instead, use an immediate load, and have installboot patch
496	 * here directly.
497	 */
498	/* Move on one filesystem block */
499fs_bsize_p = .+2
500	addw	$0x9090, %bx		/* addw $fs_bsize_p, %bx */
501
502	decw	%di
503	loop	load_blocks
504
505	/* %cx == 0 ... important it stays this way (used later) */
506
507	/*
508	 * Finished reading a set of blocks.
509	 *
510	 * This was either the direct blocks, and there may or may not
511	 * be indirect blocks to read, or it was the indirect blocks,
512	 * and we may or may not have read in all of /boot.  (Ideally
513	 * will have read in all of /boot.)
514	 */
515	orw	%di, %di
516	jz	done_load		/* No more sectors to read */
517
518	/* We have more blocks to load */
519
520	/* We only support a single indirect block (the same as previous
521	 * versions of installboot.  This is required for the boot floppies.
522	 *
523	 * We use a bit of the code to store a flag that indicates
524	 * whether we have read the first indirect block or not.
525	 *
526	 * If we've already read the indirect list, we can't load this /boot.
527	 *
528	 * indirect	uint8	0 => running through load_blocks loop reading
529	 *			direct blocks.  If != 0, we're reading the
530	 *			indirect blocks.  Must use a field that is
531	 *			initialised to 0.
532	 */
533indirect = .+2
534	movw	$PBR_TOO_MANY_INDIRECTS, %ax	/* movb $PRB_TOO..., %al */
535						/* movb indirect, %ah */
536	orb	%ah, %ah
537	jnz	err_print_crlf
538
539	incb	indirect		/* No need to worry about wrap */
540					/* around, as this will only be done */
541					/* once before we fail */
542
543	/* Okay, let's read in the indirect block */
544
545	lodsl				/* Get blk num of 1st indirect blk */
546
547	pushw	%bx			/* Remember where we got to */
548	movw	$INODESEG, %bx
549	call	*load_fsblock		/* This will crash'n'burn on errs */
550	popw	%bx			/* Indirect blocks get added on to */
551					/* just after where we got to */
552	movl	$INODEOFF, %esi
553	movw	%di, %cx		/* How many blocks left to read */
554
555	jmp	load_blocks
556
557done_load:
558	puts(crlf)
559
560	/* %cx == 0 from loop above... keep it that way */
561
562	/*
563	 * Check the magic signature at the beginning of /boot.
564	 * Since /boot is now ELF, this should be 0x7F E L F.
565	 */
566	movw	$(LOADADDR >> 4), %ax	/* Target segment */
567	movw	%ax, %es
568
569	/*
570	 * We cheat a little here, and only check the L and F.
571	 *
572	 * (Saves 3 bytes of code... the two signature bytes we
573	 * don't check, and the operand size prefix that's not
574	 * needed.)
575	 */
576	cmpw	$LFMAGIC, %es:2(,1)
577	je	exec_boot
578
579	movb	$PBR_BAD_MAGIC, %al
580
581err_print:
582	movw	$err_txt, %si
583err_print2:
584	movb	%al, err_id
585err_stop:
586	call	Lmessage
587stay_stopped:
588	sti				/* Ensure Ctl-Alt-Del will work */
589	hlt				/* (don't require power cycle) */
590	jmp	stay_stopped		/* Just to make sure :-) */
591
592exec_boot:
593	/* At this point we could try to use the entry point in
594	 * the image we just loaded.  But if we do that, we also
595	 * have to potentially support loading that image where it
596	 * is supposed to go.  Screw it, just assume that the image
597	 * is sane.
598	 */
599#ifdef BDEBUG
600	putc('P')
601#endif
602
603	/* %cx == 0 from loop above... keep it that way */
604
605	/*
606	 * We want to do movzbl %dl, %eax ; pushl %eax to zero-extend the
607	 * drive number to 32 bits and pass it to /boot.  However, this
608	 * takes 6 bytes.
609	 *
610	 * Doing it this way saves 2 bytes.
611	 */
612	pushw	%cx
613	movb	%dl, %cl
614	pushw	%cx
615
616	pushl	$BOOTMAGIC	/* use some magic */
617
618	/* jmp	/boot */
619	ljmp $(LINKADDR >> 4), $0
620	/* not reached */
621
622
623/*
624 * Load a single filesystem block into memory using CHS calls.
625 *
626 * Input:	%eax - 32-bit filesystem block number
627 * 		%bx  - target segment (target offset is 0000)
628 * 		%dl  - BIOS drive number
629 *
630 * Output:	block successfully read in (panics if not)
631 *		all general purpose registers may have been trashed
632 */
633load_chs:
634	/*
635	 * BIOS call "INT 0x13 Function 0x2" to read sectors from disk into
636	 * memory.
637	 *	Call with        %ah = 0x42
638	 *                       %ah = 0x2
639	 *                       %al = number of sectors
640	 *                       %ch = cylinder & 0xFF
641	 *                       %cl = sector (0-63) | rest of cylinder bits
642	 *                       %dh = head
643	 *                       %dl = drive (0x80 for 1st hd, 0x81 for 2nd...)
644	 *                       %es:%bx = segment:offset of buffer
645	 *       Return:
646	 *                       carry set: failure
647	 *                           %ah = err code
648	 *                           %al = number of sectors transferred
649	 *                       carry clear: success
650	 *                           %al = 0x0 OR number of sectors transferred
651	 *                                 (depends on BIOS!)
652	 *                                 (according to Ralph Brown Int List)
653	 */
654
655	/* Convert the filesystem block into a sector value */
656	call	fsbtosector
657	movl	lba_sector, %eax	/* we can only use 24 bits, really */
658
659	movw	fs_bsize_s, %cx	/* sectors per filesystem block */
660
661	/*
662	 * Some BIOSes require that reads don't cross track boundaries.
663	 * Therefore we do all CHS reads single-sector.
664	 */
665calc_chs:
666	pushal
667	movw	%bx, %es	/* Set up target segment */
668
669	pushw	%dx		/* Save drive number (in %dl) */
670	xorl	%edx, %edx
671	movl	%edx, %ecx
672
673nsectors = .+1
674	movb	$0x90, %cl	/* movb $nsectors, %cl */
675				/* Doing it this way saves 4-2 = 2 bytes code */
676				/* bytes (no data, since we would overload) */
677
678	divl	%ecx, %eax
679				/* Now have sector number in %dl */
680	pushw	%dx		/* Remember for later */
681
682	xorl	%edx, %edx
683
684maxheads = .+1
685	movb	$0x90, %cl	/* movb $maxheads, %cl; 0 <= maxheads <= 255 */
686				/* Doing it this way saves 4-2 = 2 code */
687				/* bytes (no data, since we would overload */
688
689	incw	%cx		/* Number of heads is 1..256, no "/0" worries */
690
691	divl	%ecx, %eax
692				/* Have head number in %dl */
693				/* Cylinder number in %ax */
694	movb	%al, %ch	/* Bottom 8 bits of cyl number */
695	shlb	$6, %ah		/* Move up top 2 bits of cyl number */
696	movb	%ah, %cl	/* Top 2 bits of cyl number in here */
697
698	popw	%bx		/* (pushed %dx, but need %dl for now */
699	incb	%bl		/* Sector numbers run from 1, not 0 */
700	orb	%bl, %cl	/* Or the sector number into top bits cyl */
701
702				/* Remember, %dl has head number */
703	popw	%ax
704				/* %al has BIOS drive number -> %dl */
705
706	movb	%dl, %dh	/* Now %dh has head number (from 0) */
707	movb	%al, %dl	/* Now %dl has BIOS drive number */
708
709	xorw	%bx, %bx	/* Set up target offset */
710
711	movw	$0x0201, %ax	/* %al = 1 - read one sector at a time */
712				/* %ah = 2 - int 0x13 function for CHS read */
713
714	call	do_int_13	/* saves us 1 byte :-) */
715
716	/* Get the next sector */
717
718	popal
719	incl	%eax
720	addw	$32, %bx	/* Number of segments/paras in a sector */
721	loop	calc_chs
722
723	ret
724
725	/* read error */
726read_error:
727	movb	$PBR_READ_ERROR, %al
728err_print_crlf:
729	movw	$err_txt_crlf, %si
730	jmp	err_print2
731
732
733/*
734 * Load a single filesystem block into memory using LBA calls.
735 *
736 * Input:	%eax - 32-bit filesystem block number
737 * 		%bx  - target segment (target offset is 0000)
738 * 		%dl  - BIOS drive number
739 *
740 * Output:	block successfully read in (panics if not)
741 *		all general purpose registers may have been trashed
742 */
743load_lba:
744	/*
745	 * BIOS call "INT 0x13 Extensions Extended Read"
746	 *	Call with	%ah = 0x42
747	 *			%dl = drive (0x80 for 1st hd, 0x81 for 2nd, etc)
748	 *			%ds:%si = segment:offset of command packet
749	 *	Return:
750	 *			carry set: failure
751	 *				%ah = error code (0x01, invalid func)
752	 *				command packet's sector count field set
753	 *				to the number of sectors successfully
754	 *				transferred
755	 *			carry clear: success
756	 *				%ah = 0 (success)
757	 *	Command Packet:
758	 *			0x0000	BYTE	packet size (0x10 or 0x18)
759	 *			0x0001	BYTE	reserved (should be 0)
760	 *			0x0002	WORD	sectors to transfer (max 127)
761	 *			0x0004	DWORD	seg:offset of transfer buffer
762	 *			0x0008	QWORD	starting sector number
763	 */
764	call	fsbtosector		/* Set up lba_sector & lba_sector+4 */
765
766	/* movb	%dh, lba_count		<- XXX done by installboot */
767	movw	%bx, lba_seg
768	movw	$lba_command, %si
769	movb	$0x42, %ah
770do_int_13:
771	int	$0x13
772	jc	read_error
773
774	ret
775
776
777/*
778 * Converts a given filesystem block number into a disk sector
779 * at lba_sector and lba_sector+4.
780 *
781 * Input:	%eax - 32-bit filesystem block number
782 *
783 * Output:	lba_sector and lba_sector+4 set up
784 *		XXX
785 */
786fsbtosector:
787	/*
788	 * We want to do
789	 *
790	 * movb	fsbtodb, %ch		/# Shift counts we'll need #/
791	 * movb	$32, %cl
792	 *
793	 * which is 6 bytes of code + 1 byte of data.
794	 *
795	 * We'll actually code it with an immediate 16-bit load into %cx,
796	 * which is just 3 bytes of data (saves 4 bytes).
797	 */
798fsbtodb = .+2
799	movw	$0x9020, %cx		/* %ch = fsbtodb, %cl = 0x20 */
800
801	pushl	%eax
802	subb	%ch, %cl
803	shrl	%cl, %eax
804	movl	%eax, lba_sector+4
805	popl	%eax
806
807	movb	%ch, %cl
808	shll	%cl, %eax
809
810	/*
811	 * And add p_offset, which is the block offset to the start
812	 * of the filesystem.
813	 *
814	 * We would do addl p_offset, %eax, which is 5 bytes of code
815	 * and 4 bytes of data, but it's more efficient to have
816	 * installboot patch directly in the code (this variable is
817	 * only used here) for 6 bytes of code (but no data).
818	 */
819p_offset = .+2
820	addl	$0x90909090, %eax	/* addl $p_offset, %eax */
821
822	movl	%eax, lba_sector
823	jnc	1f
824
825	incl	lba_sector+4
8261:
827	ret
828
829
830/*
831 * Display string
832 */
833Lmessage:
834	cld
8351:
836	lodsb			/* load a byte into %al */
837	orb	%al, %al
838	jz	1f
839	call	Lchr
840	jmp	1b
841
842/*
843 *	Lchr: write the character in %al to console
844 */
845Lchr:
846#ifdef SERIAL
847	pushw	%dx
848	movb	$0x01, %ah
849	xorw	%dx, %dx
850	movb	SERIAL, %dl
851	int	$0x14
852	popw	%dx
853#else
854	pushw	%bx
855	movb	$0x0e, %ah
856	xorw	%bx, %bx
857	incw	%bx		/* movw $0x01, %bx */
858	int	$0x10
859	popw	%bx
860#endif
8611:
862	ret
863
864	/* .data */
865
866/* vector to the routine to read a particular filesystem block for us */
867load_fsblock:
868	.word	load_chs
869
870
871/* This next block is used for the EDD command packet used to read /boot
872 * sectors.
873 *
874 * lba_count is set up for us by installboot.  It is the number of sectors
875 * in a filesystem block.  (Max value 127.)
876 *
877 * XXX The EDD limit of 127 sectors in one read means that we currently
878 *     restrict filesystem blocks to 127 sectors, or < 64 KB.  That is
879 *     effectively a 32 KB block limit, as filesystem block sizes are
880 *     powers of two.  The default filesystem block size is 16 KB.
881 *
882 *     I say we run with this limitation and see where it bites us...
883 */
884
885lba_command:
886	.byte	0x10			/* size of command packet */
887	.byte	0x00			/* reserved */
888fs_bsize_s:
889lba_count:
890	.word	0			/* sectors to transfer, max 127 */
891	.word	0			/* target buffer, offset */
892lba_seg:
893	.word	0			/* target buffer, segment */
894lba_sector:
895	.long	0, 0			/* sector number */
896
897load_msg:
898	.asciz	"!Loading"
899err_txt_crlf:
900	.ascii	"\r\n"
901err_txt:
902	.ascii	"ERR "
903err_id:
904	.ascii	"?"
905crlf:	.asciz	"\r\n"
906
907	. = 0x200 - 2
908	/* a little signature */
909	.word	DOSMBR_SIGNATURE
910