Linux1.0 kernel bootsect.S 学习日记

参考:

http://www.chinaunix.net/old_jh/4/130640.html

http://www.doc88.com/p-587672394556.html

http://zhidao.baidu.com/question/102135062.html

http://www.doc88.com/p-032414683132.html


!

! SYS_SIZE is the number of clicks (16 bytes) to be loaded.
! 0x7F00 is 0x7F000 bytes = 508kB, more than enough for current
! versions of linux which compress the kernel
!
#include <linux/config.h>
SYSSIZE = DEF_SYSSIZE
!
!    bootsect.s        Copyright (C) 1991, 1992 Linus Torvalds
!    modified by Drew Eckhardt
!    modified by Bruce Evans (bde)
!
! bootsect.s is loaded at 0x7c00 by the bios-startup routines, and moves
! itself out of the way to address 0x90000, and jumps there.
!
! bde - should not jump blindly, there may be systems with only 512K low
! memory.  Use int 0x12 to get the top of memory, etc.
!
! It then loads 'setup' directly after itself (0x90200), and the system
! at 0x10000, using BIOS interrupts.
!
! NOTE! currently system is at most (8*65536-4096) bytes long. This should
! be no problem, even in the future. I want to keep it simple. This 508 kB
! kernel size should be enough, especially as this doesn't contain the
! buffer cache as in minix (and especially now that the kernel is
! compressed :-)
!
! The loader has been made as simple as possible, and continuos
! read errors will result in a unbreakable loop. Reboot by hand. It
! loads pretty fast by getting whole tracks at a time whenever possible.

.text

SETUPSECS = 4                ! nr of setup-sectors
BOOTSEG   = 0x07C0            ! original address of boot-sector
INITSEG   = DEF_INITSEG            ! we move boot here - out of the way
SETUPSEG  = DEF_SETUPSEG        ! setup starts here
SYSSEG    = DEF_SYSSEG            ! system loaded at 0x10000 (65536).

! ROOT_DEV & SWAP_DEV are now written by "build".
ROOT_DEV = 0
SWAP_DEV = 0
#ifndef SVGA_MODE
#define SVGA_MODE ASK_VGA
#endif
#ifndef RAMDISK
#define RAMDISK 0
#endif
#ifndef CONFIG_ROOT_RDONLY
#define CONFIG_ROOT_RDONLY 0
#endif

! ld86 requires an entry symbol. This may as well be the usual one.
.globl    _main
_main:
#if 0 /* hook for debugger, harmless unless BIOS is fussy (old HP) */
    int    3
#endif
    //启动时BIOS会将磁盘上的0磁道上的第一个扇区读入内存,即bootsect
    //对于int 13来说,磁道上的扇区号是从1开始的,而不是0.
    mov    ax,#BOOTSEG
    mov    ds,ax
    mov    ax,#INITSEG
    mov    es,ax
    mov    cx,#256
    sub    si,si
    sub    di,di
    cld
    rep
    movsw
    jmpi    go,INITSEG

go:    mov    ax,cs        
    mov    dx,#0x4000-12    ! 0x4000 is arbitrary value >= length of
                ! bootsect + length of setup + room for stack
                ! 12 is disk parm size

! bde - changed 0xff00 to 0x4000 to use debugger at 0x6400 up (bde).  We
! wouldn't have to worry about this if we checked the top of memory.  Also
! my BIOS can be configured to put the wini drive tables in high memory
! instead of in the vector table.  The old stack might have clobbered the
! drive table.

    mov    ds,ax
    mov    es,ax
    mov    ss,ax        ! put stack at INITSEG:0x4000-12.
    mov    sp,dx
