root/arch/i386/stand/cdbr/cdbr.S

/* [<][>][^][v][top][bottom][index][help] */
    1 /*      $OpenBSD: cdbr.S,v 1.2 2004/08/24 15:24:05 tom Exp $    */
    2 
    3 /*
    4  * Copyright (c) 2004 Tom Cosgrove <tom.cosgrove@arches-consulting.com>
    5  * Copyright (c) 2001 John Baldwin <jhb@FreeBSD.org>
    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  * 3. Neither the name of the author nor the names of any co-contributors
   17  *    may be used to endorse or promote products derived from this software
   18  *    without specific prior written permission.
   19  *
   20  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
   21  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
   22  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
   23  * ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
   24  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
   25  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
   26  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
   27  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   28  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
   29  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
   30  * SUCH DAMAGE.
   31  */
   32 
   33         .file   "cdbr.S"
   34 
   35 /* #include <machine/asm.h> */
   36 /* #include <assym.h> */
   37 
   38 /*
   39  * This program is a CD boot sector, similar to the partition boot record
   40  * (pbr, also called biosboot) used by hard disks.  It is implemented as a
   41  * "no-emulation" boot sector, as described in the "El Torito" Bootable
   42  * CD-ROM Format Specification.
   43  *
   44  * The function of this boot sector is to load and start the next-stage
   45  * cdboot program, which will load the kernel.
   46  *
   47  * The El Torito standard allows us to specify where we want to be loaded,
   48  * but for maximum compatibility we choose the default load address of
   49  * 0x07C00.
   50  *
   51  * Memory layout:
   52  *
   53  * 0x00000 -> 0x003FF   real mode interrupt vector table
   54  * 0x00400 -> 0x00500   BIOS data segment
   55  *
   56  * 0x00000 -> 0x073FF   our stack (grows down)          (from 29k)
   57  * 0x07400 -> 0x07BFF   we relocate to here             (at 29k)
   58  * 0x07C00 -> 0x08400   BIOS loads us here              (at 31k, for 2k)
   59  * 0x07C00 -> ...       /cdboot
   60  *
   61  * The BIOS loads us at physical address 0x07C00.  We then relocate to
   62  * 0x07400, seg:offset 0740:0000.  We then load /cdboot at seg:offset
   63  * 07C0:0000.
   64  */
   65 #define BOOTSEG         0x7c0                   /* segment we're loaded to */
   66 #define BOOTSECTSIZE    0x800                   /* our size in bytes */
   67 #define BOOTRELOCSEG    0x740                   /* segment we relocate to */
   68 #define BOOTSTACKOFF  ((BOOTRELOCSEG << 4) - 4) /* starts here, grows down */
   69 
   70 /* Constants for reading from the CD */
   71 #define ERROR_TIMEOUT           0x80            /* BIOS timeout on read */
   72 #define NUM_RETRIES             3               /* Num times to retry */
   73 #define SECTOR_SIZE             0x800           /* size of a sector */
   74 #define SECTOR_SHIFT            11              /* number of place to shift */
   75 #define BUFFER_LEN              0x100           /* number of sectors in buffr */
   76 #define MAX_READ                0x10000         /* max we can read at a time */
   77 #define MAX_READ_PARAS          MAX_READ >> 4
   78 #define MAX_READ_SEC            MAX_READ >> SECTOR_SHIFT
   79 #define MEM_READ_BUFFER         0x9000          /* buffer to read from CD */
   80 #define MEM_VOLDESC             MEM_READ_BUFFER /* volume descriptor */
   81 #define MEM_DIR                 MEM_VOLDESC+SECTOR_SIZE /* Lookup buffer */
   82 #define VOLDESC_LBA             0x10            /* LBA of vol descriptor */
   83 #define VD_PRIMARY              1               /* Primary VD */
   84 #define VD_END                  255             /* VD Terminator */
   85 #define VD_ROOTDIR              156             /* Offset of Root Dir Record */
   86 #define DIR_LEN                 0               /* Offset of Dir Rec length */
   87 #define DIR_EA_LEN              1               /* Offset of EA length */
   88 #define DIR_EXTENT              2               /* Offset of 64-bit LBA */
   89 #define DIR_SIZE                10              /* Offset of 64-bit length */
   90 #define DIR_NAMELEN             32              /* Offset of 8-bit name len */
   91 #define DIR_NAME                33              /* Offset of dir name */
   92 
   93         .text
   94         .code16
   95 
   96         .globl  start
   97 start:
   98         /* Set up stack */
   99         xorw    %ax, %ax
  100         movw    %ax, %ss
  101         movw    $BOOTSTACKOFF, %sp
  102 
  103         /* Relocate so we can load cdboot where we were */
  104         movw    $BOOTSEG, %ax
  105         movw    %ax, %ds
  106         movw    $BOOTRELOCSEG, %ax
  107         movw    %ax, %es
  108         xorw    %si, %si
  109         xorw    %di, %di
  110         movw    $BOOTSECTSIZE, %cx      /* Bytes in cdbr, relocate it all */
  111         cld
  112         rep
  113         movsb
  114 
  115         /* Jump to relocated self */
  116         ljmp $BOOTRELOCSEG, $reloc
  117 reloc:
  118 
  119         /*
  120          * Set up %ds and %es: %ds is our data segment (= %cs), %es is
  121          * used to specify the segment address of the destination buffer
  122          * for cd reads.  We initially have %es = %ds.
  123          */
  124         movw    %cs, %ax
  125         movw    %ax, %ds
  126         movw    %ax, %es
  127 
  128         movb    %dl, drive              /* Store the boot drive number */
  129 
  130         movw    $signon, %si            /* Say "hi", and give boot drive */
  131         call    display_string
  132         movb    drive, %al
  133         call    hex_byte
  134         movw    $crlf, %si
  135         call    display_string
  136 
  137 /*
  138  * Load Volume Descriptor
  139  */
  140         movl    $VOLDESC_LBA, %eax      /* Get the sector # for vol desc */
  141 load_vd:
  142         pushl   %eax
  143         movb    $1, %dh                 /* One sector */
  144         movw    $MEM_VOLDESC, %bx       /* Destination */
  145         call    read                    /* Read it in */
  146         popl    %eax
  147         cmpb    $VD_PRIMARY, (%bx)      /* Primary vol descriptor? */
  148         je      have_vd                 /* Yes */
  149         inc     %eax                    /* Try the next one */
  150         cmpb    $VD_END, (%bx)          /* Is it the last one? */
  151         jne     load_vd                 /* No, so go try the next one */
  152         movw    $msg_novd, %si          /* No pri vol descriptor */
  153         jmp     err_stop                /* Panic */
  154 have_vd:                                /* Have Primary VD */
  155 
  156 /*
  157  * Look for the next-stage loader binary at pre-defined paths (loader_paths)
  158  */
  159         movw    $loader_paths, %si      /* Point to start of array */
  160 lookup_path:
  161         movw    %si, loader             /* remember the one we're looking for */
  162         pushw   %si                     /* Save file name pointer */
  163         call    lookup                  /* Try to find file */
  164         popw    %di                     /* Restore file name pointer */
  165         jnc     lookup_found            /* Found this file */
  166         xorb    %al, %al                /* Look for next */
  167         movw    $0xffff, %cx            /*  path name by */
  168         repnz                           /*  scanning for */
  169         scasb                           /*  nul char */
  170         movw    %di, %si                /* Point %si at next path */
  171         movb    (%si), %al              /* Get first char of next path */
  172         orb     %al, %al                /* Is it double nul? */
  173         jnz     lookup_path             /* No, try it */
  174         movw    $msg_failed, %si        /* Failed message */
  175         jmp     err_stop                /* Print it and halt */
  176 
  177 lookup_found:                           /* Found a loader file */
  178 
  179 /*
  180  * Load the binary into the buffer.  Due to real mode addressing limitations
  181  * we have to read it in in 64k chunks.
  182  */
  183         movl    DIR_SIZE(%bx), %eax     /* Read file length */
  184         add     $SECTOR_SIZE-1, %eax    /* Convert length to sectors */
  185         shr     $SECTOR_SHIFT, %eax
  186         cmp     $BUFFER_LEN, %eax
  187         jbe     load_sizeok
  188         movw    $msg_load2big, %si      /* Error message */
  189         jmp     err_stop
  190 load_sizeok:
  191         movzbw  %al, %cx                /* Num sectors to read */
  192         movl    DIR_EXTENT(%bx), %eax   /* Load extent */
  193         xorl    %edx, %edx
  194         movb    DIR_EA_LEN(%bx), %dl
  195         addl    %edx, %eax              /* Skip extended */
  196 
  197         /* Use %bx to hold the segment (para) number */
  198         movw    $BOOTSEG, %bx           /* We put cdboot here too */
  199 load_loop:
  200         movb    %cl, %dh
  201         cmpb    $MAX_READ_SEC, %cl      /* Truncate to max read size */
  202         jbe     load_notrunc
  203         movb    $MAX_READ_SEC, %dh
  204 load_notrunc:
  205         subb    %dh, %cl                /* Update count */
  206         pushl   %eax                    /* Save */
  207         movw    %bx, %es                /* %bx had the segment (para) number */
  208         xorw    %bx, %bx                /* %es:0000  for destination */
  209         call    read                    /* Read it in */
  210         popl    %eax                    /* Restore */
  211         addl    $MAX_READ_SEC, %eax     /* Update LBA */
  212         addw    $MAX_READ_PARAS, %bx    /* Update dest addr */
  213         jcxz    load_done               /* Done? */
  214         jmp     load_loop               /* Keep going */
  215 load_done:
  216 
  217         /* Now we can start the loaded program */
  218 
  219         movw    loader, %cx             /* Tell cdboot where it is */
  220                                         /* (Older versions of cdbr have */
  221                                         /*  %cx == 0 from the jcxz load_done) */
  222         movb    drive, %dl              /* Get the boot drive number */
  223         ljmp    $BOOTSEG, $0            /* Go run cdboot */
  224 
  225 /*
  226  * Lookup the file in the path at [SI] from the root directory.
  227  *
  228  * Trashes: All but BX
  229  * Returns: CF = 0 (success), BX = pointer to record
  230  *          CF = 1 (not found)
  231  */
  232 lookup:
  233         movw    $VD_ROOTDIR + MEM_VOLDESC, %bx  /* Root directory record */
  234 
  235 lookup_dir:
  236         lodsb                           /* Get first char of path */
  237         cmpb    $0, %al                 /* Are we done? */
  238         je      lookup_done             /* Yes */
  239         cmpb    $'/', %al               /* Skip path separator */
  240         je      lookup_dir
  241         decw    %si                     /* Undo lodsb side effect */
  242         call    find_file               /* Lookup first path item */
  243         jnc     lookup_dir              /* Try next component */
  244         ret
  245 lookup_done:
  246         movw    $msg_loading, %si       /* Success message - say which file */
  247         call    display_string
  248         mov     loader, %si
  249         call    display_string
  250         mov     $crlf, %si
  251         call    display_string
  252         clc                             /* Clear carry */
  253         ret
  254 
  255 /*
  256  * Lookup file at [SI] in directory whose record is at [BX].
  257  *
  258  * Trashes: All but returns
  259  * Returns: CF = 0 (success), BX = pointer to record, SI = next path item
  260  *          CF = 1 (not found), SI = preserved
  261  */
  262 find_file:
  263         mov     DIR_EXTENT(%bx), %eax   /* Load extent */
  264         xor     %edx, %edx
  265         mov     DIR_EA_LEN(%bx), %dl
  266         add     %edx, %eax              /* Skip extended attributes */
  267         mov     %eax, rec_lba           /* Save LBA */
  268         mov     DIR_SIZE(%bx), %eax     /* Save size */
  269         mov     %eax, rec_size
  270         xor     %cl, %cl                /* Zero length */
  271         push    %si                     /* Save */
  272 ff_namelen:
  273         inc     %cl                     /* Update length */
  274         lodsb                           /* Read char */
  275         cmp     $0, %al                 /* Nul? */
  276         je      ff_namedone             /* Yes */
  277         cmp     $'/', %al               /* Path separator? */
  278         jnz     ff_namelen              /* No, keep going */
  279 ff_namedone:
  280         dec     %cl                     /* Adjust length and save */
  281         mov     %cl, name_len
  282         pop     %si                     /* Restore */
  283 ff_load:
  284         mov     rec_lba, %eax           /* Load LBA */
  285         mov     $MEM_DIR, %ebx          /* Address buffer */
  286         mov     $1, %dh                 /* One sector */
  287         call    read                    /* Read directory block */
  288         incl    rec_lba                 /* Update LBA to next block */
  289 ff_scan:
  290         mov     %ebx, %edx              /* Check for EOF */
  291         sub     $MEM_DIR, %edx
  292         cmp     %edx, rec_size
  293         ja      ff_scan_1
  294         stc                             /* EOF reached */
  295         ret
  296 ff_scan_1:
  297         cmpb    $0, DIR_LEN(%bx)        /* Last record in block? */
  298         je      ff_nextblock
  299         push    %si                     /* Save */
  300         movzbw  DIR_NAMELEN(%bx), %si   /* Find end of string */
  301 ff_checkver:
  302         cmpb    $'0', DIR_NAME-1(%bx,%si)       /* Less than '0'? */
  303         jb      ff_checkver_1
  304         cmpb    $'9', DIR_NAME-1(%bx,%si)       /* Greater than '9'? */
  305         ja      ff_checkver_1
  306         dec     %si                     /* Next char */
  307         jnz     ff_checkver
  308         jmp     ff_checklen             /* All numbers in name, so */
  309                                         /*  no version */
  310 ff_checkver_1:
  311         movzbw  DIR_NAMELEN(%bx), %cx
  312         cmp     %cx, %si                /* Did we find any digits? */
  313         je      ff_checkdot             /* No */
  314         cmpb    $';', DIR_NAME-1(%bx,%si)       /* Check for semicolon */
  315         jne     ff_checkver_2
  316         dec     %si                     /* Skip semicolon */
  317         mov     %si, %cx
  318         mov     %cl, DIR_NAMELEN(%bx)   /* Adjust length */
  319         jmp     ff_checkdot
  320 ff_checkver_2:
  321         mov     %cx, %si                /* Restore %si to end of string */
  322 ff_checkdot:
  323         cmpb    $'.', DIR_NAME-1(%bx,%si)       /* Trailing dot? */
  324         jne     ff_checklen                     /* No */
  325         decb    DIR_NAMELEN(%bx)        /* Adjust length */
  326 ff_checklen:
  327         pop     %si                     /* Restore */
  328         movzbw  name_len, %cx           /* Load length of name */
  329         cmp     %cl, DIR_NAMELEN(%bx)   /* Does length match? */
  330         je      ff_checkname            /* Yes, check name */
  331 ff_nextrec:
  332         add     DIR_LEN(%bx), %bl       /* Next record */
  333         adc     $0, %bh
  334         jmp     ff_scan
  335 ff_nextblock:
  336         subl    $SECTOR_SIZE, rec_size  /* Adjust size */
  337         jnc     ff_load                 /* If subtract ok, keep going */
  338         ret                             /* End of file, so not found */
  339 ff_checkname:
  340         lea     DIR_NAME(%bx), %di      /* Address name in record */
  341         push    %si                     /* Save */
  342         repe    cmpsb                   /* Compare name */
  343         jcxz    ff_match                /* We have a winner! */
  344         pop     %si                     /* Restore */
  345         jmp     ff_nextrec              /* Keep looking */
  346 ff_match:
  347         add     $2, %sp                 /* Discard saved %si */
  348         clc                             /* Clear carry */
  349         ret
  350 
  351 /*
  352  * Load DH sectors starting at LBA %eax into address %es:%bx.
  353  *
  354  * Preserves %bx, %cx, %dx, %si, %es
  355  * Trashes %eax
  356  */
  357 read:
  358         pushw   %si                     /* Save */
  359         pushw   %cx                     /* Save since some BIOSs trash */
  360         movl    %eax, edd_lba           /* LBA to read from */
  361         movw    %es, %ax                /* Get the segment */
  362         movw    %ax, edd_addr + 2       /*  and store */
  363         movw    %bx, edd_addr           /* Store offset too */
  364 read_retry:
  365         call    twiddle                 /* Entertain the user */
  366         pushw   %dx                     /* Save */
  367         movw    $edd_packet, %si        /* Address Packet */
  368         movb    %dh, edd_len            /* Set length */
  369         movb    drive, %dl              /* BIOS Device */
  370         movb    $0x42, %ah              /* BIOS: Extended Read */
  371         int     $0x13                   /* Call BIOS */
  372         popw    %dx                     /* Restore */
  373         jc      read_fail               /* Worked? */
  374         popw    %cx                     /* Restore */
  375         popw    %si
  376         ret                             /* Return */
  377 read_fail:
  378         cmpb    $ERROR_TIMEOUT, %ah     /* Timeout? */
  379         je      read_retry              /* Yes, Retry */
  380 read_error:
  381         pushw   %ax                     /* Save error */
  382         movw    $msg_badread, %si       /* "Read error: 0x" */
  383         call    display_string
  384         popw    %ax                     /* Retrieve error code */
  385         movb    %ah, %al                /* Into %al */
  386         call    hex_byte                /* Display error code */
  387         jmp     stay_stopped            /* ... then hang */
  388 
  389 /*
  390  * Display the ASCIZ error message in %esi then halt
  391  */
  392 err_stop:
  393         call    display_string
  394 
  395 stay_stopped:
  396         sti                             /* Ensure Ctl-Alt-Del will work */
  397         hlt                             /* (don't require power cycle) */
  398         jmp     stay_stopped            /* (Just to make sure) */
  399 
  400 /*
  401  * Output the "twiddle"
  402  */
  403 twiddle:
  404         push    %ax                     /* Save */
  405         push    %bx                     /* Save */
  406         mov     twiddle_index, %al      /* Load index */
  407         mov     twiddle_chars, %bx      /* Address table */
  408         inc     %al                     /* Next */
  409         and     $3, %al                 /*  char */
  410         mov     %al, twiddle_index      /* Save index for next call */
  411         xlat                            /* Get char */
  412         call    display_char            /* Output it */
  413         mov     $8, %al                 /* Backspace */
  414         call    display_char            /* Output it */
  415         pop     %bx                     /* Restore */
  416         pop     %ax                     /* Restore */
  417         ret
  418 
  419 /*
  420  * Display the ASCIZ string pointed to by %si.
  421  *
  422  * Destroys %si, possibly others.
  423  */
  424 display_string:
  425         pushw   %ax
  426         cld
  427 1:
  428         lodsb                   /* %al = *%si++ */
  429         testb   %al, %al
  430         jz      1f
  431         call    display_char
  432         jmp     1b
  433 
  434 /*
  435  * Write out value in %eax in hex
  436  */
  437 hex_long:
  438         pushl   %eax
  439         shrl    $16, %eax
  440         call    hex_word
  441         popl    %eax
  442         /* fall thru */
  443 
  444 /*
  445  * Write out value in %ax in hex
  446  */
  447 hex_word:
  448         pushw   %ax
  449         mov     %ah, %al
  450         call    hex_byte
  451         popw    %ax
  452         /* fall thru */
  453 /*
  454  * Write out value in %al in hex
  455  */
  456 hex_byte:
  457         pushw   %ax
  458         shrb    $4, %al
  459         call    hex_nibble
  460         popw    %ax
  461         /* fall thru */
  462 
  463 /* Write out nibble in %al */
  464 hex_nibble:
  465         and     $0x0F, %al
  466         add     $'0', %al
  467         cmpb    $'9', %al
  468         jbe     display_char
  469         addb    $'A'-'9'-1, %al
  470         /* fall thru to display_char */
  471 
  472 /*
  473  * Display the character in %al
  474  */
  475 display_char:
  476         pushw   %ax
  477 
  478         pushw   %bx
  479         movb    $0x0e, %ah
  480         movw    $1, %bx
  481         int     $0x10
  482         popw    %bx
  483 1:      popw    %ax
  484         ret
  485 
  486 /*
  487  * Data
  488  */
  489 drive:          .byte   0                       /* Given to us by the BIOS */
  490 signon:         .asciz  "CD-ROM: "
  491 crlf:           .asciz  "\r\n"
  492 msg_load2big:   .asciz  "File too big"
  493 msg_badread:    .asciz  "Read error: 0x"
  494 msg_novd:       .asciz  "No Primary Volume Descriptor"
  495 msg_loading:    .asciz  "Loading "
  496 
  497 /* State for searching dir */
  498 rec_lba:        .long   0x0                     /* LBA (adjusted for EA) */
  499 rec_size:       .long   0x0                     /* File size */
  500 name_len:       .byte   0x0                     /* Length of current name */
  501 
  502 twiddle_index:  .byte   0x0
  503 twiddle_chars:  .ascii  "|/-\\"
  504 
  505 /* Packet for LBA (CD) read */
  506 edd_packet:     .byte   0x10                    /* Length */
  507                 .byte   0                       /* Reserved */
  508 edd_len:        .byte   0x0                     /* Num to read */
  509                 .byte   0                       /* Reserved */
  510 edd_addr:       .word   0x0, 0x0                /* Seg:Off */
  511 edd_lba:        .quad   0x0                     /* LBA */
  512 
  513 /* The data from here must be last in the file, only followed by 0x00 bytes */
  514 
  515 loader:         .word   0                       /* The path we end up using */
  516 
  517 msg_failed:     .ascii  "Can't find "           /* This string runs into... */
  518 
  519 /* loader_paths is a list of ASCIZ strings followed by a term NUL byte */
  520 loader_paths:   .asciz  "/cdboot"
  521                 .asciz  "/CDBOOT"
  522                 .ascii  "/", OSREV, "/", MACH, "/cdboot"
  523                 .byte   0                       /* NUL-term line above */
  524                 .ascii  "/", OSREV, "/", MACH_U, "/CDBOOT"
  525                 .byte   0                       /* NUL-term line above */
  526                 .byte   0                       /* Terminate the list */
  527 
  528         . = BOOTSECTSIZE
  529 
  530         .end

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