bootsect.S-중국어 주석(linux-0.12)

32720 단어 운영 체제
... 에서 얻다https://github.com/ultraji/linux-0.12
!
! SYS_SIZE is the number of clicks (16 bytes) to be loaded.
! SYS_SIZE            (    ,   16  )。
! 0x3000 is 0x30000 bytes = 196kB, more than enough for current
!   0x30000 bytes = 192 KB(  , 1000196KB),     
!         。
!   ,     0x8000512KB。
! versions of linux
!
#include 
!
!                      Linus               。
!   :
! DEF_SYSSIZE = 0X3000       
! DEF_INITSEG = 0x9000               
! DEF_SETUPSEG = 0x9020 setup        
! DEF_SYSSEG = 0x1000                 
!
SYSSIZE = DEF_SYSSIZE
!
!   bootsect.s      (C) 1991 Linus Torvalds
!   modified by Drew Eckhardt
!
! bootsect.s is loaded at 0x7c00 by the bios-startup routines, and moves
! iself out of the way to address 0x90000, and jumps there.
!
! It then loads 'setup' directly after itself (0x90200), and the system
! at 0x10000, using BIOS interrupts. 
!
! NOTE! currently system is at most 8*65536 bytes long. This should be no
! problem, even in the future. I want to keep it simple. This 512 kB
! kernel size should be enough, especially as this doesn't contain the          '
! buffer cache as in minix
!
! 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 sectors at a time whenever possible.

!             :
!   bootsect.s  (C) 1991 Linus Torvalds     
!   Drew Eckhardt   
!
!  bootsect.s  BIOS         0x7c00 (31KB) ,        
!   0x90000(576KB) ,      。
!
!      BIOS    'setup'          (0x90200)(576.5KB),
!    system       0x10000  。
!
!   !               (8*65536)(512KB)  ,      
!          。          。  512KB         
!    ,        MINIX            。
!
!             ,                。      。
!     ,           ,           。

.globl begtext, begdata, begbss, endtext, enddata, endbss
.text
begtext:
.data
begdata:
.bss
begbss:
.text

SETUPLEN = 4                ! nr of setup-sectors 
                            ! setup         
BOOTSEG  = 0x07c0           ! original address of boot-sector
                            ! bootsect         ( BIOS        )
INITSEG  = DEF_INITSEG          ! we move boot here - out of the way
                                ! bootsect           ,           
SETUPSEG = DEF_SETUPSEG         ! setup starts here
                                ! setup           
SYSSEG   = DEF_SYSSEG           ! system loaded at 0x10000 (65536).
                                ! system         0x10000
ENDSEG   = SYSSEG + SYSSIZE     ! where to stop loading
                                !         

! ROOT_DEV & SWAP_DEV are now written by "build".
!          ROOT_DEV         SWAP_DEV     tools      build     。
!            :
!    =    *256 +     (   dev_no = ( major <<8 ) + minor )
! (    :1-  ,2-  ,3-  ,4-ttyx,5-tty,6-   ,7-     )
! 0x300 - /dev/hd0 -       1    ;
! 0x301 - /dev/hd1 -   1      1    ;
! …
! 0x304 - /dev/hd4 -   1      4    ;
! 0x305 - /dev/hd5 -       2     ;
! 0x306 - /dev/hd6 -   2      1    ;
! …
! 0x309 - /dev/hd9 -   2      4    ;
!   Linux    0.95                  。
ROOT_DEV = 0    !                     。
SWAP_DEV = 0    !                。

entry start     !       ,    start        。
start:
    !    (bootsect)      (  0x7c00 )    0x90000256   。
    mov ax,#BOOTSEG
    mov ds,ax
    mov ax,#INITSEG
    mov es,ax
    mov cx,#256
    sub si,si       !     ds:si = 0x07c0:0x0000;
    sub di,di       !      es:di = 0x9000:0x0000;
    rep
    movw            !      ,         0x9000,  go   
                    !  jump  ,        ,          ,   0x9000:go 。
    jmpi    go,INITSEG      !     (Jump Intersegment)。INITSEG         ,
                            !    go        ;
    !
    !   go    ,CPU      0x90000         。
    !                ,       ss   sp。
    !   :    BIOS         0x7c00             ,ss = 0x00,sp = 0xfffe;
    !     push ax                ,                    , 
    !   fs   gs   ,     2          ,             ,      
    !   。      bug,  :    push ax,     pop ax    mov ax,cs 。
    !          push ax      2   (      )  。
go: mov ax,cs       
    mov dx,#0xfef4  ! arbitrary value >>512 - disk parm size
                    !        512    (  0x90200 )    ;
                    !   setup      4       sp     
                    ! ( 0x90200 +0x200 * 4 +     )。   sp     
                    !   0x9ff00 - 12(     ),  sp = 0xfef4。
    mov ds,ax
    mov es,ax
    push    ax      !       ( 0x9000 ),       。

    mov ss,ax       ! put stack at 0x9ff00 - 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
 */
