• linux kernel 0.11 bootsect


     

    bootsect作用

     

    ①将自己移动到0x90000处

     

    ②将setup从磁盘读到0x90200处

     

    ③将system从磁盘读到0x10000处

     

    寄存器

    汇编代码中存在:数据段data seg  栈段 stack seg 

    汇编代码中的寄存器概念:

    第一组:

      DS:数据段寄存器  ES:额外数据段寄存器

      SS:栈段寄存器   

      SI:源索引寄存器  DI:目的索引寄存器

      通常 DS:SI和ES:DI配对时通常用来执行一些数据段字符串操作.

      SI和DI两个寄存器叫做索引寄存器, 这两个寄存器通常用来处理数组或字符串.

    第二组:

      BP(base pointer), SP(Stack Pointer), 和IP(Instriction pointer)叫做指针寄存器.

      BP:基指针     SP:栈指针    IP:指令指针

      通常BP用来保存使用局部变量的地址.

      SP用来指向当前的栈. 尽管SP可以被很容易地修改, 你还是一定要非常小心. 因为如果这个寄存器搞错了, 你的程序就毁了.

      IP用来指示当前运行程序的当前指针. 通常和CS一起使用, IP是不允许修改的.

     中断

    系统中断分为BIOS中断和系统中断。所以就存在两个中断向量表。

    其中BIOS中断的int 0x13是磁盘I/O中断。

     

    汇编中的字符串操作

    (1) lodsb、lodsw:把DS:SI指向的存储单元中的数据装入AL或AX,然后根据DF标志增减SI(CLD递增, STD递减)
    (2) stosb、stosw:把AL或AX中的数据装入ES:DI指向的存储单元,然后根据DF标志增减DI(CLD递增, STD递减)
    (3) movsb、movsw:把DS:SI指向的存储单元中的数据装入ES:DI指向的存储单元中,然后根据DF标志分别增减SI和DI
    (4) scasb、scasw:把AL或AX中的数据与ES:DI指向的存储单元中的数据相减,影响标志位,然后根据DF标志分别增减SI和DI
    (5) cmpsb、cmpsw:把DS:SI指向的存储单元中的数据与ES:DI指向的存储单元中的数据相减,影响标志位,然后根据DF标志分别增减SI和DI
    (6) rep:重复其后的串操作指令。重复前先判断CX是否为0,为0就结束重复,否则CX减1,重复其后的串操作指令。 主要用在MOVS和STOS前。一般不用在LODS前。

      上述指令涉及的寄存器:段寄存器DS和ES、变址寄存器SI和DI、累加器AX、计数器CX
          涉及的标志位:DF、AF、CF、OF、PF、SF、ZF

    搬移字串指令有两种,分别是 MOVSB 和 MOVSW,先说 MOVSB。MOVSB 的英文是 move string byte,意思是搬移一个字节,它是把 DS:SI 所指地址的一个字节搬移到 ES:DI 所指的地址上,搬移后原来的内容不变,但是原来 ES:DI 所指的内容会被覆盖而且在搬移之后SI 和 DI 会自动地址向下一个要搬移的地址。

    一般而言,通常程序设计师一般并不会只搬一个字节,通常都会重复许多次,如果要重复的话,就得把重复次数 ( 也就是字串长度 ) 先记录在 CX 寄存器,并且在 MOVSB 之前加上 REP 指令,REP 是重复 (repeat) 的意思。这种写法很是奇怪,一般而言汇编语言源文件的每一行都只有一个指令,但 REP MOVSB 却可以在同一行写两个指令,当然分开写也是一样的。

    1、操作指令功能
       移动 movsb, movsw, movsd   从 ESI 指向的内存位置向 EDI 指向的内存位置拷贝数据  
       比较 cmpsb, cmpsw, cmpsd   把 ESI 指向内存位置的数据和 EDI 指向内存位置拷的数据比较(ESI,EDI都指向相匹配元素的后面的那个元素) 
       搜索 scasb, scasw, scasd   把 al/ax/eax 中的数据与 EDI 寻址的内存数据比较(EDI指向查找到的元素的后面的那个元素) 
       储存 stosb, stosw, stosd   把 al/ax/eax 中的数据保存在 EDI 寻址的内存单元  
       加载 lodsb, lodsw, lodsd   把 ESI 寻址的内存数据加载到 al/ax/eax 中

    2、重复执行前缀
       rep           当 ecx>0 时重复  
       repe, repz    当 ecx>0 ,且 ZF==1 时重复(只用在比较和搜索中)  
       repne,repnz   当 ecx>0 ,且 ZF==0 时重复(只用在比较和搜索中)
      
    3、重复执行方向
       cld    清除 DF 标志,ESI 和 EDI  递增  
       std    设置 DF 标志,ESI 和 EDI  递减
      
    4、字符操作指令格式
       方向               cld, std  
       数据来源             esi,al/ax/eax  
       数据目的             edi,al/ax/eax  
       循环次数             ecx  
       重复前缀 操作指令  rep, repe, repne  movsb, cmpsb, scasb, stosb, lodsb

    bootsect源代码注释

     

      1 !
      2 ! SYS_SIZE is the number of clicks (16 bytes) to be loaded.
      3 ! 0x3000 is 0x30000 bytes = 196kB, more than enough for current
      4 ! versions of linux
      5 !
      6 SYSSIZE = 0x3000            !system模块的大小
      7 !
      8 !    bootsect.s        (C) 1991 Linus Torvalds
      9 !
     10 ! bootsect.s is loaded at 0x7c00 by the bios-startup routines, and moves
     11 ! iself out of the way to address 0x90000, and jumps there.
     12 !
     13 ! It then loads 'setup' directly after itself (0x90200), and the system
     14 ! at 0x10000, using BIOS interrupts. 
     15 !
     16 ! NOTE! currently system is at most 8*65536 bytes long. This should be no
     17 ! problem, even in the future. I want to keep it simple. This 512 kB
     18 ! kernel size should be enough, especially as this doesn't contain the
     19 ! buffer cache as in minix
     20 !
     21 ! The loader has been made as simple as possible, and continuos
     22 ! read errors will result in a unbreakable loop. Reboot by hand. It
     23 ! loads pretty fast by getting whole sectors at a time whenever possible.
     24 
     25 .globl begtext, begdata, begbss, endtext, enddata, endbss    !全局标识符
     26 .text                        !文本段
     27 begtext:                
     28 .data                        !数据段
     29 begdata:                
     30 .bss                        !堆栈段
     31 begbss:
     32 .text
     33 
     34 SETUPLEN = 4                ! nr of setup-sectors    setup程序的扇区数
     35 BOOTSEG  = 0x07c0            ! original address of boot-sector    
     36 INITSEG  = 0x9000            ! we move boot here - out of the way
     37 SETUPSEG = 0x9020            ! setup starts here
     38 SYSSEG   = 0x1000            ! system loaded at 0x10000 (65536).
     39 ENDSEG   = SYSSEG + SYSSIZE        ! where to stop loading
     40                                                             !    从0x10000加载system模块,大小为
     41 ! ROOT_DEV:    0x000 - same type of floppy as boot.
     42 !        0x301 - first partition on first drive etc
     43 ROOT_DEV = 0x306                            !根文件系统的在第二盘第一分区上
     44 
     45 entry start                                        !连接程序从start处开始执行
     46 start:
     47                                                             ! 47--56 行作用是将自身(bootsect) 从目前段位置 0x07c0(31k)
     48                                                             ! 移动到 0x9000(576k)处,共 256 字(512 字节),然后跳转到
     49                                                           ! 移动后代码的 go 标号处,也即本程序的下一语句处。
     50     mov    ax,#BOOTSEG
     51     mov    ds,ax                                        !    ds=07c0
     52     mov    ax,#INITSEG
     53     mov    es,ax                                        !    es=9000
     54     mov    cx,#256                                    !    cx=256=bootsect大小
     55     sub    si,si
     56     sub    di,di
     57     rep                                                    !    rep movb或rep movw根据cx的值,重复执行串传送指令
     58     movw                                                !    movw,串传送指令,将ds:si指向的内存单元的字数据送入到es:di中,将si和di增2
     59     jmpi    go,INITSEG                        !    jmp是段内跳转指令,而jmpi是段间跳转指令,所以需要提供段地址(第二个操作数)。
     60                                                             !    即jmpi的第一个操作数是段内偏移地址;第二个是跳转到的段地址。
     61 go:    mov    ax,cs                                    !    CS存放指令的段地址,此时已经为9000,IP存放指令的偏移地址。
     62     mov    ds,ax                                        !    将ds    es    ss指向新的代码段
     63     mov    es,ax                                        !    因为程序设计堆栈操作,所以必须设置堆栈
     64 ! put stack at 0x9ff00.
     65     mov    ss,ax
     66     mov    sp,#0xFF00        ! arbitrary value >>512
     67                                                             ! ?
     68                                                             !    栈指针指向9ff00处,因为90200处放setup,setup大约占4个扇区
     69                                                             !    所以sp指向,(200+200*4+堆栈大小)之外
     70 ! load the setup-sectors directly after the bootblock.
     71 ! Note that 'es' is already set up.
     72 
     73 load_setup:                                        !    cs指令的段基址+ip就指向了这里。
     74                                                             ! 68--77 行的用途是利用 BIOS 中断 INT 0x13 将 setup 模块从磁盘第 2 个扇区  
     75                                                             ! 开始读到 0x90200 开始处,共读 4 个扇区。如果读出错,则复位驱动器,并    
     76                                                             ! 重试,没有退路。INT 0x13 的使用方法如下:                               
     77                                                             ! 读扇区:                                                                
     78                                                             ! ah = 0x02 - 读磁盘扇区到内存;al = 需要读出的扇区数量;                 
     79                                                             ! ch = 磁道(柱面)号的低 8 位; cl = 开始扇区(0-5 位),磁道号高 2 位(6-7);
     80                                                             ! dh = 磁头号; dl = 驱动器号(如果是硬盘则要置位 7);                   
     81                                                             ! es:bx 指向数据缓冲区; 如果出错则 CF 标志置位。 
     82                                                             !    INT 13h / AH = 02h - read disk sectors into memory.
     83                                                             !    input:
     84                                                             !    AL = number of sectors to read/write (must be nonzero)
     85                                                             !    CH = cylinder number (0..79).
     86                                                             !    CL = sector number (1..18).
     87                                                             !    DH = head number (0..1).
     88                                                             !    DL = drive number (0..3 , depends on quantity of FLOPPY_? files).
     89                                                             !    ES:BX points to data buffer.
     90                                                             !    return:
     91                                                             !    CF set on error.
     92                                                             !    CF clear if successful.
     93                                                             !    AH = status (0 - if successful).
     94                                                             !    AL = number of sectors transferred. 
     95                                                             !    Note: each sector has 512 bytes.  
     96                                                             !    将从0磁道第二2扇区开始,读取4个扇区的数据到ES:BX指定的内存中。                     
     97     mov    dx,#0x0000        ! drive 0, head 0                        dx=dl+dh
     98     mov    cx,#0x0002        ! sector 2, track 0                    cx=cl+ch
     99     mov    bx,#0x0200        ! address = 512, in INITSEG    es+bx=090200,
    100     mov    ax,#0x0200+SETUPLEN    ! service 2, nr of sectors    读磁盘的位置+读取的扇区数目
    101     int    0x13            ! read it            产生中断,AH为入口参数,将数据读入,读取完毕!加载setup完毕!
    102     jnc    ok_load_setup        ! ok - continue    跳转 有添加跳转,如果中断操作成功,则输出system loading....
    103     mov    dx,#0x0000            !    否则复位磁盘,重新读取setup模块
    104     mov    ax,#0x0000        ! reset the diskette    复位磁盘
    105     int    0x13
    106     j    load_setup            !    无条件跳转
    107 
    108 ok_load_setup:                                !?
    109 
    110 ! Get disk drive parameters, specifically nr of sectors/track
    111 
    112     mov    dl,#0x00
    113     mov    ax,#0x0800        ! AH=8 is get drive parameters
    114     int    0x13
    115     mov    ch,#0x00
    116     seg cs
    117     mov    sectors,cx
    118     mov    ax,#INITSEG
    119     mov    es,ax
    120 
    121 ! Print some inane message
    122 
    123     mov    ah,#0x03        ! read cursor pos
    124     xor    bh,bh
    125     int    0x10
    126     
    127     mov    cx,#24
    128     mov    bx,#0x0007        ! page 0, attribute 7 (normal)
    129     mov    bp,#msg1            !    显示加载system
    130     mov    ax,#0x1301        ! write string, move cursor
    131     int    0x10
    132 
    133 ! ok, we've written the message, now
    134 ! we want to load the system (at 0x10000)
    135 
    136     mov    ax,#SYSSEG
    137     mov    es,ax        ! segment of 0x010000
    138     call    read_it            !子程序调用,读取system,es为参数
    139     call    kill_motor
    140 
    141 ! After that we check which root-device to use. If the device is
    142 ! defined (!= 0), nothing is done and the given device is used.
    143 ! Otherwise, either /dev/PS0 (2,28) or /dev/at0 (2,8), depending
    144 ! on the number of sectors that the BIOS reports currently.
    145 
    146     seg cs
    147     mov    ax,root_dev
    148     cmp    ax,#0
    149     jne    root_defined
    150     seg cs
    151     mov    bx,sectors
    152     mov    ax,#0x0208        ! /dev/ps0 - 1.2Mb
    153     cmp    bx,#15
    154     je    root_defined
    155     mov    ax,#0x021c        ! /dev/PS0 - 1.44Mb
    156     cmp    bx,#18
    157     je    root_defined
    158 undef_root:
    159     jmp undef_root
    160 root_defined:
    161     seg cs
    162     mov    root_dev,ax
    163 
    164 ! after that (everyting loaded), we jump to
    165 ! the setup-routine loaded directly after
    166 ! the bootblock:
    167 
    168     jmpi    0,SETUPSEG
    169 
    170 ! This routine loads the system at address 0x10000, making sure
    171 ! no 64kB boundaries are crossed. We try to load it as fast as
    172 ! possible, loading whole tracks whenever we can.
    173 !
    174 ! in:    es - starting address segment (normally 0x1000)
    175 !
    176 sread:    .word 1+SETUPLEN    ! sectors read of current track    
    177                                                     !    开始读取system在磁盘的开始扇区标号
    178                                                     !    1:bootsect mbr主引导扇区
    179                                                     !    SETUPLEN:setup所占的扇区数
    180                                                     !sread:读取system开始的扇区数
    181 head:    .word 0            ! current head
    182 track:    .word 0            ! current track
    183 
    184 read_it:
    185     mov ax,es
    186     test ax,#0x0fff        !    0x1000&&0x0ffff
    187 die:    jne die            ! es must be at 64kB boundary    如果不在0x10000处,则进入死循环
    188     xor bx,bx        ! bx is starting address within segment
    189 rp_read:
    190     mov ax,es
    191     cmp ax,#ENDSEG        ! have we loaded all yet?
    192     jb ok1_read                !    如果未结束,继续读取
    193     ret
    194 ok1_read:
    195     seg cs                        !    不想使用默认的段地址寄存器,那么你可以强制指定一个段地址寄存器
    196     mov ax,sectors        !    读取磁道的扇区数
    197     sub ax,sread            !    减去已读的磁道扇区数
    198     mov cx,ax                    !    cx=未读的扇区数
    199     shl cx,#9                    !    逻辑左移指令    cx=cx*512
    200     add cx,bx                    
    201     jnc ok2_read
    202     je ok2_read
    203     xor ax,ax
    204     sub ax,bx
    205     shr ax,#9
    206 ok2_read:
    207     call read_track
    208     mov cx,ax
    209     add ax,sread
    210     seg cs
    211     cmp ax,sectors
    212     jne ok3_read
    213     mov ax,#1
    214     sub ax,head
    215     jne ok4_read
    216     inc track
    217 ok4_read:
    218     mov head,ax
    219     xor ax,ax
    220 ok3_read:
    221     mov sread,ax
    222     shl cx,#9
    223     add bx,cx
    224     jnc rp_read
    225     mov ax,es
    226     add ax,#0x1000
    227     mov es,ax
    228     xor bx,bx
    229     jmp rp_read
    230 
    231 read_track:
    232     push ax
    233     push bx
    234     push cx
    235     push dx
    236     mov dx,track
    237     mov cx,sread
    238     inc cx
    239     mov ch,dl
    240     mov dx,head
    241     mov dh,dl
    242     mov dl,#0
    243     and dx,#0x0100
    244     mov ah,#2
    245     int 0x13
    246     jc bad_rt
    247     pop dx
    248     pop cx
    249     pop bx
    250     pop ax
    251     ret
    252 bad_rt:    mov ax,#0
    253     mov dx,#0
    254     int 0x13
    255     pop dx
    256     pop cx
    257     pop bx
    258     pop ax
    259     jmp read_track
    260 
    261 !/*
    262 ! * This procedure turns off the floppy drive motor, so
    263 ! * that we enter the kernel in a known state, and
    264 ! * don't have to worry about it later.
    265 ! */
    266 kill_motor:
    267     push dx
    268     mov dx,#0x3f2
    269     mov al,#0
    270     outb
    271     pop dx
    272     ret
    273 
    274 sectors:
    275     .word 0
    276 
    277 msg1:
    278     .byte 13,10
    279     .ascii "Loading system ..."
    280     .byte 13,10,13,10
    281 
    282 .org 508
    283 root_dev:
    284     .word ROOT_DEV
    285 boot_flag:
    286     .word 0xAA55
    287 
    288 .text
    289 endtext:
    290 .data
    291 enddata:
    292 .bss
    293 endbss:
  • 相关阅读:
    小记2_finddata_t结构体
    小记1
    2014-1-2 笔记
    _RecordsetPtr的 open函数
    SAFEARRAY
    用VC实现特定编辑框上对回车键响应
    常用控件的常用消息
    单文档与多文档
    java中得到json格式的数据
    form表单验证时的onsubmit事件
  • 原文地址:https://www.cnblogs.com/cz-blog/p/4752203.html
Copyright © 2020-2023  润新知