• <ins id="pjuwb"></ins>
    <blockquote id="pjuwb"><pre id="pjuwb"></pre></blockquote>
    <noscript id="pjuwb"></noscript>
          <sup id="pjuwb"><pre id="pjuwb"></pre></sup>
            <dd id="pjuwb"></dd>
            <abbr id="pjuwb"></abbr>
            posts - 2, comments - 3, trackbacks - 0, articles - 0
              C++博客 :: 首頁 :: 新隨筆 :: 聯系 :: 聚合  :: 管理

            自制os開發記(一)——啟動部分

            Posted on 2009-02-03 14:38 bpt 閱讀(1317) 評論(2)  編輯 收藏 引用
            將自制的操作系統命名為BlackPoint

            基本是按照《自己動手寫os》中的步驟來的,從軟盤啟動,調入Loader再調入Kernel
            沒有完全復制書中的代碼,而是按照其中的思路來自己寫一遍,收獲頗豐啊。

            第一步先構造軟盤的啟動扇區boot.asm,使用NASM在XP下開發:
             1 %include "address.inc"
             2 %include "macro.inc"
             3 
             4 org 0x7c00
             5 TOP_OF_STACK EQU 0x7c00
             6 
             7 jmp short LAB_boot
             8 nop
             9 
            10 %include "fat12hdr"
            11 
            12 LAB_boot:
            13         mov ax, cs
            14         mov ds, ax
            15         mov es, ax
            16         mov ss, ax
            17         mov sp, TOP_OF_STACK
            18 
            19         RESET_FLOPPY
            20 
            21         ;load FAT1
            22         LOAD_SEC SBASE_FAT, START_FAT1, LENGTH_FAT1
            23 
            24         ;load Root Entry Table
            25         LOAD_SEC SBASE_RET, START_RET, LENGTH_RET
            26 
            27         ;load loader
            28         LOAD_FILE SBASE_loader, OFFSET_loader, loader_filename
            29 
            30         jmp SBASE_loader:OFFSET_loader
            31 
            32 
            33 ;strings
            34 loader_filename        DB        `LOADER  BIN`, 0
            35 
            36 %include "floppy.asm"
            37 
            38 TIMES (510 - ($ - $$)) DB 0
            39 DW 0xaa55
            啟動扇區包含了四個文件:address是系統的內存布局安排,macro是我為了偷懶定義的一些宏。
            fat12hdr是fat12格式軟盤的頭信息。
            而floppy.asm是一些寫好的過程,因為loader中也要用到,所以干脆做成了一個文件。

            下面是floppy.asm的代碼,他跟fat12hdr的依賴度很高:
              1 %include "address.inc"
              2 
              3 ;---------------------------------------------------------------------
              4 
              5 ;subroutine ReadSector
              6 ;read bl Sections start from Section ax
              7 ;result will be in es:di
              8 ReadSector:
              9 
             10         mov cl, 18
             11         div cl
             12         inc ah
             13         mov cl, ah            ;get Section
             14         mov ch, al
             15         shr ch, 1            ;get Cylinder
             16         mov dh, al
             17         and dh, 1            ;get Head
             18         xor dl, dl            ;disk0
             19         
             20         mov bh, 0x2
             21         push bp
             22         push bx
             23         mov bp, sp
             24         mov bx, di
             25 .1:
             26         mov ax, word [bp]
             27         int 0x13
             28         test ah, ah
             29         jnz .1
             30         pop bx
             31         pop bp
             32         ret
             33         
             34 ;---------------------------------------------------------------------
             35 
             36 ;subroutine SearchFile        
             37 ;search file in root entry table (SBASE_RET:0)
             38 ;input: filename should be stored in ds:si
             39 ;output: ax will be the first cluster no. of the file 
             40 SearchFile:
             41         mov bx, si            ;ds:bx -> filename
             42         mov ax, SBASE_RET
             43         mov es, ax
             44         xor di, di            ;es:0 -> the first Root Entry
             45         mov dx, 224
             46 .search:
             47         mov cx, 11
             48 .compare:
             49         mov al, byte [ds:bx]
             50         cmp al, byte [es:di]
             51         jne .next_entry
             52         inc bx
             53         inc di
             54         loop .compare
             55         jmp .ok
             56 .next_entry:
             57         mov bx, si        ;ds:bx -> filename
             58         and di, 0xffe0
             59         add di, 32        ;es:di -> next Root Entry
             60         dec dx
             61         jnz .search
             62 .fail:
             63         mov ax, cs
             64         mov ds, ax
             65         mov si, .msg_fail
             66 .print:
             67         mov al, byte [ds:si]
             68         test al, al
             69         jz $
             70         mov ah, 0x0e
             71         int 0x10
             72         inc si
             73         jmp .print
             74 .ok:
             75         and di, 0xffe0
             76         mov ax, word [es:di + 0x1a]        ;get cluster no.
             77         ret
             78 
             79 ;strings
             80 .msg_fail        DB        ` file is missing\n\r`, 0
             81 
             82 ;---------------------------------------------------------------------
             83 
             84 ;subroutine LoadFile
             85 ;load file started from cluster ax to es:di
             86 LoadFile:
             87 .1:
             88         cmp ax, 0xff8
             89         jae .end
             90         push ax
             91         add ax, 31
             92         mov bl, 1
             93         call ReadSector
             94         pop ax
             95         call GetNextClus
             96         add di, 512
             97         jmp .1
             98 .end:
             99         ret
            100 
            101 ;---------------------------------------------------------------------
            102 
            103 ;subroutine GetNextClus
            104 ;get next clus_num of current clus(stored in ax)
            105 ;FAT must be loaded in SBASE_FAT:0
            106 ;result will be in ax
            107 ;none of regs will be changed besides ax
            108 GetNextClus:
            109         push ds
            110         push si
            111         push bx
            112 
            113         mov bx, SBASE_FAT
            114         mov ds, bx
            115         mov bx, ax        ;let bx be the cluster no.
            116         shr ax, 1
            117         imul ax, 3
            118         mov si, ax
            119         test bx, 1        ;test cluster no. whether even or odd
            120         jnz .odd
            121 .even:
            122         mov ax, word [ds:si]
            123         and ax, 0xfff
            124         jmp .end
            125 .odd:
            126         mov ax, word [ds:si + 1]
            127         shr ax, 4
            128 .end:
            129         pop bx
            130         pop si
            131         pop ds
            132         ret

            下面是fat12hdr的內容,抄自《自己動手寫os》
             1 BS_OEMName            DB        'bpt     '
             2 BPB_BytsPerSec        DW        512
             3 BPB_SecPerClus        DB        1
             4 BPB_RsvdSecCnt        DW        1
             5 BPB_NumFATs            DB        2
             6 BPB_RootEntCnt        DW        224
             7 BPB_TotSec16        DW        2880
             8 BPB_Media            DB        0xF0
             9 BPB_FATSz16            DW        9
            10 BPB_SecPerTrk        DW        18
            11 BPB_NumHeads        DW        2
            12 BPB_HiddSec            DD        0
            13 BPB_TotSec32        DD        0
            14 BS_DrvNum            DB        0
            15 BS_Reserved1        DB        0
            16 BS_BootSig            DB        29h
            17 BS_VolID            DD        0
            18 BS_VolLab            DB        'BlackPoint '
            19 BS_FileSysType        DB        'FAT12   '
            20 
            21 %ifndef __FAT12HDR
            22 %define __FAT12HDR
            23 
            24 START_FAT1        EQU        1    ;BPB_RsvdSecCnt
            25 LENGTH_FAT1        EQU        9    ;BPB_FATSz16
            26 START_RET        EQU        19    ;BPB_RsvdSecCnt + BPB_NumFATs * BPB_FATSz16
            27 LENGTH_RET        EQU        14    ;BPB_RootEntCnt * 32 / BPB_BytsPerSec
            28 
            29 %endif

            下面是address.inc,其中的內容是啟動時os的內存安排
             1 %ifndef __ADDRESS_INC
             2 %define __ADDRESS_INC
             3 
             4 SBASE_FAT        EQU        0x8000
             5 SBASE_RET        EQU        0x8500
             6 
             7 SBASE_loader    EQU        0x1000
             8 OFFSET_loader    EQU        0x00100
             9 BASE_loader        EQU        0x10000
            10 
            11 SBASE_mem        EQU        0x9000
            12 BASE_mem        EQU        0x90000
            13     ;name                ;offset        length        note
            14     mem_size    EQU        0            ;4            memory size
            15     num_ards    EQU        4            ;4            number of ards
            16     mem_info    EQU        8            ;20 x 50    memory block info
            17 
            18 SBASE_elf        EQU        0x2000
            19 OFFSET_elf        EQU        0x0
            20 BASE_elf        EQU        0x20000
            21 
            22 BASE_kernel        EQU        0x30000
            23 KERNEL_ENTRY    EQU        0x30400
            24 
            25 BASE_page_dir    EQU        0x100000
            26 BASE_page_table    EQU        0x101000
            27 
            28 %endif

            在下面就是我用來偷懶的macro.inc
             1 %ifndef __MACRO_INC
             2 %define __MACRO_INC
             3 
             4 ;---------------------------------------------------------------------
             5 
             6 %macro RESET_FLOPPY 0
             7         xor ah, ah
             8         xor dl, dl
             9         int 0x13
            10 
            11 %endmacro
            12 
            13 ;---------------------------------------------------------------------
            14 
            15 %macro CLOSE_FLOPPY 0
            16         mov dx, 0x3f2
            17         xor al, al
            18         out dx, al
            19 %endmacro
            20 
            21 ;---------------------------------------------------------------------
            22 
            23 ;load %3 sectors from %2 to %1:0
            24 %macro LOAD_SEC 3
            25         push es
            26         mov ax, %1
            27         mov es, ax
            28         xor di, di
            29         mov ax, %2
            30         mov bl, %3
            31         call ReadSector
            32         pop es
            33 %endmacro
            34 
            35 ;---------------------------------------------------------------------
            36 
            37 ;load file(ds:%3) to %1:%2
            38 %macro LOAD_FILE 3
            39         mov si, %3
            40         call SearchFile
            41         push es
            42         mov bx, %1
            43         mov es, bx
            44         mov di, %2
            45         call LoadFile
            46         pop es
            47 %endmacro
            48 
            49 ;---------------------------------------------------------------------
            50 
            51 ;PRINT row(byte), col(byte), char(byte)
            52 %macro PRINT 3
            53         mov edi, (80 * (%1) + (%2)) * 2
            54         mov ah, 0x0c
            55         mov al, (%3)
            56         mov [gs:edi], ax
            57 %endmacro
            58 
            59 ;---------------------------------------------------------------------
            60 
            61 %endif

            折騰了這么多,軟盤啟動扇區算是開發完了。一路下來算是會用NASM了。記得剛開始用NASM時那個難啊。其實萬事開頭難,在暴風雨中堅持住,陽光自己來。

            接下來是Loader的開發,更是讓我叫苦不迭,每走一步都是荊棘遍野。通常是后面的bug調好了又發現了前面的bug,甚至多次重寫。好在loader功能不多,可以一個一個小模塊的開發,再組合起來。
            先亮出一個重要的頭文件,與保護模式有關的宏和定義都放置在x86.inc中:
              1 %ifndef __X86_INC
              2 %define __X86_INC
              3 
              4 %define BIT(X) (1 << (X))
              5 
              6 ;===============================================================================
              7 
              8 ;despcritor des_t base(dword), limit(dword), attribute(word)
              9 ;
             10 ;attribute:
             11 ;    11    10    9    8        7    6    5    4        3    2    1    0
             12 ;    G    D    0    0        P    <DPL>    S        < type    >    A
             13 %macro des_t 3
             14     DW        ((%2) & 0xffff)            ;limit 15~0
             15     DW        ((%1) & 0xffff)            ;base 15~0
             16     DB        (((%1) >> 16) & 0xff)    ;base 23~16
             17     DB        ((%3) & 0xff)            ;P, DPL, S, type, A
             18     DB        ((((%2) >> 16) & 0xf) | (((%3) >> 4) & 0xf0))
             19                                     ;G, D, 0, 0, limit 19~16
             20     DB        (((%1) >> 24) & 0xff)    ;base 31~24
             21 %endmacro
             22 
             23 ;descriptor attribute
             24 DA_G            EQU        BIT(11)            ;granularity 4KB
             25 DA_4G            EQU        DA_G
             26 DA_D            EQU        BIT(10)            ;default operation size 32bits
             27 DA_B            EQU        DA_D
             28 DA_P            EQU        BIT(7)            ;segment present
             29 DA_S            EQU        BIT(4)
             30 DA_DATA            EQU        DA_S            ;data segment
             31 DA_E            EQU        BIT(2)
             32 DA_W            EQU        BIT(1)            ;(data segment)writable
             33 DA_CODE            EQU        DA_S | BIT(3)    ;code segment
             34 DA_C            EQU        BIT(2)            ;(code segment)readable
             35 DA_R            EQU        BIT(1)            ;(code segment)conforming
             36 DA_A            EQU        BIT(0)            ;Accessed
             37 
             38 DA_LDT            EQU        0x2 | DA_P
             39 DA_TSS            EQU        0x9 | DA_P
             40 DA_CODE16        EQU        DA_CODE | DA_P
             41 DA_CODE32        EQU        DA_CODE | DA_D | DA_P
             42 DA_CODE32C        EQU        DA_CODE32 | DA_C
             43 DA_CODE32R        EQU        DA_CODE32 | DA_R
             44 DA_CODE32CR        EQU        DA_CODE32C | DA_R
             45 DA_CODE32RC        EQU        DA_CODE32CR
             46 DA_DATA16        EQU        DA_DATA | DA_P
             47 DA_DATA16W        EQU        DA_DATA16 | DA_W
             48 DA_DATA32        EQU        DA_DATA | DA_B | DA_P
             49 DA_DATA32W        EQU        DA_DATA32 | DA_W
             50 DA_STACK16        EQU        DA_DATA | DA_W | DA_P
             51 DA_STACK32        EQU        DA_DATA | DA_W | DA_B | DA_P
             52 
             53 DA_DPL0            EQU        0000_0000b        ;descriptor privilege level
             54 DA_DPL1            EQU        0010_0000b
             55 DA_DPL2            EQU        0100_0000b
             56 DA_DPL3            EQU        0110_0000b
             57 
             58 
             59 ;FILL_DES_BASE        descriptor, segment(word), offset(word)
             60 ;fill descriptor's dase with segment:offset
             61 ;eax will be modified
             62 %macro FILL_DES_BASE 3
             63         xor eax, eax
             64         mov ax, %2
             65         shl eax, 4
             66         add eax, %3
             67         mov word [%1 + 2], ax
             68         shr eax, 16
             69         mov byte [%1 + 4], al
             70         mov byte [%1 + 7], ah
             71 %endmacro
             72 
             73 ;FILL_DES_LIMIT        descriptor, limit(dword)
             74 ;fill descriptor's limit
             75 ;eax will be modified
             76 %macro FILL_DES_LIMIT 2
             77         mov eax, %2
             78         mov word [%1], ax
             79         shr eax, 16
             80         and al, 0xf
             81         or byte [(%1) + 6], al
             82 %endmacro
             83 
             84 ;===============================================================================
             85 
             86 ;gate_t selector(word), offset(dword), param_count(byte), attribute(byte)
             87 %macro gate_t 4
             88     DW        ((%2) & 0xffff)            ;offset 15~0
             89     DW        ((%1) & 0xffff)            ;selector
             90     DB        ((%3) & 0x11111b)        ;param count
             91     DB        ((%4) & 0xff)            ;P, DPL, S, type
             92     DW        (((%2) >> 16) & 0xffff)    ;offset 31~24
             93 %endmacro
             94 
             95 ;gate attribute
             96 GA_P            EQU        BIT(7)            ;gate present
             97 
             98 GA_CALL32        EQU        0xc | GA_P
             99 GA_INT32        EQU        0xe | GA_P
            100 GA_TRAP32        EQU        0xf | GA_P
            101 
            102 GA_DPL0            EQU        0000_0000b        ;gate privilege level
            103 GA_DPL1            EQU        0010_0000b
            104 GA_DPL2            EQU        0100_0000b
            105 GA_DPL3            EQU        0110_0000b
            106 
            107 ;===============================================================================
            108 
            109 ;DEFINE_SELECTOR    name, offset(word), attribute(byte)
            110 %macro DEFINE_SELECTOR 3
            111     %1 EQU (((%2) & 1111_1000b) | (%3))
            112 %endmacro
            113 
            114 ;selector attribute
            115 SA_TI            EQU        BIT(2)
            116 SA_GDT            EQU        0
            117 SA_LDT            EQU        SA_TI
            118 
            119 SA_RPL0            EQU        0
            120 SA_RPL1            EQU        1
            121 SA_RPL2            EQU        2
            122 SA_RPL3            EQU        3
            123 
            124 ;===============================================================================
            125 
            126 ;Page Directory/Table Entry
            127 PG_P    EQU        BIT(0)
            128 PG_R    EQU        0
            129 PG_W    EQU        BIT(1)
            130 PG_S    EQU        0
            131 PG_U    EQU        BIT(2)
            132 ;not complete
            133 
            134 ;===============================================================================
            135 
            136 %undef BIT
            137 
            138 %endif
            剛開始接觸保護模式時,被成堆的資料雷住了... 其實后來發現我接觸的保護模式并不難,因為我只用了其中一小部分,只要能把參考文檔看懂,都是死東西。主要內容按照《自己動手寫os》第3章各節的內容練一遍,再準備好匯編黑皮書和Intel的開發者手冊,基本上可以過關。

            有了保護模式的一些知識,就開始著手寫loader:
              1 %include "address.inc"
              2 %include "macro.inc"
              3 %include "x86.inc"
              4 
              5 org 0x100
              6 TOP_OF_STACK    EQU        0x100
              7 
              8 ;===============================================================================
              9 LAB_loader:
             10         mov ax, cs
             11         mov ds, ax
             12         mov es, ax
             13         mov ss, ax
             14         mov sp, TOP_OF_STACK
             15         
             16         RESET_FLOPPY
             17         LOAD_FILE SBASE_elf, OFFSET_elf, kernel_filename
             18         CLOSE_FLOPPY
             19 
             20         call CheckMem
             21         shr eax, 20
             22         call PrintEAX
             23         mov si, msg_RAM
             24         call PrintString
             25 
             26         lgdt [gdtr]
             27 
             28         cli
             29 
             30         in al, 0x92
             31         or al, 0000_0010b
             32         out 0x92, al
             33 
             34         mov eax, cr0
             35         or eax, 1
             36         mov cr0, eax
             37 
             38         jmp dword gsel_flat_code:(BASE_loader + section.SEG_code32.start)
             39 
             40 ;strings
             41 kernel_filename        DB        "KERNEL  BIN", 0
             42 msg_RAM                DB        `MB Memory\n\r`, 0
             43 
             44 ;---------------------------------------------------------------------
             45 
             46 ;subroutine CheckMem
             47 ;none of segment regs will be modified
             48 CheckMem:
             49         push ds
             50         push es
             51 
             52         mov ax, SBASE_mem
             53         mov ds, ax
             54         mov es, ax
             55         xor ebx, ebx
             56         mov edi, mem_info
             57 .info:
             58         mov eax, 0xe820
             59         mov ecx, 20
             60         mov edx, 0x534D4150
             61         int 0x15
             62         jc .fail
             63         add edi, 20
             64         inc dword [num_ards]
             65         test ebx, ebx
             66         jnz .info
             67         jmp .ok
             68 .fail:
             69         mov ax, cs
             70         mov ds, ax
             71         mov si, .msg_fail
             72 .print:
             73         mov al, byte [ds:si]
             74         test al, al
             75         jz $
             76         mov ah, 0x0e
             77         int 0x10
             78         inc si
             79         jmp .print
             80 .ok:
             81         mov ecx, dword [num_ards]
             82         mov si, mem_info
             83 .count:
             84         cmp dword [si + 16], 1
             85         jne .next
             86         mov eax, dword [si]
             87         add eax, dword [si + 8]
             88         cmp eax, dword [mem_size]
             89         jna .next
             90         mov dword [mem_size], eax
             91 .next:
             92         add si, 20
             93         loop .count
             94 
             95         mov eax, dword [mem_size]
             96         pop es
             97         pop ds
             98         ret
             99 
            100 ;strings
            101 .msg_fail        DB        `memeory check error\n\r`, 0
            102 
            103 ;---------------------------------------------------------------------
            104 
            105 ;subroutine PrintEAX
            106 ;none of regs will be modified
            107 PrintEAX:
            108         push eax
            109         push ebx
            110         push ecx
            111         push edx
            112 
            113         xor ecx, ecx
            114 .cal:
            115         xor edx, edx
            116         mov ebx, 10
            117         div ebx
            118         push edx
            119         inc ecx
            120         test eax, eax
            121         jnz .cal
            122 .print:
            123         pop eax
            124         add al, '0'
            125         call PrintAL
            126         loop .print
            127 
            128         pop edx
            129         pop ecx
            130         pop ebx
            131         pop eax
            132         ret
            133 
            134 ;---------------------------------------------------------------------
            135 
            136 ;subroutine PrintString
            137 ;ds:si should be the address of the string end of 0
            138 ;none of regs will be modified
            139 PrintString:
            140         push si
            141         push ax
            142 .1:
            143         mov al, byte [ds:si]
            144         test al, al
            145         jz .end
            146         call PrintAL
            147         inc si
            148         jmp .1
            149 .end:
            150         pop ax
            151         pop si
            152         ret
            153 
            154 ;---------------------------------------------------------------------
            155 
            156 PrintAL:
            157     push ax
            158     mov ah, 0xe
            159     int 0x10
            160     pop ax
            161     ret
            162 
            163 ;----------------------------------------------------------------------
            164 
            165 %include "floppy.asm"
            166 
            167 ;^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
            168 
            169 ;===============================================================================
            170 SECTION SEG_gdt align=8
            171 
            172 gdes_null            des_t        0, 0, 0
            173 gdes_flat_code        des_t        0, 0xfffff, DA_CODE32R | DA_4G | DA_DPL0
            174 gdes_flat_data        des_t        0, 0xfffff, DA_DATA32W | DA_4G | DA_DPL0
            175 gdes_video            des_t        0xb8000, 0xffff, DA_DATA16W | DA_DPL3
            176 
            177 gdtr            DW        $ - $$ - 1
            178                 DD        BASE_loader + $$
            179 
            180 DEFINE_SELECTOR        gsel_flat_code, gdes_flat_code - $$, SA_GDT | SA_RPL0
            181 DEFINE_SELECTOR        gsel_flat_data, gdes_flat_data - $$, SA_GDT | SA_RPL0
            182 DEFINE_SELECTOR        gsel_video, gdes_video - $$, SA_GDT | SA_RPL0
            183 ;SECTION SEG_gdt^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
            184 
            185 ;===============================================================================
            186 SECTION SEG_code32 align=16
            187 BITS 32
            188 
            189         mov ax, gsel_flat_data
            190         mov ds, ax
            191         mov es, ax
            192         mov fs, ax
            193         mov ss, ax
            194         mov esp, TOP_stack
            195 
            196         mov ax, gsel_video
            197         mov gs, ax
            198 
            199         PRINT 10, 3, 'P'
            200         
            201         call SetupPaging
            202 
            203         PRINT 10, 4, 'P'
            204 
            205         call InitKernel
            206 
            207         PRINT 10, 5, 'P'
            208 
            209         jmp gsel_flat_code:KERNEL_ENTRY
            210 
            211 ;---------------------------------------------------------------------
            212 
            213 ;subroutine SetupPaging
            214 SetupPaging:
            215 
            216         mov ecx, dword [BASE_mem]
            217         test ecx, 00000_00000_11111_11111_11111_11111_11b
            218         jnz .another_pde
            219         shr ecx, 22
            220         jmp .init_pd
            221 .another_pde:
            222         shr ecx, 22
            223         inc ecx
            224 .init_pd:
            225         push ecx
            226         mov edi, BASE_page_dir
            227         mov eax, BASE_page_table | PG_U | PG_W | PG_P
            228 .1:
            229         mov dword [edi], eax
            230         add edi, 4
            231         add eax, 4 * 1024
            232         loop .1
            233 .init_pt:
            234         mov edi, BASE_page_table
            235         mov eax, 0 | PG_U | PG_W | PG_P
            236         pop ecx
            237         shl ecx, 10        ;ecx *= 1024
            238 .2:
            239         mov dword [edi], eax
            240         add edi, 4
            241         add eax, 4 * 1024
            242         loop .2
            243 
            244         mov eax, BASE_page_dir
            245         mov cr3, eax
            246 
            247         mov eax, cr0
            248         or eax, 1 << 31
            249         mov cr0, eax
            250 
            251         ret
            252 
            253 ;---------------------------------------------------------------------
            254 
            255 ;subroutine InitKernel
            256 InitKernel:
            257 
            258         xor ebx, ebx
            259         mov bx, word [BASE_elf + 0x2a]    ;ebx = size of one entry in the pht
            260         xor edx, edx
            261         mov dx, word [BASE_elf + 0x2c]    ;edx = number of entries in the pht
            262         mov esi, dword [BASE_elf + 0x1c];esi = offset of the pht
            263         add esi, BASE_elf                ;esi = address of the pht
            264 .loop_edx:
            265         test edx, edx
            266         jz .endloop_edx
            267         cmp dword [esi], 1
            268         jne .2                            ;the seg can be loaded if type = 1
            269         push esi                        ;backup esi
            270         mov edi, dword [esi + 0x8]        ;edi = virtual address
            271         xor ecx, ecx
            272         mov cx, word [esi + 0x10]        ;ecx = size
            273         mov esi, dword [esi + 0x4]        ;esi = offset of program
            274         add esi, BASE_elf                ;esi = address of program
            275 .loop_ecx:
            276         test ecx, ecx
            277         jz .endloop_ecx
            278         mov al, byte [esi]
            279         mov byte [edi], al
            280         inc esi
            281         inc edi
            282         dec ecx
            283         jmp .loop_ecx
            284 .endloop_ecx:
            285         pop esi                ;restore esi
            286 .2:
            287         add esi, ebx        ;esi += pht_entry_size
            288         dec edx
            289         jmp .loop_edx
            290 .endloop_edx:
            291 
            292         ret
            293 
            294 ;---------------------------------------------------------------------
            295 
            296 LEN_code32    EQU        $ - $$
            297 ;SECTION SEG_code32^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
            298 
            299 ;===============================================================================
            300 SECTION SEG_stack
            301 ALIGN 4
            302 
            303 TIMES 2048 DB 0        ;2KB
            304 
            305 TOP_stack    EQU        BASE_loader + $
            306 ;SECTION SEG_stack^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
            loader中要做下面幾件事:
            1.將elf格式的kernel.bin調入內存。
            2.檢查內存情況,啟動分頁機制。
            3.切換到保護模式,轉移控制到kernel

            對1來說,有了boot的經驗,這個應該不成問題。
            對2來說,我僅僅實現了算出該PC上內存上限,并無考慮內存存在空洞。
            對3來說,識別elf格式的地方曾經出了一些問題,因為我用ubuntu下的ld鏈接出來的elf格式的kernel.bin比書中的代碼要多一個program。后來我仔細閱讀了elf格式的文檔之后修正了這個bug。這個bug是我進入kernel之前的最后一只攔路虎,突破之后就可以開始用C寫一些東西了。

            最后貼個圖,是我在vmware中用軟盤啟動后的情況:

            Feedback

            # re: 自制os開發記(一)——啟動部分  回復  更多評論   

            2009-02-06 13:59 by 路青飛
            贊一個。

            # re: 自制os開發記(一)——啟動部分  回復  更多評論   

            2009-02-06 16:38 by 李現民
            現在很少有人這么做了。
            国内精品九九久久精品| 久久se这里只有精品| 久久超乳爆乳中文字幕| 久久综合久久综合久久| 日韩中文久久| 久久不射电影网| 日韩精品久久久久久久电影| 国产精品久久久久久久久| 久久久久国产精品麻豆AR影院| 色偷偷偷久久伊人大杳蕉| 激情五月综合综合久久69| 麻豆亚洲AV永久无码精品久久| 久久精品国产亚洲Aⅴ香蕉| 欧美大香线蕉线伊人久久| 久久婷婷五月综合色99啪ak| 国内精品久久久久影院日本| 亚洲天堂久久久| 久久精品无码一区二区三区免费 | 亚洲国产欧洲综合997久久| 亚洲伊人久久大香线蕉苏妲己| 久久久久久久久久久| 久久久久国产精品三级网| 亚洲一区中文字幕久久| 成人久久久观看免费毛片| 国产99久久久国产精品小说| 激情久久久久久久久久| 久久最新精品国产| 99久久免费国产精精品| 日韩精品无码久久久久久| 久久精品国产男包| 无码人妻久久一区二区三区蜜桃 | 88久久精品无码一区二区毛片| 久久人人爽人人爽人人片av高请| 久久久久免费精品国产| 日本三级久久网| 伊人久久大香线焦综合四虎| 99久久国产综合精品麻豆| 狠狠狠色丁香婷婷综合久久五月| 久久精品夜夜夜夜夜久久| 久久久久亚洲Av无码专| 亚洲AV日韩精品久久久久久|