/*
 *                                  ,   BIOS
 *          。       7   。
 *
 *           ,    。                  (  1    )
 *        。              181.44MB           。
 *
 *         ,       。
 *
 *          :ds = es = ss = cs    INITSEG (0x9000),
 * fs = 0,gs =        。
 */

 ! BIOS       0x1e0x1e * 4 = 0x78  。
 !           0x0000:0x0078            0x9000:0xfef4  ,        
 !          18。
    push    #0          !       fs = 0
    pop fs              ! fs:bx             (     )。
    mov bx,#0x78        ! fs:bx is parameter table address
    ! seg fs           ,            fs         。     
    ! fs:bx               gs:si       ,     es:di = 0x9000:0xfef4 
    !        。 
    seg fs
    lgs si,(bx)         ! gs:si is source

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

    rep                 !   12         0x9000:0xfef4  。
    seg gs
    movw

    mov di,dx           ! es:di     ,        4       。
    movb    4(di),*18       ! patch sector count

    seg fs              !       0x1e       。
    mov (bx),di
    seg fs
    mov 2(bx),es

    pop ax              !ax = 0x9000
    mov fs,ax
    mov gs,ax

    xor ah,ah           ! reset FDC !        ,       。
    xor dl,dl           ! dl = 0;  1   
    int     0x13    

! load the setup-sectors directly after the bootblock.
! Note that 'es' is already set up.
!   bootsect           setup        。
!       ,es       。 
!   BIOS   INT 0x13   setup        2    
!     0x902004    。     ,           ,      , 
!   ,    。INT 0x13        :
!    :
! ah = 0x02 -         ;al =          ;
! ch =   (  )   8  ; cl =     (0-5  ),    2  (6-7);
! dh =    ; dl =     (         7);
! es:bx        ;       CF     ,  ah     。
load_setup:
    xor dx, dx          ! drive 0, head 0
    mov cx,#0x0002      ! sector 2, track 0
    mov bx,#0x0200      ! address = 512, in INITSEG
    mov ax,#0x0200+SETUPLEN ! service 2, nr of sectors
    int 0x13            ! read it
    jnc ok_load_setup   ! ok - continue

    push    ax          ! dump error code   !      。     。
    call    print_nl    !       
    mov bp, sp          ! ss:bp        (word)
    call    print_hex   !        
    pop ax  

    xor dl, dl          ! reset FDC !       ,  。
    xor ah, ah
    int 0x13
    j   load_setup      ! j   jmp

ok_load_setup:

! Get disk drive parameters, specifically nr of sectors/track
!              ,          ,       sectors  。
!          INT 0x13            :
! ah = 0x08 dl =     (         7  1)。
!     :
!       CF   ,   ah =    。
! ah = 0, al = 0, bl =      (AT/PS2)
! ch =         8  ,cl =         (  0-5),       2  (  6-7)
! dh =      , dl =      ,
! es:di ->        。

    xor dl,dl
    mov ah,#0x08        ! AH=8 is get drive parameters
    int 0x13
    xor ch,ch
    seg cs              !           ,      
    mov sectors,cx      !         。
    mov ax,#INITSEG
    mov es,ax           !              es  ,       

! Print some inane message
!        ('Loading' +    +   ,  9    )。

    mov ah,#0x03        ! read cursor pos   !      
    xor bh,bh           ! bh   
    int 0x10

    mov cx,#9           ! cx         
    mov bx,#0x0007      ! page 0, attribute 7 (normal)
                        ! bh =   ,bl =     
    mov bp,#msg1
    mov ax,#0x1301      ! write string, move cursor
                        ! ah = 0x13 -      。al =             。0x01 -     bl     ,  
                        !        
    int 0x10
! ok, we've written the message, now                        '

! we want to load the system (at 0x10000)
!       system       0x10000 ( 64K ) 。

    mov ax,#SYSSEG
    mov es,ax       ! segment of 0x010000
    call    read_it !      system   ,es      。
    call    kill_motor !        ,              。
    call    print_nl    !       ,          system      int 0x10    。

! 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.
!   ,                (     )。         (!= 0)  
!         。        BIOS                 /dev/PS0 (2,28) 
!    /dev/at0 (2,8)。
!               :
!   Linux          2(    78     ),     = type * 4 + nr,  
! nr   0 - 3       A、B、C  D;type       (2->1.2M   7->1.44M  )。
!    7*4 + 0 = 28,   /dev/PS0 (2,28)   1.44M A    ,      0x021c
!    /dev/at0 (2,8)   1.2M A    ,     0x0208。

    seg cs
    mov ax,root_dev     !    root_dev   ,           
    or  ax,ax
    jne root_defined
    seg cs              !    sectors   (      );sectors = 15      1.2MB     ;
    mov bx,sectors      ! sectors = 18      1.44MB    。          ,   A 。
    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