/*
 *    Many BIOS's default disk parameter tables will not
 *    recognize multi-sector reads beyond the maximum sector number
 *    specified in the default diskette parameter tables - this may
 *    mean 7 sectors in some cases.
 *
 *    Since single sector reads are slow and out of the question,
 *    we must take care of this by creating new parameter tables
 *    (for the first disk) in RAM.  We will set the maximum sector
 *    count to 18 - the most we will encounter on an HD 1.44.  
 *
 *    High doesn't hurt.  Low does.
 *
 *    Segments are as follows: ds=es=ss=cs - INITSEG,
 *        fs = 0, gs = parameter table segment
 */

    push    #0
    pop    fs
    //0x78到0x80,0x81四个字节中存放着磁盘参数表的地址
    mov    bx,#0x78        ! fs:bx is parameter table address
    seg fs
    lgs    si,(bx)            ! gs:si is source

    mov    di,dx            ! es:di is destination
    mov    cx,#6            ! copy 12 bytes
    cld

    //将初始的磁盘参数列表里的内容(12个字节)复制一份到INITSEG:0x4000-12开始的12个字节里
    rep
    seg gs
    movsw

    mov    di,dx
    //在复制的磁盘参数表中,Sector count(即最大扇区数)对应的内存大小为1 byte,偏移量为4.
    //所以要将磁盘参数表中的最大扇区数改为18,ds:[di+4]处赋值为18
    movb    4(di),*18        ! patch sector count

    //然后在0x78处修改磁盘参数表的地址为新的赋值后的地址INITSEG:0x4000-12
    seg fs
    mov    (bx),di
    seg fs
    mov    2(bx),es

    mov    ax,cs
    mov    fs,ax
    mov    gs,ax
    
    xor    ah,ah            ! reset FDC
    xor    dl,dl
    int     0x13    

! load the setup-sectors directly after the bootblock.
! Note that 'es' is already set up.

load_setup:
    xor    dx, dx            ! drive 0, head 0
    //从0磁道的第2扇区开始读setup(0磁道的第1扇区是bootsect)
    mov    cx,#0x0002        ! sector 2, track 0
    mov    bx,#0x0200        ! address = 512, in INITSEG
    mov    ax,#0x0200+SETUPSECS    ! service 2, nr of sectors
                    ! (assume all on head 0, track 0)
    int    0x13            ! read it
    jnc    ok_load_setup        ! ok - continue

    push    ax            ! dump error code
    call    print_nl
    mov    bp, sp
    call    print_hex
    pop    ax    
    
    xor    dl, dl            ! reset FDC
    xor    ah, ah
    int    0x13
    jmp    load_setup

ok_load_setup:

! Get disk drive parameters, specifically nr of sectors/track
//取得磁盘驱动器参数,特别是每个磁道的扇区数(nr即number的缩写,/track表示每个磁道的意思);

#if 0

! bde - the Phoenix BIOS manual says function 0x08 only works for fixed
! disks.  It doesn't work for one of my BIOS's (1987 Award).  It was
! fatal not to check the error code.

    xor    dl,dl
    mov    ah,#0x08        ! AH=8 is get drive parameters
    int    0x13
    xor    ch,ch
#else

! It seems that there is no BIOS call to get the number of sectors.  Guess
! 18 sectors if sector 18 can be read, 15 if sector 15 can be read.
! Otherwise guess 9.

    xor    dx, dx            ! drive 0, head 0
    mov    cx,#0x0012        ! sector 18, track 0
    mov    bx,#0x0200+SETUPSECS*0x200  ! address after setup (es = cs)
    mov    ax,#0x0201        ! service 2, 1 sector
    int    0x13
    //先尝试读0磁头,0磁道的第18个扇区,如果成功,则认为每个磁道的扇区数为18.否则,尝试15。如果失败,则默认就为9了。
    jnc    got_sectors
    mov    cl,#0x0f        ! sector 15
    mov    ax,#0x0201        ! service 2, 1 sector
    int    0x13
    jnc    got_sectors
    mov    cl,#0x09

#endif

got_sectors:
    seg cs
    mov    sectors,cx
    mov    ax,#INITSEG
    mov    es,ax

! Print some inane message

    mov    ah,#0x03        ! read cursor pos
    xor    bh,bh
    int    0x10
    
    mov    cx,#9
    mov    bx,#0x0007        ! page 0, attribute 7 (normal)
    mov    bp,#msg1
    mov    ax,#0x1301        ! write string, move cursor
    int    0x10

