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