undef_root:             !              
    jmp undef_root
root_defined:           !            root_dev  。
    seg cs
    mov root_dev,ax

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

    jmpi    0,SETUPSEG

!!!!!!!!!!!!!!!!!!!!! bootsect.S         。

! 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)
!
!                  0x1000064KB      。      
!      ,    ,            。
!   :es –         (    0x1000)
sread:  .word 1+SETUPLEN    ! sectors read of current track  ! bootsect   setup         。
head:   .word 0         ! current head !     
track:  .word 0         ! current track !     

read_it:
!          。        64KB    ,       。 bx    ,        
!          。
    mov ax,es
    test ax,#0x0fff
die:    jne die         ! es must be at 64kB boundary ! es      64KB     。
    xor bx,bx       ! bx is starting address within segment ! bx        。
rp_read:
    mov ax,es
    cmp ax,#ENDSEG      ! have we loaded all yet? !            ?
    jb ok1_read
    ret
ok1_read:
!                  ,   ax     。
!                             ,              , 
!           64KB       。    ,              (64KB –   
!     ),             。
    seg cs
    mov ax,sectors
    sub ax,sread    ! bootsect   setup         
    mov cx,ax       ! cx = ax =          。
    shl cx,#9       ! cx = cx * 512   。
    add cx,bx       ! cx + bx =       ,         (    )。
    jnc ok2_read    !       64KB   ,     ok2_read    。
    je ok2_read
    !                     64KB,           
    !    (64KB –        ),            。
    xor ax,ax
    sub ax,bx       ! 0 - bx      ,             
    shr ax,#9       !   9      512,      
ok2_read:
    call read_track !                    
    mov cx,ax
    add ax,sread
    seg cs
    cmp ax,sectors  !             ,    ok3_read。
    jne ok3_read
    !                   ,           (1   )    。
    !     ,       
    mov ax,#1
    sub ax,head
    jne ok4_read    !    0  ,             
    inc track       !        。
ok4_read:
    mov head,ax
    xor ax,ax
    !            ,            ,             。
ok3_read:
    mov sread,ax        !            。
    shl cx,#9           !        *512   。
    add bx,cx           !             。
    jnc rp_read         !     64KB    ,    rp_read ,     。
                        !        ,          。
    mov ax,es           !        
    add ah,#0x10
    mov es,ax
    xor bx,bx           !            
    jmp rp_read

!                       es:bx    。   67    BIOS      
! int 0x13,ah=2    。
! al –      ;es:bx –        。
read_track:
    pusha           !        (push all)
    !      BIOS   ,   ah = 0x0e (        ),       。
    pusha           
    mov ax, #0xe2e  ! loading... message 2e = .
    mov bx, #7
    int 0x10
    popa        

!            。
    mov dx,track    !      
    mov cx,sread    !          
    inc cx
    mov ch,dl       ! ch -     ,cl -       
    mov dx,head     !       
    mov dh,dl       ! dh =    ,dl =     ( 0    A )。
    and dx,#0x0100  !       1.
    mov ah,#2

    push    dx              ! save for error dump
    push    cx              !       
    push    bx
    push    ax

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

!        。        ,          (       0),    read_track   。
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                 !              ax + ax,bx,cx,dx
    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 #5      ! error code + 4 registers
    mov bp, sp  

print_loop:
    push    cx      ! save count left
    call    print_nl    ! nl for readability
    jae no_reg      ! see if register name is needed

    mov ax, #0xe05 + 0x41 - 1
    sub al, cl
    int 0x10

    mov al, #0x58   ! X
    int 0x10

    mov al, #0x3a   ! :
    int 0x10

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

!    BIOS    0x10,           
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   4 
    mov ah, #0xe    
    mov al, dl      ! mask off so we have only next nibble
    and al, #0xf    !        
    add al, #0x30   ! convert to 0 based digit, '0'
    cmp al, #0x39   ! check for overflow !   9   ,   A-F
    jbe good_digit
    add al, #0x41 - 0x30 - 0xa  ! 'A' - '0' - 0xa 

good_digit:
    int 0x10
    loop    print_digit         ! cx--。 cx>0        
    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                !  al      dx      。
    pop dx
    ret

sectors:
    .word 0

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

.org 506
!           506 (0x1FC)  ,   swap_dev         506  
!    2     ,root_dev         508     2     。
swap_dev:
    .word SWAP_DEV
root_dev:
    .word ROOT_DEV
!                  。
boot_flag:
    .word 0xAA55

.text
endtext:
.data
enddata:
.bss
endbss:

좋은 웹페이지 즐겨찾기