! ok, we've written the message, now
! we want to load the system (at 0x10000)
    //开始去load系统了
    mov    ax,#SYSSEG
    mov    es,ax        ! segment of 0x010000
    call    read_it
    call    kill_motor
    call    print_nl

! After that we check which root-device to use. If the device is
! defined (!= 0), nothing is done and the given device is used.
! Otherwise, either /dev/PS0 (2,28) or /dev/at0 (2,8), depending
! on the number of sectors that the BIOS reports currently.

    //如果没有定义根设备,则根据每个磁道上的扇区数来判断根设备
    //不过根设备判断出来干什么用呢?目前我还没看到
    seg cs
    mov    ax,root_dev
    or    ax,ax
    jne    root_defined
    seg cs
    mov    bx,sectors
    mov    ax,#0x0208        ! /dev/ps0 - 1.2Mb
    cmp    bx,#15
    je    root_defined
    mov    ax,#0x021c        ! /dev/PS0 - 1.44Mb
    cmp    bx,#18
    je    root_defined
    mov    ax,#0x0200        ! /dev/fd0 - autodetect
root_defined:
    seg cs
    mov    root_dev,ax

! after that (everyting loaded), we jump to
! the setup-routine loaded directly after
! the bootblock:

    jmpi    0,SETUPSEG  -----jump到setup模块去执行,setup模块的起始地址:0x9000*16 + bootsec的大小512字节=0x90000+0x200=0x90200,所以SETUPSEG=0x9020

! This routine loads the system at address 0x10000, making sure
! no 64kB boundaries are crossed. We try to load it as fast as
! possible, loading whole tracks whenever we can.
!
! in:    es - starting address segment (normally 0x1000)
!
sread:    .word 1+SETUPSECS    ! sectors read of current track  ----0磁道的第1扇区是bootsect,紧接着的4个扇区是setup模块。所以在读system模块前的已读扇区数为5.
head:    .word 0            ! current head
track:    .word 0            ! current track

//load system模块的时候限制:
//1> 13h中断一次只能读取同一磁道上的一个或多个扇区
//2> 因为是实模式下,所以内存段的大小不能超过64k
//因为上述限制,所以每次在读之前,我们取当前磁道上剩余扇区的空间大小和当前的这个段64k中的剩余空间大小。
//然后比较这两个空间大小,如果当前磁道上剩余的扇区空间小,则用磁道的最大扇区数减去此磁道上的已读扇区数得到此次要读的扇区数;
//如果当前段64k中剩余的空间小,则用这个较小的字节值除以512就得到了此次要读扇区大小。

//磁盘的读取规则:
//当0磁头的某个磁道读完,下一次就读1磁头的相同磁道;当1磁头的某个磁道读完,下一次就读0磁头的下一个磁道。
//例如,0磁头0磁道,1磁头0磁道;0磁头1磁道,1磁头1磁道。

read_it:
    mov ax,es   -----es的值为0x1000
    test ax,#0x0fff  ----es的值和0x0fff做与运算后必须为0,而值0x1000是满足这个条件的。不过0x2000也满足这个条件呢,^_^
die:    jne die            ! es must be at 64kB boundary
    xor bx,bx        ! bx is starting address within segment
rp_read:
    mov ax,es  ---es的值为0x1000
    sub ax,#SYSSEG ---第一次执行时,ax为0x1000,SYSSEG也为0x1000
    //由于es的段值变化只能是以64k为单位,即为0x1000,0x2000,0x3000……,0x9000,不可能为0x7F00。这几个段之间的间隔内存大小刚好都是64k

    //而syssize的大小为0x7F00,所以加载系统时不可能准确地加载到0x7F00大小,只可能是加载到比它大一点点的大小0x8000(es=0x9000,es-0x1000=0x8000,0x8000 > 0x7F00).1000~9000大小为8×64k=512k,比实际的508k要大一点。

    //syssize大小指定的是段值(segment)的大小,而不是说整个system模块的size,syssize*16才是system模块的大小508k。
    cmp ax,syssize        ! have we loaded all yet?
    jbe ok1_read  ---当前的segment段值小于等于syssize,表示还没有读完system模块,就继续读;否则就不读了。
    ret
