root/arch/i386/stand/mbr/mbr.S

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

/* [<][>][^][v][top][bottom][index][help] */