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