ok1_read:
    seg cs
    mov ax,sectors ----sectors=每个磁道的扇区数
    sub ax,sread  -----减去当前磁道已读扇区数得到可读的扇区数并存在ax中,al=当前磁道未读的扇区数(ah=0)
    mov cx,ax
    shl cx,#9 -----乘512,cx = 当前磁道未读的字节数
    add cx,bx  -------加上当前段内偏移值,es:bx为当前读入的数据缓冲区地址
    jnc ok2_read   ----如果cx+bx没有进位,则表示当前段内再读入cx这么多的字节数也不会超过64k的,即取当前磁道上的所有扇区为这次要读入的扇区数。
    je ok2_read  ----如果有进位,但是cx+bx结果为0,则表示cx+bx刚好等于64k(1 00000000 00000000=2的16次方=64k),即取当前磁道上的所有扇区为这次要读入的扇区数。
    //否则如果进位且cx+bx结果不为0,则表示当前磁道上的所有扇区大小加上bx要大于64k,则取当前段的剩余空间除以512(每个扇区的size大小为512byte)等到这次要读的扇区数
    //sub命令运算时,认为bx中的数据都是以补码的形式存在的,0 - bx = 0 + (-bx)的补码=(-bx)的补码
    //而(-bx)的补码的求值方式就是把bx中的每一位(包括最高位即符号位)取反,末位加1.因为bx和(-bx)的反码按二进制相加的话就是FFFF,即和为65535.那么加1的话即为65536=64k。
    //那么就是(-bx)的反码 + 1 =64k - bx,即为当前段的剩余字节。
    //如果bx为0时,则求出来的剩余字节数就为0,显然不对。不过不用担心,因为如果bx为0,则实际剩余字节数为64k,则jnc ok2_read肯定会成立。因为最大扇区数18×512要小于64k的。
    //这里通过bx中的已读的字节数来求当前段中的剩余字节数的方法是相当的灵巧。
    xor ax,ax   
    sub ax,bx
    shr ax,#9
ok2_read:
    call read_track
    mov cx,ax    ----ax中为此次读取的扇区数
    add ax,sread ----已经读的扇区数sread加上此次read_track中读的扇区数,得到现在总共已读的扇区数并存放在ax中。
    seg cs
    cmp ax,sectors  ----比较当前的磁道上的已读扇区数和磁道的最大扇区值,看是否已经读完此磁道上的所有扇区。
    jne ok3_read  ---如果还没有读完当前磁道上的所有扇区,则继续读。
    //如果已经读完了当前磁道的所有扇区,则指定下一个要读的磁道。
    mov ax,#1
    sub ax,head
    jne ok4_read  ----如果当前磁头是0,则下一个要读的磁道就是1磁头的相同磁道。
    inc track  ---如果当前磁头是1,则下一个要的读的磁道就是0磁头的下一个磁道,所以track加1。
ok4_read:
    mov head,ax
    xor ax,ax
ok3_read:
    mov sread,ax   ---ax中为已经读的总的扇区数
    shl cx,#9  ---cx中为此次读的扇区数,乘以512,得到此次读的总的字节数
    add bx,cx  ---算出当前段的偏移量,bx加上此次所读的当前磁道的总的字节数即为当前偏移量。
    //如果是有进位的(产生进位的分支就是je ok2_read和读当前段的剩余空间这两个分支的时候),这时就是说刚好时当前段的64k用完了,要先换到下一个段,然后继续循环读;
    jnc rp_read  ----//如果没有进位,表示当前段的64k未用完,继续循环读。
    //否则指定下一个段
    mov ax,es
    add ah,#0x10  ----进入下一个段
    mov es,ax
    xor bx,bx
    jmp rp_read  ----指定下一个段后,继续循环读。

