Home | History | Annotate | Line # | Download | only in cdboot
cdboot.S revision 1.6.74.1
      1  1.6.74.1       mjf /*	$NetBSD: cdboot.S,v 1.6.74.1 2008/06/02 13:22:18 mjf Exp $	*/
      2       1.1  junyoung 
      3       1.1  junyoung /*-
      4       1.1  junyoung  * Copyright (c) 2005 The NetBSD Foundation, Inc.
      5       1.1  junyoung  * All rights reserved.
      6       1.1  junyoung  *
      7       1.1  junyoung  * This code is derived from software contributed to The NetBSD Foundation
      8       1.1  junyoung  * by Bang Jun-Young.
      9       1.1  junyoung  *
     10       1.1  junyoung  * Redistribution and use in source and binary forms, with or without
     11       1.1  junyoung  * modification, are permitted provided that the following conditions
     12       1.1  junyoung  * are met:
     13       1.1  junyoung  * 1. Redistributions of source code must retain the above copyright
     14       1.1  junyoung  *    notice, this list of conditions and the following disclaimer.
     15       1.1  junyoung  * 2. Redistributions in binary form must reproduce the above copyright
     16       1.1  junyoung  *    notice, this list of conditions and the following disclaimer in the
     17       1.1  junyoung  *    documentation and/or other materials provided with the distribution.
     18       1.1  junyoung  *
     19       1.1  junyoung  * THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
     20       1.1  junyoung  * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
     21       1.1  junyoung  * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
     22       1.1  junyoung  * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS
     23       1.1  junyoung  * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
     24       1.1  junyoung  * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
     25       1.1  junyoung  * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
     26       1.1  junyoung  * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
     27       1.1  junyoung  * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
     28       1.1  junyoung  * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
     29       1.1  junyoung  * POSSIBILITY OF SUCH DAMAGE.
     30       1.1  junyoung  */
     31       1.1  junyoung 
     32       1.1  junyoung /*
     33       1.1  junyoung  * This is a primary boot loader that loads a secondary boot loader
     34       1.1  junyoung  * directly from CD without performing floppy/hard disk emulation as
     35       1.1  junyoung  * described by the El Torito specification.
     36       1.1  junyoung  *
     37       1.1  junyoung  * TODO:
     38       1.1  junyoung  *  - Support for loading secondary boot loader > 64kB
     39       1.1  junyoung  */
     40       1.1  junyoung 
     41       1.1  junyoung #include <machine/asm.h>
     42       1.5    dyoung #include <sys/bootblock.h>
     43       1.1  junyoung 
     44       1.1  junyoung #define BOOT_ADDR	0x7c00
     45       1.1  junyoung #define BLOCK_SIZE	2048		/* Default for ISO 9660 */
     46       1.1  junyoung #define VD_LBA		16		/* LBA of Volume Descriptor (VD) */
     47       1.1  junyoung #define PVD_ADDR	0x1000		/* Where Primary VD is loaded */
     48       1.1  junyoung #define ROOTDIR_ADDR	0x1800		/* Where Root Directory is loaded */
     49       1.1  junyoung #define LOADER_ADDR	SECONDARY_LOAD_ADDRESS
     50       1.1  junyoung 
     51       1.5    dyoung #ifdef BOOT_FROM_FAT
     52       1.5    dyoung #define MBR_AFTERBPB	90		/* BPB size in FAT32 partition BR */
     53       1.5    dyoung #else
     54       1.5    dyoung #define MBR_AFTERBPB	62		/* BPB size in floppy master BR */
     55       1.5    dyoung #endif
     56       1.5    dyoung 
     57       1.1  junyoung /*
     58       1.3  junyoung  * See src/sys/sys/bootblock.h for details.
     59       1.3  junyoung  */
     60       1.3  junyoung #define MBR_PART_COUNT	4
     61       1.3  junyoung #define MBR_PART_OFFSET	446
     62       1.3  junyoung #define MBR_PART_SIZE	16		/* sizeof(struct mbr_partition) */
     63       1.3  junyoung 
     64       1.3  junyoung /*
     65       1.1  junyoung  * Disk error codes
     66       1.1  junyoung  */
     67       1.1  junyoung #define ERROR_TIMEOUT	0x80
     68       1.1  junyoung 
     69       1.1  junyoung /*
     70       1.1  junyoung  * Volume Descriptor types.
     71       1.1  junyoung  */
     72       1.1  junyoung #define VD_PRIMARY		1
     73       1.1  junyoung #define VD_SUPPLEMENTARY	2
     74       1.1  junyoung #define VD_TERMINATOR		255
     75       1.1  junyoung 
     76       1.1  junyoung /* Only actually used entries are listed below */
     77       1.1  junyoung 
     78       1.1  junyoung /*
     79       1.1  junyoung  * Format of Primary Volume Descriptor (8.4)
     80       1.1  junyoung  */
     81       1.1  junyoung #define PVD_ROOT_DR	156	/* Offset of Root Directory Record */
     82       1.1  junyoung 
     83       1.1  junyoung /*
     84       1.1  junyoung  * Format of Directory Record (9.1)
     85       1.1  junyoung  */
     86       1.1  junyoung #define DR_LEN		0
     87       1.1  junyoung #define DR_EXTENT	2
     88       1.1  junyoung #define DR_DATA_LEN	10
     89       1.1  junyoung #define DR_NAME_LEN	32
     90       1.1  junyoung #define DR_NAME		33
     91       1.1  junyoung 
     92       1.1  junyoung 	.text
     93       1.1  junyoung 	.code16
     94       1.1  junyoung ENTRY(start)
     95       1.5    dyoung 	jmp	start1
     96       1.5    dyoung 
     97       1.5    dyoung 	. = start + MBR_AFTERBPB	/* skip BPB */
     98       1.5    dyoung 	. = start + MBR_DSN_OFFSET
     99       1.5    dyoung 	.long	0
    100       1.5    dyoung 
    101       1.5    dyoung /* mbr_bootsel_magic (not used here) */
    102       1.5    dyoung 	. = start + MBR_BS_MAGIC_OFFSET
    103       1.5    dyoung 	.word	0
    104       1.5    dyoung 
    105       1.5    dyoung 	. = start + MBR_PART_OFFSET
    106       1.5    dyoung 	. = start + MBR_MAGIC_OFFSET
    107       1.5    dyoung pbr_magic:
    108       1.5    dyoung 	.word	MBR_MAGIC
    109       1.5    dyoung 	.fill	512			/* reserve space for disklabel */
    110       1.5    dyoung start1:
    111       1.5    dyoung 	jmp	1f
    112       1.5    dyoung 	.balign	4
    113       1.5    dyoung 	.long	X86_BOOT_MAGIC_1	/* checked by installboot & pbr code */
    114       1.5    dyoung boot_params:				/* space for patchable variables */
    115       1.5    dyoung 	.long	1f - boot_params	/* length of this data area */
    116       1.5    dyoung #include <boot_params.S>
    117       1.5    dyoung 	. = start1 + 0x80		/* Space for patching unknown params */
    118       1.5    dyoung 
    119       1.5    dyoung 1:	xorw	%ax, %ax
    120       1.1  junyoung 	movw	%ax, %ds
    121       1.1  junyoung 	movw	%ax, %es
    122       1.1  junyoung 	movw	%ax, %ss
    123       1.1  junyoung 	movw	$BOOT_ADDR, %sp
    124       1.1  junyoung 	movw	%sp, %si
    125       1.1  junyoung 	movw	$start, %di
    126       1.1  junyoung 	movw	$BLOCK_SIZE/2, %cx
    127       1.1  junyoung 	rep
    128       1.1  junyoung 	movsw
    129       1.1  junyoung 	ljmp	$0, $real_start
    130       1.1  junyoung 
    131       1.1  junyoung real_start:
    132       1.1  junyoung 	movb	%dl, boot_drive		/* Save boot drive number */
    133       1.2  junyoung 
    134       1.4  junyoung #ifndef DISABLE_KEYPRESS
    135       1.3  junyoung 	/*
    136       1.3  junyoung 	 * We can skip boot wait when:
    137       1.3  junyoung 	 *  - there's no hard disk present.
    138       1.3  junyoung 	 *  - there's no active partition in the MBR of the 1st hard disk.
    139       1.3  junyoung 	 */
    140       1.3  junyoung 
    141       1.3  junyoung 	/*
    142       1.3  junyoung 	 * Check presence of hard disks.
    143       1.3  junyoung 	 */
    144       1.3  junyoung 	movw	$0x475, %si
    145       1.2  junyoung 	movb	(%si), %al
    146       1.2  junyoung 	testb	%al, %al
    147       1.2  junyoung 	jz	boot_cdrom
    148       1.2  junyoung 
    149       1.3  junyoung 	/*
    150       1.3  junyoung 	 * Find the active partition from the MBR.
    151       1.3  junyoung 	 */
    152       1.3  junyoung 	movw	$0x0201, %ax		/* %al = number of sectors to read */
    153       1.3  junyoung 	movw	$BOOT_ADDR, %bx		/* %es:%bx = data buffer */
    154       1.3  junyoung 	movw	$0x0001, %cx		/* %ch = low 8 bits of cylinder no */
    155       1.3  junyoung 					/* %cl = high 2 bits of cyl no & */
    156       1.3  junyoung 					/*       sector number */
    157       1.3  junyoung 	movw	$0x0080, %dx		/* %dh = head number */
    158       1.3  junyoung 					/* %dl = disk number */
    159       1.3  junyoung 	int	$0x13			/* Read MBR into memory */
    160       1.3  junyoung 	jc	boot_cdrom		/* CF set on error */
    161       1.3  junyoung 
    162       1.3  junyoung 	movb	$1, mbr_loaded
    163       1.3  junyoung 	movb	$MBR_PART_COUNT, %cl
    164       1.3  junyoung 	movw	$BOOT_ADDR+MBR_PART_OFFSET, %si
    165       1.3  junyoung 1:
    166       1.3  junyoung 	movb	(%si), %al
    167       1.3  junyoung 	testb	$0x80, %al
    168       1.3  junyoung 	jnz	found_active
    169       1.3  junyoung 	addw	$MBR_PART_SIZE, %si
    170       1.3  junyoung 	decb	%cl
    171       1.3  junyoung 	testb	%cl, %cl
    172       1.3  junyoung 	jnz	1b			/* If 0, no active partition found */
    173       1.3  junyoung 	jmp	boot_cdrom
    174       1.3  junyoung 
    175       1.3  junyoung found_active:
    176       1.1  junyoung 	movw	$str_press_key, %si
    177       1.1  junyoung 	call	message
    178       1.1  junyoung next_second:
    179       1.1  junyoung 	movw	$str_dot, %si
    180       1.1  junyoung 	call	message
    181       1.1  junyoung 	decb	wait_count
    182       1.1  junyoung 	jz	boot_hard_disk
    183       1.1  junyoung 	xorb	%ah, %ah		/* Get system time */
    184       1.1  junyoung 	int	$0x1a
    185       1.1  junyoung 	movw	%dx, %di		/* %cx:%dx = number of clock ticks */
    186       1.1  junyoung 	addw	$19, %di		/* 19 ~= 18.2 Hz */
    187       1.1  junyoung wait_key:
    188       1.1  junyoung 	movb	$1, %ah			/* Check for keystroke */
    189       1.1  junyoung 	int	$0x16
    190       1.1  junyoung 	jz	not_avail		/* ZF clear if keystroke available */
    191       1.1  junyoung 	xorb	%ah, %ah		/* Read key to flush keyboard buf */
    192       1.1  junyoung 	int	$0x16
    193       1.1  junyoung 	jmp	boot_cdrom
    194       1.1  junyoung not_avail:
    195       1.1  junyoung 	xorb	%ah, %ah		/* Get system time */
    196       1.1  junyoung 	int	$0x1a
    197       1.1  junyoung 	cmpw	%dx, %di		/* Compare with saved time */
    198       1.1  junyoung 	jnz	wait_key
    199       1.1  junyoung 	jmp	next_second
    200       1.1  junyoung 
    201       1.1  junyoung boot_hard_disk:
    202       1.1  junyoung 	movw	$str_crlf, %si
    203       1.1  junyoung 	call	message
    204       1.3  junyoung 	cmpb	$1, mbr_loaded
    205       1.3  junyoung 	jz	1f
    206       1.1  junyoung 	movw	$0x0201, %ax		/* %al = number of sectors to read */
    207       1.1  junyoung 	movw	$BOOT_ADDR, %bx		/* %es:%bx = data buffer */
    208       1.1  junyoung 	movw	$0x0001, %cx		/* %ch = low 8 bits of cylinder no */
    209       1.1  junyoung 					/* %cl = high 2 bits of cyl no & */
    210       1.1  junyoung 					/*       sector number */
    211       1.1  junyoung 	movw	$0x0080, %dx		/* %dh = head number */
    212       1.1  junyoung 					/* %dl = disk number */
    213       1.1  junyoung 	int	$0x13			/* Read MBR into memory */
    214       1.1  junyoung 	jc	panic			/* CF set on error */
    215       1.3  junyoung 1:
    216       1.1  junyoung 	movw	%cs, %ax		/* Restore initial state */
    217       1.1  junyoung 	movw	%ax, %ds
    218       1.1  junyoung 	movw	%ax, %es
    219       1.1  junyoung 	movw	$0x0080, %dx		/* %dl = boot drive number */
    220       1.1  junyoung 	jmp	$0, $BOOT_ADDR		/* Jump to MBR! */
    221       1.4  junyoung 	jmp	panic			/* This should be never executed */
    222       1.4  junyoung #endif /* !DISABLE_KEYPRESS */
    223       1.1  junyoung 
    224       1.1  junyoung boot_cdrom:
    225       1.1  junyoung 	movw	$str_banner, %si
    226       1.1  junyoung 	call	message
    227       1.1  junyoung 	movl	$VD_LBA, %eax
    228       1.1  junyoung next_block:
    229       1.1  junyoung 	movb	$1, %dh			/* Number of sectors to read */
    230       1.1  junyoung 	movl	$PVD_ADDR, %ebx
    231       1.1  junyoung 	call	read_sectors
    232       1.1  junyoung 	cmpb	$VD_PRIMARY, (%bx)	/* Is it Primary Volume Descriptor? */
    233       1.1  junyoung 	jz	pvd_found
    234       1.1  junyoung 	incl	%eax
    235       1.1  junyoung 	cmpb	$VD_TERMINATOR, (%bx)
    236       1.1  junyoung 	jnz	next_block
    237       1.1  junyoung 	movw	$str_no_pvd, %si
    238       1.1  junyoung 	call	message
    239       1.1  junyoung 	jmp	panic
    240       1.1  junyoung 
    241       1.1  junyoung pvd_found:
    242       1.1  junyoung 	movw	$PVD_ADDR+PVD_ROOT_DR, %bx
    243       1.1  junyoung 	movl	DR_EXTENT(%bx), %eax	/* LBA of the root directory */
    244       1.1  junyoung 	movl	DR_DATA_LEN(%bx), %edx
    245       1.1  junyoung 	shrl	$11, %edx		/* Convert to number of sectors */
    246       1.1  junyoung 	movb	%dl, %dh		/*  ... and load it to %dh */
    247       1.1  junyoung 	movl	$ROOTDIR_ADDR, %ebx
    248       1.1  junyoung 	call	read_sectors
    249       1.1  junyoung next_entry:
    250       1.1  junyoung 	cmpb	$0, DR_LEN(%bx)
    251       1.1  junyoung 	jz	last_entry
    252       1.1  junyoung 	movw	%bx, %si
    253       1.1  junyoung 	addw	$DR_NAME, %si
    254       1.1  junyoung 	movb	DR_NAME_LEN(%bx), %cl
    255       1.1  junyoung 	movw	$str_loader, %di
    256       1.1  junyoung 1:
    257       1.1  junyoung 	movb	(%si), %al
    258       1.1  junyoung 	cmpb	%al, (%di)
    259       1.1  junyoung 	jnz	fail
    260       1.1  junyoung 	incw	%si
    261       1.1  junyoung 	incw	%di
    262       1.1  junyoung 	decb	%cl
    263       1.1  junyoung 	jnz	1b
    264       1.1  junyoung 	jmp	load_loader
    265       1.1  junyoung fail:
    266       1.1  junyoung 	addw	DR_LEN(%bx), %bx
    267       1.1  junyoung 	jmp	next_entry
    268       1.1  junyoung last_entry:
    269       1.1  junyoung 	movw	$str_no_loader, %si
    270       1.1  junyoung 	call	message
    271       1.1  junyoung 	jmp	panic
    272       1.1  junyoung 
    273       1.1  junyoung load_loader:
    274       1.1  junyoung 	movl	DR_EXTENT(%bx), %eax
    275       1.1  junyoung 	movl	DR_DATA_LEN(%bx), %edx
    276       1.1  junyoung 	addl	$(BLOCK_SIZE-1), %edx	/* Convert file length to */
    277       1.1  junyoung 	shrl	$11, %edx		/*  ... number of sectors */
    278       1.1  junyoung 	movb	%dl, %dh
    279       1.1  junyoung 	movl	$LOADER_ADDR, %ebx
    280       1.1  junyoung 	call	read_sectors
    281       1.5    dyoung 	movl	$boot_params, %esi	/* Provide boot_params */
    282       1.1  junyoung 	xorl	%edx, %edx
    283       1.1  junyoung 	movb	boot_drive, %dl
    284       1.1  junyoung 	xorl	%ebx, %ebx		/* Zero sector number */
    285       1.1  junyoung 	lcall	$LOADER_ADDR/16, $0
    286       1.4  junyoung 	/* fall through on load failure */
    287       1.4  junyoung panic:
    288       1.4  junyoung 	hlt
    289       1.1  junyoung 	jmp	panic
    290       1.1  junyoung 
    291       1.1  junyoung /*
    292       1.1  junyoung  * Read disk sector(s) into memory
    293       1.1  junyoung  *
    294       1.1  junyoung  * %eax = LBA of starting sector
    295       1.1  junyoung  * %ebx = buffer to store sectors
    296       1.1  junyoung  * %dh = number of sectors to read
    297       1.1  junyoung  */
    298       1.1  junyoung read_sectors:
    299       1.1  junyoung 	pusha
    300       1.1  junyoung 	movl	%eax, edd_lba		/* Convert LBA to segment */
    301       1.1  junyoung 	shrl	$4, %ebx
    302       1.1  junyoung 	movw	%bx, edd_segment
    303       1.1  junyoung 	movb	%dh, edd_nsecs
    304       1.1  junyoung 	movb	boot_drive, %dl
    305       1.1  junyoung 	movw	$edd_packet, %si
    306       1.1  junyoung read_again:
    307       1.1  junyoung 	movb	$0x42, %ah
    308       1.1  junyoung 	int	$0x13
    309       1.1  junyoung 	jc	read_fail
    310       1.1  junyoung 	popa
    311       1.1  junyoung 	ret
    312       1.1  junyoung read_fail:
    313       1.1  junyoung 	cmpb	$ERROR_TIMEOUT, %ah
    314       1.1  junyoung 	jz	read_again
    315       1.1  junyoung 	movw	$str_read_error, %si
    316       1.1  junyoung 	call	message
    317       1.1  junyoung 	jmp	panic
    318       1.1  junyoung 
    319       1.1  junyoung /*
    320       1.1  junyoung  * For debugging purpose
    321       1.1  junyoung  */
    322       1.1  junyoung put_char:
    323       1.1  junyoung 	pusha
    324       1.1  junyoung 	movb	$0x0e, %ah
    325       1.1  junyoung 	movw	$0x0001, %bx
    326       1.1  junyoung 	int	$0x10
    327       1.1  junyoung 	popa
    328       1.1  junyoung 	ret
    329       1.1  junyoung 
    330       1.1  junyoung #include <message.S>
    331       1.1  junyoung 
    332       1.1  junyoung edd_packet:
    333       1.1  junyoung edd_len:	.word	16
    334       1.1  junyoung edd_nsecs:	.word	0		/* Number of sectors to transfer */
    335       1.1  junyoung edd_offset:	.word	0
    336       1.1  junyoung edd_segment:	.word	0
    337       1.1  junyoung edd_lba:	.quad	0
    338       1.1  junyoung 
    339       1.1  junyoung wait_count:	.byte	6
    340       1.1  junyoung boot_drive:	.byte	0
    341       1.3  junyoung mbr_loaded:	.byte	0
    342       1.1  junyoung 
    343  1.6.74.1       mjf str_banner:	.ascii	"\r\nNetBSD/x86 cd9660 Primary Bootstrap"
    344       1.1  junyoung str_crlf:	.asciz	"\r\n"
    345       1.1  junyoung str_press_key:	.asciz	"\r\nPress any key to boot from CD"
    346       1.1  junyoung str_dot:	.asciz	"."
    347       1.1  junyoung str_read_error:	.asciz	"Can't read CD"
    348       1.1  junyoung str_no_pvd:	.asciz	"Can't find Primary Volume Descriptor"
    349       1.1  junyoung str_no_loader:	.asciz	"Can't find /boot"
    350       1.1  junyoung str_loader:	.asciz	"BOOT.;1"
    351       1.1  junyoung 
    352       1.1  junyoung /* Used to calculate free bytes */
    353       1.1  junyoung free_space = end - .
    354       1.1  junyoung 
    355       1.1  junyoung 	. = start + BLOCK_SIZE
    356       1.1  junyoung end:
    357