Home | History | Annotate | Download | only in BootSector
      1 ;------------------------------------------------------------------------------
      2 ;*
      3 ;*   Copyright (c) 2006 - 2011, Intel Corporation. All rights reserved.<BR>
      4 ;*   This program and the accompanying materials                          
      5 ;*   are licensed and made available under the terms and conditions of the BSD License         
      6 ;*   which accompanies this distribution.  The full text of the license may be found at        
      7 ;*   http://opensource.org/licenses/bsd-license.php                                            
      8 ;*                                                                                             
      9 ;*   THE PROGRAM IS DISTRIBUTED UNDER THE BSD LICENSE ON AN "AS IS" BASIS,                     
     10 ;*   WITHOUT WARRANTIES OR REPRESENTATIONS OF ANY KIND, EITHER EXPRESS OR IMPLIED.             
     11 ;*   
     12 ;*    start32.asm
     13 ;*  
     14 ;*   Abstract:
     15 ;*
     16 ;------------------------------------------------------------------------------
     17 
     18         .model  small
     19         .stack
     20         .486p
     21         .code
     22 
     23 FAT_DIRECTORY_ENTRY_SIZE    EQU     020h
     24 FAT_DIRECTORY_ENTRY_SHIFT   EQU     5
     25 BLOCK_SIZE                  EQU     0200h
     26 BLOCK_MASK                  EQU     01ffh
     27 BLOCK_SHIFT                 EQU     9
     28 
     29         org 0h
     30 Ia32Jump:
     31   jmp   BootSectorEntryPoint  ; JMP inst    - 3 bytes
     32   nop
     33 
     34 OemId               db  "INTEL   "    ; OemId                           - 8 bytes
     35 SectorSize          dw  0             ; Sector Size                     - 2 bytes
     36 SectorsPerCluster   db  0             ; Sector Per Cluster              - 1 byte
     37 ReservedSectors     dw  0             ; Reserved Sectors                - 2 bytes
     38 NoFats              db  0             ; Number of FATs                  - 1 byte
     39 RootEntries         dw  0             ; Root Entries                    - 2 bytes
     40 Sectors             dw  0             ; Number of Sectors               - 2 bytes
     41 Media               db  0             ; Media                           - 1 byte
     42 SectorsPerFat16     dw  0             ; Sectors Per FAT for FAT12/FAT16 - 2 byte
     43 SectorsPerTrack     dw  0             ; Sectors Per Track               - 2 bytes
     44 Heads               dw  0             ; Heads                           - 2 bytes
     45 HiddenSectors       dd  0             ; Hidden Sectors                  - 4 bytes
     46 LargeSectors        dd  0             ; Large Sectors                   - 4 bytes
     47 
     48 ;******************************************************************************
     49 ;
     50 ;The structure for FAT32 starting at offset 36 of the boot sector. (At this point, 
     51 ;the BPB/boot sector for FAT12 and FAT16 differs from the BPB/boot sector for FAT32.)
     52 ;
     53 ;******************************************************************************
     54 
     55 SectorsPerFat32     dd  0             ; Sectors Per FAT for FAT32       - 4 bytes
     56 ExtFlags            dw  0             ; Mirror Flag                     - 2 bytes
     57 FSVersion           dw  0             ; File System Version             - 2 bytes
     58 RootCluster         dd  0             ; 1st Cluster Number of Root Dir  - 4 bytes
     59 FSInfo              dw  0             ; Sector Number of FSINFO         - 2 bytes
     60 BkBootSector        dw  0             ; Sector Number of Bk BootSector  - 2 bytes
     61 Reserved            db  12 dup(0)     ; Reserved Field                  - 12 bytes
     62 PhysicalDrive       db  0             ; Physical Drive Number           - 1 byte
     63 Reserved1           db  0             ; Reserved Field                  - 1 byte
     64 Signature           db  0             ; Extended Boot Signature         - 1 byte
     65 VolId               db  "    "        ; Volume Serial Number            - 4 bytes
     66 FatLabel            db  "           " ; Volume Label                    - 11 bytes
     67 FileSystemType      db  "FAT32   "    ; File System Type                - 8 bytes
     68 
     69 BootSectorEntryPoint:
     70         ASSUME  ds:@code
     71         ASSUME  ss:@code
     72       ; ds = 1000, es = 2000 + x (size of first cluster >> 4)
     73       ; cx = Start Cluster of EfiLdr
     74       ; dx = Start Cluster of Efivar.bin
     75 
     76 ; Re use the BPB data stored in Boot Sector
     77         mov     bp,07c00h
     78 
     79 
     80         push    cx
     81 ; Read Efivar.bin
     82 ;       1000:dx    = DirectoryEntry of Efivar.bin -> BS.com has filled already
     83         mov     ax,01900h
     84         mov     es,ax
     85         test    dx,dx
     86         jnz     CheckVarStoreSize
     87 
     88         mov     al,1
     89 NoVarStore:
     90         push    es
     91 ; Set the 5th byte start @ 0:19000 to non-zero indicating we should init var store header in DxeIpl
     92         mov     byte ptr es:[4],al
     93         jmp     SaveVolumeId
     94 
     95 CheckVarStoreSize:
     96         mov     di,dx
     97         cmp     dword ptr ds:[di+2], 04000h
     98         mov     al,2
     99         jne     NoVarStore
    100 
    101 LoadVarStore:
    102         mov     al,0
    103         mov     byte ptr es:[4],al
    104         mov     cx,word ptr[di]
    105 ;       ES:DI = 1500:0
    106         xor     di,di
    107         push    es
    108         mov     ax,01500h
    109         mov     es,ax
    110         call    ReadFile
    111 SaveVolumeId:
    112         pop     es
    113         mov     ax,word ptr [bp+VolId]
    114         mov     word ptr es:[0],ax                  ; Save Volume Id to 0:19000. we will find the correct volume according to this VolumeId
    115         mov     ax,word ptr [bp+VolId+2]
    116         mov     word ptr es:[2],ax
    117 
    118 ; Read Efildr
    119         pop     cx
    120 ;       cx    = Start Cluster of Efildr -> BS.com has filled already
    121 ;       ES:DI = 2000:0, first cluster will be read again
    122         xor     di,di                               ; di = 0
    123         mov     ax,02000h
    124         mov     es,ax
    125         call    ReadFile
    126         mov     ax,cs
    127         mov     word ptr cs:[JumpSegment],ax
    128 JumpFarInstruction:
    129         db      0eah
    130 JumpOffset:
    131         dw      0200h
    132 JumpSegment:
    133         dw      2000h
    134 
    135 
    136 
    137 
    138 ; ****************************************************************************
    139 ; ReadFile
    140 ;
    141 ; Arguments:
    142 ;   CX    = Start Cluster of File
    143 ;   ES:DI = Buffer to store file content read from disk
    144 ;
    145 ; Return:
    146 ;   (ES << 4 + DI) = end of file content Buffer
    147 ;
    148 ; ****************************************************************************
    149 ReadFile:
    150 ; si      = NumberOfClusters
    151 ; cx      = ClusterNumber
    152 ; dx      = CachedFatSectorNumber
    153 ; ds:0000 = CacheFatSectorBuffer
    154 ; es:di   = Buffer to load file
    155 ; bx      = NextClusterNumber
    156         pusha
    157         mov     si,1                                ; NumberOfClusters = 1
    158         push    cx                                  ; Push Start Cluster onto stack
    159         mov     dx,0fffh                            ; CachedFatSectorNumber = 0xfff
    160 FatChainLoop:
    161         mov     ax,cx                               ; ax = ClusterNumber    
    162         and     ax,0fff8h                           ; ax = ax & 0xfff8
    163         cmp     ax,0fff8h                           ; See if this is the last cluster
    164         je      FoundLastCluster                    ; Jump if last cluster found
    165         mov     ax,cx                               ; ax = ClusterNumber
    166         shl     ax,2                                ; FatOffset = ClusterNumber * 4
    167         push    si                                  ; Save si
    168         mov     si,ax                               ; si = FatOffset
    169         shr     ax,BLOCK_SHIFT                      ; ax = FatOffset >> BLOCK_SHIFT
    170         add     ax,word ptr [bp+ReservedSectors]    ; ax = FatSectorNumber = ReservedSectors + (FatOffset >> BLOCK_OFFSET)
    171         and     si,BLOCK_MASK                       ; si = FatOffset & BLOCK_MASK
    172         cmp     ax,dx                               ; Compare FatSectorNumber to CachedFatSectorNumber
    173         je      SkipFatRead
    174         mov     bx,2                                
    175         push    es
    176         push    ds
    177         pop     es
    178         call    ReadBlocks                          ; Read 2 blocks starting at AX storing at ES:DI
    179         pop     es
    180         mov     dx,ax                               ; CachedFatSectorNumber = FatSectorNumber
    181 SkipFatRead:
    182         mov     bx,word ptr [si]                    ; bx = NextClusterNumber
    183         mov     ax,cx                               ; ax = ClusterNumber
    184         pop     si                                  ; Restore si
    185         dec     bx                                  ; bx = NextClusterNumber - 1
    186         cmp     bx,cx                               ; See if (NextClusterNumber-1)==ClusterNumber
    187         jne     ReadClusters
    188         inc     bx                                  ; bx = NextClusterNumber
    189         inc     si                                  ; NumberOfClusters++
    190         mov     cx,bx                               ; ClusterNumber = NextClusterNumber
    191         jmp     FatChainLoop
    192 ReadClusters:
    193         inc     bx
    194         pop     ax                                  ; ax = StartCluster
    195         push    bx                                  ; StartCluster = NextClusterNumber
    196         mov     cx,bx                               ; ClusterNumber = NextClusterNumber
    197         sub     ax,2                                ; ax = StartCluster - 2
    198         xor     bh,bh                               
    199         mov     bl,byte ptr [bp+SectorsPerCluster]  ; bx = SectorsPerCluster
    200         mul     bx                                  ; ax = (StartCluster - 2) * SectorsPerCluster
    201         add     ax, word ptr [bp]                   ; ax = FirstClusterLBA + (StartCluster-2)*SectorsPerCluster
    202         push    ax                                  ; save start sector
    203         mov     ax,si                               ; ax = NumberOfClusters
    204         mul     bx                                  ; ax = NumberOfClusters * SectorsPerCluster
    205         mov     bx,ax                               ; bx = Number of Sectors
    206         pop     ax                                  ; ax = Start Sector
    207         call    ReadBlocks
    208         mov     si,1                                ; NumberOfClusters = 1
    209         jmp     FatChainLoop
    210 FoundLastCluster:
    211         pop     cx
    212         popa
    213         ret
    214 
    215 
    216 ; ****************************************************************************
    217 ; ReadBlocks - Reads a set of blocks from a block device
    218 ;
    219 ; AX    = Start LBA
    220 ; BX    = Number of Blocks to Read
    221 ; ES:DI = Buffer to store sectors read from disk
    222 ; ****************************************************************************
    223 
    224 ; cx = Blocks
    225 ; bx = NumberOfBlocks
    226 ; si = StartLBA
    227 
    228 ReadBlocks:
    229         pusha
    230         add     eax,dword ptr [bp+LBAOffsetForBootSector]    ; Add LBAOffsetForBootSector to Start LBA
    231         add     eax,dword ptr [bp+HiddenSectors]    ; Add HiddenSectors to Start LBA
    232         mov     esi,eax                             ; esi = Start LBA
    233         mov     cx,bx                               ; cx = Number of blocks to read
    234 ReadCylinderLoop:
    235         mov     bp,07bfch                           ; bp = 0x7bfc
    236         mov     eax,esi                             ; eax = Start LBA
    237         xor     edx,edx                             ; edx = 0
    238         movzx   ebx,word ptr [bp]                   ; bx = MaxSector
    239         div     ebx                                 ; ax = StartLBA / MaxSector
    240         inc     dx                                  ; dx = (StartLBA % MaxSector) + 1
    241 
    242         mov     bx,word ptr [bp]                    ; bx = MaxSector
    243         sub     bx,dx                               ; bx = MaxSector - Sector
    244         inc     bx                                  ; bx = MaxSector - Sector + 1
    245         cmp     cx,bx                               ; Compare (Blocks) to (MaxSector - Sector + 1)
    246         jg      LimitTransfer
    247         mov     bx,cx                               ; bx = Blocks
    248 LimitTransfer:
    249         push    ax                                  ; save ax
    250         mov     ax,es                               ; ax = es
    251         shr     ax,(BLOCK_SHIFT-4)                  ; ax = Number of blocks into mem system
    252         and     ax,07fh                             ; ax = Number of blocks into current seg
    253         add     ax,bx                               ; ax = End Block number of transfer
    254         cmp     ax,080h                             ; See if it crosses a 64K boundry
    255         jle     NotCrossing64KBoundry               ; Branch if not crossing 64K boundry
    256         sub     ax,080h                             ; ax = Number of blocks past 64K boundry
    257         sub     bx,ax                               ; Decrease transfer size by block overage
    258 NotCrossing64KBoundry:
    259         pop     ax                                  ; restore ax
    260 
    261         push    cx
    262         mov     cl,dl                               ; cl = (StartLBA % MaxSector) + 1 = Sector
    263         xor     dx,dx                               ; dx = 0
    264         div     word ptr [bp+2]                     ; ax = ax / (MaxHead + 1) = Cylinder  
    265                                                     ; dx = ax % (MaxHead + 1) = Head
    266 
    267         push    bx                                  ; Save number of blocks to transfer
    268         mov     dh,dl                               ; dh = Head
    269         mov     bp,07c00h                           ; bp = 0x7c00
    270         mov     dl,byte ptr [bp+PhysicalDrive]      ; dl = Drive Number
    271         mov     ch,al                               ; ch = Cylinder
    272         mov     al,bl                               ; al = Blocks
    273         mov     ah,2                                ; ah = Function 2
    274         mov     bx,di                               ; es:bx = Buffer address
    275         int     013h
    276         jc      DiskError
    277         pop     bx
    278         pop     cx
    279         movzx   ebx,bx
    280         add     esi,ebx                             ; StartLBA = StartLBA + NumberOfBlocks
    281         sub     cx,bx                               ; Blocks = Blocks - NumberOfBlocks
    282         mov     ax,es
    283         shl     bx,(BLOCK_SHIFT-4)
    284         add     ax,bx
    285         mov     es,ax                               ; es:di = es:di + NumberOfBlocks*BLOCK_SIZE
    286         cmp     cx,0
    287         jne     ReadCylinderLoop
    288         popa
    289         ret
    290 
    291 DiskError:
    292         push cs
    293         pop  ds
    294         lea  si, [ErrorString]
    295         mov  cx, 7
    296         jmp  PrintStringAndHalt
    297 
    298 PrintStringAndHalt:
    299         mov  ax,0b800h
    300         mov  es,ax
    301         mov  di,160
    302         rep  movsw
    303 Halt:
    304         jmp   Halt
    305 
    306 ErrorString:
    307         db 'S', 0ch, 'E', 0ch, 'r', 0ch, 'r', 0ch, 'o', 0ch, 'r', 0ch, '!', 0ch
    308 
    309         org     01fah
    310 LBAOffsetForBootSector:
    311         dd      0h
    312 
    313         org     01feh
    314         dw      0aa55h
    315 
    316 ;******************************************************************************
    317 ;******************************************************************************
    318 ;******************************************************************************
    319 
    320 DELAY_PORT           equ     0edh    ; Port to use for 1uS delay
    321 KBD_CONTROL_PORT     equ     060h    ; 8042 control port     
    322 KBD_STATUS_PORT      equ     064h    ; 8042 status port      
    323 WRITE_DATA_PORT_CMD  equ     0d1h    ; 8042 command to write the data port
    324 ENABLE_A20_CMD       equ     0dfh    ; 8042 command to enable A20
    325 
    326         org     200h
    327         jmp start
    328 Em64String:
    329         db 'E', 0ch, 'm', 0ch, '6', 0ch, '4', 0ch, 'T', 0ch, ' ', 0ch, 'U', 0ch, 'n', 0ch, 's', 0ch, 'u', 0ch, 'p', 0ch, 'p', 0ch, 'o', 0ch, 'r', 0ch, 't', 0ch, 'e', 0ch, 'd', 0ch, '!', 0ch
    330 
    331 start:  
    332         mov ax,cs
    333         mov ds,ax
    334         mov es,ax
    335         mov ss,ax
    336         mov sp,MyStack
    337 
    338 ;        mov ax,0b800h
    339 ;        mov es,ax
    340 ;        mov byte ptr es:[160],'a'
    341 ;        mov ax,cs
    342 ;        mov es,ax
    343 
    344         mov ebx,0
    345         lea edi,MemoryMap
    346 MemMapLoop:
    347         mov eax,0e820h
    348         mov ecx,20
    349         mov edx,'SMAP'
    350         int 15h
    351         jc  MemMapDone
    352         add edi,20
    353         cmp ebx,0
    354         je  MemMapDone
    355         jmp MemMapLoop
    356 MemMapDone:
    357         lea eax,MemoryMap
    358         sub edi,eax                         ; Get the address of the memory map
    359         mov dword ptr [MemoryMapSize],edi   ; Save the size of the memory map
    360 
    361         xor     ebx,ebx
    362         mov     bx,cs                       ; BX=segment
    363         shl     ebx,4                       ; BX="linear" address of segment base
    364         lea     eax,[GDT_BASE + ebx]        ; EAX=PHYSICAL address of gdt
    365         mov     dword ptr [gdtr + 2],eax    ; Put address of gdt into the gdtr
    366         lea     eax,[IDT_BASE + ebx]        ; EAX=PHYSICAL address of idt
    367         mov     dword ptr [idtr + 2],eax    ; Put address of idt into the idtr
    368         lea     edx,[MemoryMapSize + ebx]   ; Physical base address of the memory map
    369 
    370         add ebx,01000h                      ; Source of EFI32
    371         mov dword ptr [JUMP+2],ebx
    372         add ebx,01000h
    373         mov esi,ebx                         ; Source of EFILDR32
    374 
    375 ;        mov ax,0b800h
    376 ;        mov es,ax
    377 ;        mov byte ptr es:[162],'b'
    378 ;        mov ax,cs
    379 ;        mov es,ax
    380 
    381 ;
    382 ; Enable A20 Gate 
    383 ;
    384 
    385         mov ax,2401h                        ; Enable A20 Gate
    386         int 15h
    387         jnc A20GateEnabled                  ; Jump if it suceeded
    388 
    389 ;
    390 ; If INT 15 Function 2401 is not supported, then attempt to Enable A20 manually.
    391 ;
    392 
    393         call    Empty8042InputBuffer        ; Empty the Input Buffer on the 8042 controller
    394         jnz     Timeout8042                 ; Jump if the 8042 timed out
    395         out     DELAY_PORT,ax               ; Delay 1 uS
    396         mov     al,WRITE_DATA_PORT_CMD      ; 8042 cmd to write output port
    397         out     KBD_STATUS_PORT,al          ; Send command to the 8042
    398         call    Empty8042InputBuffer        ; Empty the Input Buffer on the 8042 controller
    399         jnz     Timeout8042                 ; Jump if the 8042 timed out
    400         mov     al,ENABLE_A20_CMD           ; gate address bit 20 on
    401         out     KBD_CONTROL_PORT,al         ; Send command to thre 8042
    402         call    Empty8042InputBuffer        ; Empty the Input Buffer on the 8042 controller
    403         mov     cx,25                       ; Delay 25 uS for the command to complete on the 8042
    404 Delay25uS:
    405         out     DELAY_PORT,ax               ; Delay 1 uS
    406         loop    Delay25uS                       
    407 Timeout8042:
    408 
    409 
    410 A20GateEnabled:
    411         mov     bx,0008h                    ; Flat data descriptor
    412 ;
    413 ; DISABLE INTERRUPTS - Entering Protected Mode
    414 ;
    415 
    416         cli                             
    417 
    418 ;        mov ax,0b800h
    419 ;        mov es,ax
    420 ;        mov byte ptr es:[164],'c'
    421 ;        mov ax,cs
    422 ;        mov es,ax
    423 
    424         db      66h     
    425         lgdt    fword ptr [gdtr]
    426         db      66h     
    427         lidt    fword ptr [idtr]
    428 
    429         mov     eax,cr0
    430         or      al,1
    431         mov     cr0,eax
    432 JUMP:
    433 ; jmp far 0010:00020000
    434         db  066h
    435         db  0eah
    436         dd  000020000h
    437         dw  00010h
    438 
    439 Empty8042InputBuffer:
    440         mov cx,0
    441 Empty8042Loop:
    442         out     DELAY_PORT,ax               ; Delay 1us
    443         in      al,KBD_STATUS_PORT          ; Read the 8042 Status Port
    444         and     al,02h                      ; Check the Input Buffer Full Flag
    445         loopnz  Empty8042Loop               ; Loop until the input buffer is empty or a timout of 65536 uS
    446         ret
    447 
    448 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    449 ; data
    450 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    451 
    452         align 02h
    453 
    454 gdtr    dw GDT_END - GDT_BASE - 1   ; GDT limit
    455         dd 0                        ; (GDT base gets set above)
    456 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    457 ;   global descriptor table (GDT)
    458 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    459 
    460         align 02h
    461 
    462 public GDT_BASE
    463 GDT_BASE:
    464 ; null descriptor
    465 NULL_SEL            equ $-GDT_BASE
    466         dw 0            ; limit 15:0
    467         dw 0            ; base 15:0
    468         db 0            ; base 23:16
    469         db 0            ; type
    470         db 0            ; limit 19:16, flags
    471         db 0            ; base 31:24
    472 
    473 ; linear data segment descriptor
    474 LINEAR_SEL      equ $-GDT_BASE
    475         dw 0FFFFh       ; limit 0xFFFFF
    476         dw 0            ; base 0
    477         db 0
    478         db 092h         ; present, ring 0, data, expand-up, writable
    479         db 0CFh                 ; page-granular, 32-bit
    480         db 0
    481 
    482 ; linear code segment descriptor
    483 LINEAR_CODE_SEL equ $-GDT_BASE
    484         dw 0FFFFh       ; limit 0xFFFFF
    485         dw 0            ; base 0
    486         db 0
    487         db 09Ah         ; present, ring 0, data, expand-up, writable
    488         db 0CFh                 ; page-granular, 32-bit
    489         db 0
    490 
    491 ; system data segment descriptor
    492 SYS_DATA_SEL    equ $-GDT_BASE
    493         dw 0FFFFh       ; limit 0xFFFFF
    494         dw 0            ; base 0
    495         db 0
    496         db 092h         ; present, ring 0, data, expand-up, writable
    497         db 0CFh                 ; page-granular, 32-bit
    498         db 0
    499 
    500 ; system code segment descriptor
    501 SYS_CODE_SEL    equ $-GDT_BASE
    502         dw 0FFFFh       ; limit 0xFFFFF
    503         dw 0            ; base 0
    504         db 0
    505         db 09Ah         ; present, ring 0, data, expand-up, writable
    506         db 0CFh                 ; page-granular, 32-bit
    507         db 0
    508 
    509 ; spare segment descriptor
    510 SPARE3_SEL  equ $-GDT_BASE
    511         dw 0            ; limit 0xFFFFF
    512         dw 0            ; base 0
    513         db 0
    514         db 0            ; present, ring 0, data, expand-up, writable
    515         db 0            ; page-granular, 32-bit
    516         db 0
    517 
    518 ; spare segment descriptor
    519 SPARE4_SEL  equ $-GDT_BASE
    520         dw 0            ; limit 0xFFFFF
    521         dw 0            ; base 0
    522         db 0
    523         db 0            ; present, ring 0, data, expand-up, writable
    524         db 0            ; page-granular, 32-bit
    525         db 0
    526 
    527 ; spare segment descriptor
    528 SPARE5_SEL  equ $-GDT_BASE
    529         dw 0            ; limit 0xFFFFF
    530         dw 0            ; base 0
    531         db 0
    532         db 0            ; present, ring 0, data, expand-up, writable
    533         db 0            ; page-granular, 32-bit
    534         db 0
    535 
    536 GDT_END:
    537 
    538         align 02h
    539 
    540 
    541 
    542 idtr            dw IDT_END - IDT_BASE - 1   ; IDT limit
    543         dd 0                        ; (IDT base gets set above)
    544 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    545 ;   interrupt descriptor table (IDT)
    546 ;
    547 ;   Note: The hardware IRQ's specified in this table are the normal PC/AT IRQ
    548 ;       mappings.  This implementation only uses the system timer and all other
    549 ;       IRQs will remain masked.  The descriptors for vectors 33+ are provided
    550 ;       for convenience.
    551 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    552 
    553 ;idt_tag db "IDT",0     
    554         align 02h
    555 
    556 public IDT_BASE
    557 IDT_BASE:
    558 ; divide by zero (INT 0)
    559 DIV_ZERO_SEL        equ $-IDT_BASE
    560         dw 0            ; offset 15:0
    561         dw SYS_CODE_SEL ; selector 15:0
    562         db 0            ; 0 for interrupt gate
    563         db 0eh OR 80h   ; type = 386 interrupt gate, present
    564         dw 0            ; offset 31:16
    565 
    566 ; debug exception (INT 1)
    567 DEBUG_EXCEPT_SEL    equ $-IDT_BASE
    568         dw 0            ; offset 15:0
    569         dw SYS_CODE_SEL ; selector 15:0
    570         db 0            ; 0 for interrupt gate
    571         db 0eh OR 80h   ; type = 386 interrupt gate, present
    572         dw 0            ; offset 31:16
    573 
    574 ; NMI (INT 2)
    575 NMI_SEL             equ $-IDT_BASE
    576         dw 0            ; offset 15:0
    577         dw SYS_CODE_SEL ; selector 15:0
    578         db 0            ; 0 for interrupt gate
    579         db 0eh OR 80h   ; type = 386 interrupt gate, present
    580         dw 0            ; offset 31:16
    581 
    582 ; soft breakpoint (INT 3)
    583 BREAKPOINT_SEL      equ $-IDT_BASE
    584         dw 0            ; offset 15:0
    585         dw SYS_CODE_SEL ; selector 15:0
    586         db 0            ; 0 for interrupt gate
    587         db 0eh OR 80h   ; type = 386 interrupt gate, present
    588         dw 0            ; offset 31:16
    589 
    590 ; overflow (INT 4)
    591 OVERFLOW_SEL        equ $-IDT_BASE
    592         dw 0            ; offset 15:0
    593         dw SYS_CODE_SEL ; selector 15:0
    594         db 0            ; 0 for interrupt gate
    595         db 0eh OR 80h   ; type = 386 interrupt gate, present
    596         dw 0            ; offset 31:16
    597 
    598 ; bounds check (INT 5)
    599 BOUNDS_CHECK_SEL    equ $-IDT_BASE
    600         dw 0            ; offset 15:0
    601         dw SYS_CODE_SEL ; selector 15:0
    602         db 0            ; 0 for interrupt gate
    603         db 0eh OR 80h   ; type = 386 interrupt gate, present
    604         dw 0            ; offset 31:16
    605 
    606 ; invalid opcode (INT 6)
    607 INVALID_OPCODE_SEL  equ $-IDT_BASE
    608         dw 0            ; offset 15:0
    609         dw SYS_CODE_SEL ; selector 15:0
    610         db 0            ; 0 for interrupt gate
    611         db 0eh OR 80h   ; type = 386 interrupt gate, present
    612         dw 0            ; offset 31:16
    613 
    614 ; device not available (INT 7)
    615 DEV_NOT_AVAIL_SEL   equ $-IDT_BASE
    616         dw 0            ; offset 15:0
    617         dw SYS_CODE_SEL ; selector 15:0
    618         db 0            ; 0 for interrupt gate
    619         db 0eh OR 80h   ; type = 386 interrupt gate, present
    620         dw 0            ; offset 31:16
    621 
    622 ; double fault (INT 8)
    623 DOUBLE_FAULT_SEL    equ $-IDT_BASE
    624         dw 0            ; offset 15:0
    625         dw SYS_CODE_SEL ; selector 15:0
    626         db 0            ; 0 for interrupt gate
    627         db 0eh OR 80h   ; type = 386 interrupt gate, present
    628         dw 0            ; offset 31:16
    629 
    630 ; Coprocessor segment overrun - reserved (INT 9)
    631 RSVD_INTR_SEL1      equ $-IDT_BASE
    632         dw 0            ; offset 15:0
    633         dw SYS_CODE_SEL ; selector 15:0
    634         db 0            ; 0 for interrupt gate
    635         db 0eh OR 80h   ; type = 386 interrupt gate, present
    636         dw 0            ; offset 31:16
    637 
    638 ; invalid TSS (INT 0ah)
    639 INVALID_TSS_SEL     equ $-IDT_BASE
    640         dw 0            ; offset 15:0
    641         dw SYS_CODE_SEL ; selector 15:0
    642         db 0            ; 0 for interrupt gate
    643         db 0eh OR 80h   ; type = 386 interrupt gate, present
    644         dw 0            ; offset 31:16
    645 
    646 ; segment not present (INT 0bh)
    647 SEG_NOT_PRESENT_SEL equ $-IDT_BASE
    648         dw 0            ; offset 15:0
    649         dw SYS_CODE_SEL ; selector 15:0
    650         db 0            ; 0 for interrupt gate
    651         db 0eh OR 80h   ; type = 386 interrupt gate, present
    652         dw 0            ; offset 31:16
    653 
    654 ; stack fault (INT 0ch)
    655 STACK_FAULT_SEL     equ $-IDT_BASE
    656         dw 0            ; offset 15:0
    657         dw SYS_CODE_SEL ; selector 15:0
    658         db 0            ; 0 for interrupt gate
    659         db 0eh OR 80h   ; type = 386 interrupt gate, present
    660         dw 0            ; offset 31:16
    661 
    662 ; general protection (INT 0dh)
    663 GP_FAULT_SEL        equ $-IDT_BASE
    664         dw 0            ; offset 15:0
    665         dw SYS_CODE_SEL ; selector 15:0
    666         db 0            ; 0 for interrupt gate
    667         db 0eh OR 80h   ; type = 386 interrupt gate, present
    668         dw 0            ; offset 31:16
    669 
    670 ; page fault (INT 0eh)
    671 PAGE_FAULT_SEL      equ $-IDT_BASE
    672         dw 0            ; offset 15:0
    673         dw SYS_CODE_SEL ; selector 15:0
    674         db 0            ; 0 for interrupt gate
    675         db 0eh OR 80h   ; type = 386 interrupt gate, present
    676         dw 0            ; offset 31:16
    677 
    678 ; Intel reserved - do not use (INT 0fh)
    679 RSVD_INTR_SEL2      equ $-IDT_BASE
    680         dw 0            ; offset 15:0
    681         dw SYS_CODE_SEL ; selector 15:0
    682         db 0            ; 0 for interrupt gate
    683         db 0eh OR 80h   ; type = 386 interrupt gate, present
    684         dw 0            ; offset 31:16
    685 
    686 ; floating point error (INT 10h)
    687 FLT_POINT_ERR_SEL   equ $-IDT_BASE
    688         dw 0            ; offset 15:0
    689         dw SYS_CODE_SEL ; selector 15:0
    690         db 0            ; 0 for interrupt gate
    691         db 0eh OR 80h   ; type = 386 interrupt gate, present
    692         dw 0            ; offset 31:16
    693 
    694 ; alignment check (INT 11h)
    695 ALIGNMENT_CHECK_SEL equ $-IDT_BASE
    696         dw 0            ; offset 15:0
    697         dw SYS_CODE_SEL ; selector 15:0
    698         db 0            ; 0 for interrupt gate
    699         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    700         dw 0            ; offset 31:16
    701 
    702 ; machine check (INT 12h)
    703 MACHINE_CHECK_SEL   equ $-IDT_BASE
    704         dw 0            ; offset 15:0
    705         dw SYS_CODE_SEL ; selector 15:0
    706         db 0            ; 0 for interrupt gate
    707         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    708         dw 0            ; offset 31:16
    709 
    710 ; SIMD floating-point exception (INT 13h)
    711 SIMD_EXCEPTION_SEL  equ $-IDT_BASE
    712         dw 0            ; offset 15:0
    713         dw SYS_CODE_SEL ; selector 15:0
    714         db 0            ; 0 for interrupt gate
    715         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    716         dw 0            ; offset 31:16
    717 
    718 ; 85 unspecified descriptors, First 12 of them are reserved, the rest are avail
    719         db (85 * 8) dup(0)
    720         
    721 ; IRQ 0 (System timer) - (INT 68h)
    722 IRQ0_SEL            equ $-IDT_BASE
    723         dw 0            ; offset 15:0
    724         dw SYS_CODE_SEL ; selector 15:0
    725         db 0            ; 0 for interrupt gate
    726         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    727         dw 0            ; offset 31:16
    728 
    729 ; IRQ 1 (8042 Keyboard controller) - (INT 69h)
    730 IRQ1_SEL            equ $-IDT_BASE
    731         dw 0            ; offset 15:0
    732         dw SYS_CODE_SEL ; selector 15:0
    733         db 0            ; 0 for interrupt gate
    734         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    735         dw 0            ; offset 31:16
    736 
    737 ; Reserved - IRQ 2 redirect (IRQ 2) - DO NOT USE!!! - (INT 6ah)
    738 IRQ2_SEL            equ $-IDT_BASE
    739         dw 0            ; offset 15:0
    740         dw SYS_CODE_SEL ; selector 15:0
    741         db 0            ; 0 for interrupt gate
    742         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    743         dw 0            ; offset 31:16
    744 
    745 ; IRQ 3 (COM 2) - (INT 6bh)
    746 IRQ3_SEL            equ $-IDT_BASE
    747         dw 0            ; offset 15:0
    748         dw SYS_CODE_SEL ; selector 15:0
    749         db 0            ; 0 for interrupt gate
    750         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    751         dw 0            ; offset 31:16
    752 
    753 ; IRQ 4 (COM 1) - (INT 6ch)
    754 IRQ4_SEL            equ $-IDT_BASE
    755         dw 0            ; offset 15:0
    756         dw SYS_CODE_SEL ; selector 15:0
    757         db 0            ; 0 for interrupt gate
    758         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    759         dw 0            ; offset 31:16
    760 
    761 ; IRQ 5 (LPT 2) - (INT 6dh)
    762 IRQ5_SEL            equ $-IDT_BASE
    763         dw 0            ; offset 15:0
    764         dw SYS_CODE_SEL ; selector 15:0
    765         db 0            ; 0 for interrupt gate
    766         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    767         dw 0            ; offset 31:16
    768 
    769 ; IRQ 6 (Floppy controller) - (INT 6eh)
    770 IRQ6_SEL            equ $-IDT_BASE
    771         dw 0            ; offset 15:0
    772         dw SYS_CODE_SEL ; selector 15:0
    773         db 0            ; 0 for interrupt gate
    774         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    775         dw 0            ; offset 31:16
    776 
    777 ; IRQ 7 (LPT 1) - (INT 6fh)
    778 IRQ7_SEL            equ $-IDT_BASE
    779         dw 0            ; offset 15:0
    780         dw SYS_CODE_SEL ; selector 15:0
    781         db 0            ; 0 for interrupt gate
    782         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    783         dw 0            ; offset 31:16
    784 
    785 ; IRQ 8 (RTC Alarm) - (INT 70h)
    786 IRQ8_SEL            equ $-IDT_BASE
    787         dw 0            ; offset 15:0
    788         dw SYS_CODE_SEL ; selector 15:0
    789         db 0            ; 0 for interrupt gate
    790         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    791         dw 0            ; offset 31:16
    792 
    793 ; IRQ 9 - (INT 71h)
    794 IRQ9_SEL            equ $-IDT_BASE
    795         dw 0            ; offset 15:0
    796         dw SYS_CODE_SEL ; selector 15:0
    797         db 0            ; 0 for interrupt gate
    798         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    799         dw 0            ; offset 31:16
    800 
    801 ; IRQ 10 - (INT 72h)
    802 IRQ10_SEL            equ $-IDT_BASE
    803         dw 0            ; offset 15:0
    804         dw SYS_CODE_SEL ; selector 15:0
    805         db 0            ; 0 for interrupt gate
    806         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    807         dw 0            ; offset 31:16
    808 
    809 ; IRQ 11 - (INT 73h)
    810 IRQ11_SEL            equ $-IDT_BASE
    811         dw 0            ; offset 15:0
    812         dw SYS_CODE_SEL ; selector 15:0
    813         db 0            ; 0 for interrupt gate
    814         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    815         dw 0            ; offset 31:16
    816 
    817 ; IRQ 12 (PS/2 mouse) - (INT 74h)
    818 IRQ12_SEL            equ $-IDT_BASE
    819         dw 0            ; offset 15:0
    820         dw SYS_CODE_SEL ; selector 15:0
    821         db 0            ; 0 for interrupt gate
    822         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    823         dw 0            ; offset 31:16
    824 
    825 ; IRQ 13 (Floating point error) - (INT 75h)
    826 IRQ13_SEL            equ $-IDT_BASE
    827         dw 0            ; offset 15:0
    828         dw SYS_CODE_SEL ; selector 15:0
    829         db 0            ; 0 for interrupt gate
    830         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    831         dw 0            ; offset 31:16
    832 
    833 ; IRQ 14 (Secondary IDE) - (INT 76h)
    834 IRQ14_SEL            equ $-IDT_BASE
    835         dw 0            ; offset 15:0
    836         dw SYS_CODE_SEL ; selector 15:0
    837         db 0            ; 0 for interrupt gate
    838         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    839         dw 0            ; offset 31:16
    840 
    841 ; IRQ 15 (Primary IDE) - (INT 77h)
    842 IRQ15_SEL            equ $-IDT_BASE
    843         dw 0            ; offset 15:0
    844         dw SYS_CODE_SEL ; selector 15:0
    845         db 0            ; 0 for interrupt gate
    846         db 0eh OR 80h   ; (10001110)type = 386 interrupt gate, present
    847         dw 0            ; offset 31:16
    848 
    849 IDT_END:
    850 
    851         align 02h
    852 
    853 MemoryMapSize   dd  0
    854 MemoryMap   dd  0,0,0,0,0,0,0,0
    855         dd  0,0,0,0,0,0,0,0
    856         dd  0,0,0,0,0,0,0,0
    857         dd  0,0,0,0,0,0,0,0
    858         dd  0,0,0,0,0,0,0,0
    859         dd  0,0,0,0,0,0,0,0
    860         dd  0,0,0,0,0,0,0,0
    861         dd  0,0,0,0,0,0,0,0
    862         dd  0,0,0,0,0,0,0,0
    863         dd  0,0,0,0,0,0,0,0
    864         dd  0,0,0,0,0,0,0,0
    865         dd  0,0,0,0,0,0,0,0
    866         dd  0,0,0,0,0,0,0,0
    867         dd  0,0,0,0,0,0,0,0
    868         dd  0,0,0,0,0,0,0,0
    869         dd  0,0,0,0,0,0,0,0
    870         dd  0,0,0,0,0,0,0,0
    871         dd  0,0,0,0,0,0,0,0
    872         dd  0,0,0,0,0,0,0,0
    873         dd  0,0,0,0,0,0,0,0
    874         dd  0,0,0,0,0,0,0,0
    875         dd  0,0,0,0,0,0,0,0
    876         dd  0,0,0,0,0,0,0,0
    877         dd  0,0,0,0,0,0,0,0
    878         dd  0,0,0,0,0,0,0,0
    879         dd  0,0,0,0,0,0,0,0
    880         dd  0,0,0,0,0,0,0,0
    881         dd  0,0,0,0,0,0,0,0
    882         dd  0,0,0,0,0,0,0,0
    883         dd  0,0,0,0,0,0,0,0
    884 
    885         dd  0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
    886         dd  0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
    887 
    888         org 0fe0h
    889 MyStack:    
    890         ; below is the pieces of the IVT that is used to redirect INT 68h - 6fh
    891         ;    back to INT 08h - 0fh  when in real mode...  It is 'org'ed to a
    892         ;    known low address (20f00) so it can be set up by PlMapIrqToVect in
    893         ;    8259.c
    894                 
    895         int 8
    896         iret
    897         
    898         int 9
    899         iret
    900         
    901         int 10
    902         iret
    903         
    904         int 11
    905         iret
    906         
    907         int 12
    908         iret
    909         
    910         int 13
    911         iret
    912         
    913         int 14
    914         iret
    915         
    916         int 15
    917         iret
    918         
    919         
    920         org 0ffeh
    921 BlockSignature:
    922         dw  0aa55h
    923 
    924         end 
    925