read_track:
    pusha ----pusha两次,后面popa两次
    pusha    
    mov    ax, #0xe2e     ! loading... message 2e = .
    mov    bx, #7
     int    0x10
    popa        

    mov    dx,track  -----track = 当前磁道
    mov    cx,sread  ----sread为当前磁道已读的扇区数
    inc    cx        ----cl=扇区号,接下来要读的当前磁道上的多个扇区的起始扇区号
    mov    ch,dl
    mov    dx,head
    mov    dh,dl
    and    dx,#0x0100
    mov    ah,#2  ---ok1_read中已经给al赋值,其值为当前磁道上未读的扇区数
    
    push    dx                ! save for error dump
    push    cx
    push    bx
    push    ax

    int    0x13
    jc    bad_rt
    add    sp, #8
    popa
    ret

bad_rt:    push    ax                ! save error code
    call    print_all            ! ah = error, al = read
    
    
    xor ah,ah
    xor dl,dl
    int 0x13
    

    add    sp, #10
    popa    
    jmp read_track

/*
 *    print_all is for debugging purposes.  
 *    It will print out all of the registers.  The assumption is that this is
 *    called from a routine, with a stack frame like
 *    dx
 *    cx
 *    bx
 *    ax
 *    error
 *    ret <- sp
 *
*/
 
print_all:
    mov    cx, #5        ! error code + 4 registers
    mov    bp, sp    

print_loop:
    push    cx        ! save count left
    call    print_nl    ! nl for readability

    cmp    cl, 5
    jae    no_reg        ! see if register name is needed
    
    mov    ax, #0xe05 + 'A - 1
    sub    al, cl
    int    0x10

    mov    al, #'X
    int    0x10

    mov    al, #':
    int    0x10

no_reg:
    add    bp, #2        ! next register
    call    print_hex    ! print it
    pop    cx
    loop    print_loop
    ret

print_nl:
    mov    ax, #0xe0d    ! CR
    int    0x10
    mov    al, #0xa    ! LF
    int     0x10
    ret

/*
 *    print_hex is for debugging purposes, and prints the word
 *    pointed to by ss:bp in hexadecmial.
*/

print_hex:
    mov    cx, #4        ! 4 hex digits
    mov    dx, (bp)    ! load word into dx
print_digit:
    rol    dx, #4        ! rotate so that lowest 4 bits are used
    mov    ah, #0xe    
    mov    al, dl        ! mask off so we have only next nibble
    and    al, #0xf
    add    al, #'0        ! convert to 0-based digit
    cmp    al, #'9        ! check for overflow
    jbe    good_digit
    add    al, #'A - '0 - 10

good_digit:
    int    0x10
    loop    print_digit
    ret


/*
 * This procedure turns off the floppy drive motor, so
 * that we enter the kernel in a known state, and
 * don't have to worry about it later.
 */
kill_motor:
    push dx
    mov dx,#0x3f2
    xor al, al
    outb
    pop dx
    ret

sectors:
    .word 0

msg1:
    .byte 13,10
    .ascii "Loading"

.org 498
root_flags:
    .word CONFIG_ROOT_RDONLY
syssize:
    .word SYSSIZE
swap_dev:
    .word SWAP_DEV
ram_size:
    .word RAMDISK
vid_mode:
    .word SVGA_MODE
root_dev:
    .word ROOT_DEV
boot_flag:
    .word 0xAA55

评论
添加红包

请填写红包祝福语或标题

红包个数最小为10个

红包金额最低5元

当前余额3.43前往充值 >
需支付:10.00
成就一亿技术人!
领取后你会自动成为博主和红包主的粉丝 规则
hope_wisdom
发出的红包
实付
使用余额支付
点击重新获取
扫码支付
钱包余额 0

抵扣说明:

1.余额是钱包充值的虚拟货币,按照1:1的比例进行支付金额的抵扣。
2.余额无法直接购买下载,可以购买VIP、付费专栏及课程。

余额充值