root/arch/i386/stand/biosboot/biosboot.S

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

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